llama-cpp-hs
Safe HaskellNone
LanguageHaskell2010

Llama.Internal.Types

Synopsis

Types

data LlamaTokenData Source #

Constructors

LlamaTokenData 

Fields

Instances

Instances details
GStorable LlamaTokenData Source # 
Instance details

Defined in Llama.Internal.Types

Generic LlamaTokenData Source # 
Instance details

Defined in Llama.Internal.Types

Associated Types

type Rep LlamaTokenData 
Instance details

Defined in Llama.Internal.Types

type Rep LlamaTokenData = D1 ('MetaData "LlamaTokenData" "Llama.Internal.Types" "llama-cpp-hs-0.1.0.0-inplace" 'False) (C1 ('MetaCons "LlamaTokenData" 'PrefixI 'True) (S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LlamaToken) :*: (S1 ('MetaSel ('Just "logit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CFloat) :*: S1 ('MetaSel ('Just "p") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CFloat))))
Show LlamaTokenData Source # 
Instance details

Defined in Llama.Internal.Types

Eq LlamaTokenData Source # 
Instance details

Defined in Llama.Internal.Types

type Rep LlamaTokenData Source # 
Instance details

Defined in Llama.Internal.Types

type Rep LlamaTokenData = D1 ('MetaData "LlamaTokenData" "Llama.Internal.Types" "llama-cpp-hs-0.1.0.0-inplace" 'False) (C1 ('MetaCons "LlamaTokenData" 'PrefixI 'True) (S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LlamaToken) :*: (S1 ('MetaSel ('Just "logit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CFloat) :*: S1 ('MetaSel ('Just "p") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CFloat))))

data LlamaTokenDataArray Source #

Constructors

LlamaTokenDataArray 

Fields

Instances

Instances details
GStorable LlamaTokenDataArray Source # 
Instance details

Defined in Llama.Internal.Types

Generic LlamaTokenDataArray Source # 
Instance details

Defined in Llama.Internal.Types

Associated Types

type Rep LlamaTokenDataArray 
Instance details

Defined in Llama.Internal.Types

type Rep LlamaTokenDataArray = D1 ('MetaData "LlamaTokenDataArray" "Llama.Internal.Types" "llama-cpp-hs-0.1.0.0-inplace" 'False) (C1 ('MetaCons "LlamaTokenDataArray" 'PrefixI 'True) ((S1 ('MetaSel ('Just "data_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ptr LlamaTokenData)) :*: S1 ('MetaSel ('Just "size_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CSize)) :*: (S1 ('MetaSel ('Just "selected") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CLong) :*: S1 ('MetaSel ('Just "sorted") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CBool))))
Show LlamaTokenDataArray Source # 
Instance details

Defined in Llama.Internal.Types

Eq LlamaTokenDataArray Source # 
Instance details

Defined in Llama.Internal.Types

type Rep LlamaTokenDataArray Source # 
Instance details

Defined in Llama.Internal.Types

type Rep LlamaTokenDataArray = D1 ('MetaData "LlamaTokenDataArray" "Llama.Internal.Types" "llama-cpp-hs-0.1.0.0-inplace" 'False) (C1 ('MetaCons "LlamaTokenDataArray" 'PrefixI 'True) ((S1 ('MetaSel ('Just "data_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ptr LlamaTokenData)) :*: S1 ('MetaSel ('Just "size_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CSize)) :*: (S1 ('MetaSel ('Just "selected") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CLong) :*: S1 ('MetaSel ('Just "sorted") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CBool))))

data LlamaBatch Source #

Constructors

LlamaBatch 

Fields

Instances

Instances details
GStorable LlamaBatch Source # 
Instance details

Defined in Llama.Internal.Types

Generic LlamaBatch Source # 
Instance details

Defined in Llama.Internal.Types

Show LlamaBatch Source # 
Instance details

Defined in Llama.Internal.Types

Eq LlamaBatch Source # 
Instance details

Defined in Llama.Internal.Types

type Rep LlamaBatch Source # 
Instance details

Defined in Llama.Internal.Types

data AddBos Source #

Constructors

Always 
Never 

data LlamaKvCacheView Source #

Corresponds to `struct llama_kv_cache_view`

Constructors

LlamaKvCacheView 

Fields

data LlamaChatMessage Source #

Constructors

LlamaChatMessage 

Fields

Instances

Instances details
GStorable LlamaChatMessage Source # 
Instance details

Defined in Llama.Internal.Types

Generic LlamaChatMessage Source # 
Instance details

Defined in Llama.Internal.Types

Associated Types

type Rep LlamaChatMessage 
Instance details

Defined in Llama.Internal.Types

type Rep LlamaChatMessage = D1 ('MetaData "LlamaChatMessage" "Llama.Internal.Types" "llama-cpp-hs-0.1.0.0-inplace" 'False) (C1 ('MetaCons "LlamaChatMessage" 'PrefixI 'True) (S1 ('MetaSel ('Just "role") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CString) :*: S1 ('MetaSel ('Just "content") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CString)))
Show LlamaChatMessage Source # 
Instance details

Defined in Llama.Internal.Types

Eq LlamaChatMessage Source # 
Instance details

Defined in Llama.Internal.Types

type Rep LlamaChatMessage Source # 
Instance details

Defined in Llama.Internal.Types

type Rep LlamaChatMessage = D1 ('MetaData "LlamaChatMessage" "Llama.Internal.Types" "llama-cpp-hs-0.1.0.0-inplace" 'False) (C1 ('MetaCons "LlamaChatMessage" 'PrefixI 'True) (S1 ('MetaSel ('Just "role") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CString) :*: S1 ('MetaSel ('Just "content") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CString)))

data LlamaSamplerI Source #

Corresponds to `struct llama_sampler_i`

Constructors

LlamaSamplerI 

Fields

Instances

Instances details
GStorable LlamaSamplerI Source # 
Instance details

Defined in Llama.Internal.Types

Generic LlamaSamplerI Source # 
Instance details

Defined in Llama.Internal.Types

Show LlamaSamplerI Source # 
Instance details

Defined in Llama.Internal.Types

Eq LlamaSamplerI Source # 
Instance details

Defined in Llama.Internal.Types

type Rep LlamaSamplerI Source # 
Instance details

Defined in Llama.Internal.Types

data LlamaSampler Source #

Corresponds to `struct llama_sampler`

Constructors

LlamaSampler 

Fields

Instances

Instances details
GStorable LlamaSampler Source # 
Instance details

Defined in Llama.Internal.Types

Generic LlamaSampler Source # 
Instance details

Defined in Llama.Internal.Types

Associated Types

type Rep LlamaSampler 
Instance details

Defined in Llama.Internal.Types

type Rep LlamaSampler = D1 ('MetaData "LlamaSampler" "Llama.Internal.Types" "llama-cpp-hs-0.1.0.0-inplace" 'False) (C1 ('MetaCons "LlamaSampler" 'PrefixI 'True) (S1 ('MetaSel ('Just "iface") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ptr LlamaSamplerI)) :*: S1 ('MetaSel ('Just "ctx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LlamaSamplerContext)))
Show LlamaSampler Source # 
Instance details

Defined in Llama.Internal.Types

Eq LlamaSampler Source # 
Instance details

Defined in Llama.Internal.Types

type Rep LlamaSampler Source # 
Instance details

Defined in Llama.Internal.Types

type Rep LlamaSampler = D1 ('MetaData "LlamaSampler" "Llama.Internal.Types" "llama-cpp-hs-0.1.0.0-inplace" 'False) (C1 ('MetaCons "LlamaSampler" 'PrefixI 'True) (S1 ('MetaSel ('Just "iface") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ptr LlamaSamplerI)) :*: S1 ('MetaSel ('Just "ctx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LlamaSamplerContext)))

type LlamaSamplerContext = Ptr () Source #

Corresponds to llama_sampler_context_t (void *)

data LlamaPerfContextData Source #

Constructors

LlamaPerfContextData 

Fields

Instances

Instances details
GStorable LlamaPerfContextData Source # 
Instance details

Defined in Llama.Internal.Types

Generic LlamaPerfContextData Source # 
Instance details

Defined in Llama.Internal.Types

Associated Types

type Rep LlamaPerfContextData 
Instance details

Defined in Llama.Internal.Types

Show LlamaPerfContextData Source # 
Instance details

Defined in Llama.Internal.Types

Eq LlamaPerfContextData Source # 
Instance details

Defined in Llama.Internal.Types

type Rep LlamaPerfContextData Source # 
Instance details

Defined in Llama.Internal.Types

data LlamaPerfSamplerData Source #

Constructors

LlamaPerfSamplerData 

Fields

Instances

Instances details
GStorable LlamaPerfSamplerData Source # 
Instance details

Defined in Llama.Internal.Types

Generic LlamaPerfSamplerData Source # 
Instance details

Defined in Llama.Internal.Types

Associated Types

type Rep LlamaPerfSamplerData 
Instance details

Defined in Llama.Internal.Types

type Rep LlamaPerfSamplerData = D1 ('MetaData "LlamaPerfSamplerData" "Llama.Internal.Types" "llama-cpp-hs-0.1.0.0-inplace" 'False) (C1 ('MetaCons "LlamaPerfSamplerData" 'PrefixI 'True) (S1 ('MetaSel ('Just "t_sample_ms") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CDouble) :*: S1 ('MetaSel ('Just "n_sample") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt)))
Show LlamaPerfSamplerData Source # 
Instance details

Defined in Llama.Internal.Types

Eq LlamaPerfSamplerData Source # 
Instance details

Defined in Llama.Internal.Types

type Rep LlamaPerfSamplerData Source # 
Instance details

Defined in Llama.Internal.Types

type Rep LlamaPerfSamplerData = D1 ('MetaData "LlamaPerfSamplerData" "Llama.Internal.Types" "llama-cpp-hs-0.1.0.0-inplace" 'False) (C1 ('MetaCons "LlamaPerfSamplerData" 'PrefixI 'True) (S1 ('MetaSel ('Just "t_sample_ms") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CDouble) :*: S1 ('MetaSel ('Just "n_sample") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CInt)))

data LlamaLogitBias Source #

Constructors

LlamaLogitBias 

Instances

Instances details
GStorable LlamaLogitBias Source # 
Instance details

Defined in Llama.Internal.Types

Generic LlamaLogitBias Source # 
Instance details

Defined in Llama.Internal.Types

Associated Types

type Rep LlamaLogitBias 
Instance details

Defined in Llama.Internal.Types

type Rep LlamaLogitBias = D1 ('MetaData "LlamaLogitBias" "Llama.Internal.Types" "llama-cpp-hs-0.1.0.0-inplace" 'False) (C1 ('MetaCons "LlamaLogitBias" 'PrefixI 'True) (S1 ('MetaSel ('Just "tokenLogitBias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LlamaToken) :*: S1 ('MetaSel ('Just "bias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float)))
Show LlamaLogitBias Source # 
Instance details

Defined in Llama.Internal.Types

Eq LlamaLogitBias Source # 
Instance details

Defined in Llama.Internal.Types

type Rep LlamaLogitBias Source # 
Instance details

Defined in Llama.Internal.Types

type Rep LlamaLogitBias = D1 ('MetaData "LlamaLogitBias" "Llama.Internal.Types" "llama-cpp-hs-0.1.0.0-inplace" 'False) (C1 ('MetaCons "LlamaLogitBias" 'PrefixI 'True) (S1 ('MetaSel ('Just "tokenLogitBias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LlamaToken) :*: S1 ('MetaSel ('Just "bias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float)))

Raw pointers

newtype CLlamaVocab Source #

Raw pointer to llama_vocab struct

Constructors

CLlamaVocab (Ptr CLlamaVocab) 

Instances

Instances details
Show CLlamaVocab Source # 
Instance details

Defined in Llama.Internal.Types

Eq CLlamaVocab Source # 
Instance details

Defined in Llama.Internal.Types

newtype CLlamaModel Source #

Raw pointer to llama_model struct

Constructors

CLlamaModel (Ptr CLlamaModel) 

Instances

Instances details
Show CLlamaModel Source # 
Instance details

Defined in Llama.Internal.Types

Eq CLlamaModel Source # 
Instance details

Defined in Llama.Internal.Types

newtype CLlamaContext Source #

Raw pointer to llama_context struct

Instances

Instances details
Show CLlamaContext Source # 
Instance details

Defined in Llama.Internal.Types

Eq CLlamaContext Source # 
Instance details

Defined in Llama.Internal.Types

newtype CLlamaKVCache Source #

Instances

Instances details
Show CLlamaKVCache Source # 
Instance details

Defined in Llama.Internal.Types

Eq CLlamaKVCache Source # 
Instance details

Defined in Llama.Internal.Types

Managed handles

newtype Vocab Source #

Managed vocabulary handle with automatic cleanup.

Constructors

Vocab (ForeignPtr CLlamaVocab) 

Instances

Instances details
Show Vocab Source # 
Instance details

Defined in Llama.Internal.Types

Methods

showsPrec :: Int -> Vocab -> ShowS #

show :: Vocab -> String #

showList :: [Vocab] -> ShowS #

Eq Vocab Source # 
Instance details

Defined in Llama.Internal.Types

Methods

(==) :: Vocab -> Vocab -> Bool #

(/=) :: Vocab -> Vocab -> Bool #

newtype Batch Source #

Managed batch pointer with automatic cleanup

Constructors

Batch (Ptr LlamaBatch) 

Instances

Instances details
Show Batch Source # 
Instance details

Defined in Llama.Internal.Types

Methods

showsPrec :: Int -> Batch -> ShowS #

show :: Batch -> String #

showList :: [Batch] -> ShowS #

Eq Batch Source # 
Instance details

Defined in Llama.Internal.Types

Methods

(==) :: Batch -> Batch -> Bool #

(/=) :: Batch -> Batch -> Bool #

newtype Model Source #

Managed model handle with automatic cleanup.

Constructors

Model (ForeignPtr CLlamaModel) 

Instances

Instances details
Show Model Source # 
Instance details

Defined in Llama.Internal.Types

Methods

showsPrec :: Int -> Model -> ShowS #

show :: Model -> String #

showList :: [Model] -> ShowS #

Eq Model Source # 
Instance details

Defined in Llama.Internal.Types

Methods

(==) :: Model -> Model -> Bool #

(/=) :: Model -> Model -> Bool #

newtype Context Source #

Managed context handle with automatic cleanup.

Instances

Instances details
Show Context Source # 
Instance details

Defined in Llama.Internal.Types

Eq Context Source # 
Instance details

Defined in Llama.Internal.Types

Methods

(==) :: Context -> Context -> Bool #

(/=) :: Context -> Context -> Bool #

newtype Sampler Source #

Managed sampler handle with automatic cleanup.

Instances

Instances details
Show Sampler Source # 
Instance details

Defined in Llama.Internal.Types

Eq Sampler Source # 
Instance details

Defined in Llama.Internal.Types

Methods

(==) :: Sampler -> Sampler -> Bool #

(/=) :: Sampler -> Sampler -> Bool #

newtype KVCache Source #

Instances

Instances details
Show KVCache Source # 
Instance details

Defined in Llama.Internal.Types

Eq KVCache Source # 
Instance details

Defined in Llama.Internal.Types

Methods

(==) :: KVCache -> KVCache -> Bool #

(/=) :: KVCache -> KVCache -> Bool #

newtype AdapterLora Source #

Instances

Instances details
Show AdapterLora Source # 
Instance details

Defined in Llama.Internal.Types

Eq AdapterLora Source # 
Instance details

Defined in Llama.Internal.Types