{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
module Llama.Internal.Types
(
LlamaTokenData (..)
, LlamaTokenDataArray (..)
, LlamaBatch (..)
, AddBos (..)
, LlamaToken
, LlamaKvCacheView (..)
, LlamaSeqId
, LlamaPos
, LlamaChatMessage (..)
, LlamaSamplerI (..)
, LlamaSampler (..)
, LlamaSamplerContext
, LlamaPerfContextData (..)
, LlamaPerfSamplerData (..)
, LlamaLogitBias (..)
, CLlamaVocab (..)
, CLlamaModel (..)
, CLlamaContext (..)
, CLlamaKVCache (..)
, CLlamaAdapterLora (..)
, Vocab (..)
, Batch (..)
, Model (..)
, Context (..)
, Sampler (..)
, KVCache (..)
, AdapterLora (..)
) where
import Foreign
import Foreign.C.String
import Foreign.C.Types
import Foreign.Storable.Generic
import GHC.Generics
data AddBos = Always | Never
data LlamaLogitBias = LlamaLogitBias
{ LlamaLogitBias -> LlamaToken
tokenLogitBias :: LlamaToken
, LlamaLogitBias -> Float
bias :: Float
}
deriving (Int -> LlamaLogitBias -> ShowS
[LlamaLogitBias] -> ShowS
LlamaLogitBias -> String
(Int -> LlamaLogitBias -> ShowS)
-> (LlamaLogitBias -> String)
-> ([LlamaLogitBias] -> ShowS)
-> Show LlamaLogitBias
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LlamaLogitBias -> ShowS
showsPrec :: Int -> LlamaLogitBias -> ShowS
$cshow :: LlamaLogitBias -> String
show :: LlamaLogitBias -> String
$cshowList :: [LlamaLogitBias] -> ShowS
showList :: [LlamaLogitBias] -> ShowS
Show, LlamaLogitBias -> LlamaLogitBias -> Bool
(LlamaLogitBias -> LlamaLogitBias -> Bool)
-> (LlamaLogitBias -> LlamaLogitBias -> Bool) -> Eq LlamaLogitBias
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LlamaLogitBias -> LlamaLogitBias -> Bool
== :: LlamaLogitBias -> LlamaLogitBias -> Bool
$c/= :: LlamaLogitBias -> LlamaLogitBias -> Bool
/= :: LlamaLogitBias -> LlamaLogitBias -> Bool
Eq, (forall x. LlamaLogitBias -> Rep LlamaLogitBias x)
-> (forall x. Rep LlamaLogitBias x -> LlamaLogitBias)
-> Generic LlamaLogitBias
forall x. Rep LlamaLogitBias x -> LlamaLogitBias
forall x. LlamaLogitBias -> Rep LlamaLogitBias x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LlamaLogitBias -> Rep LlamaLogitBias x
from :: forall x. LlamaLogitBias -> Rep LlamaLogitBias x
$cto :: forall x. Rep LlamaLogitBias x -> LlamaLogitBias
to :: forall x. Rep LlamaLogitBias x -> LlamaLogitBias
Generic, LlamaLogitBias -> Int
(LlamaLogitBias -> Int)
-> (LlamaLogitBias -> Int)
-> (forall b. Ptr b -> Int -> IO LlamaLogitBias)
-> (forall b. Ptr b -> Int -> LlamaLogitBias -> IO ())
-> GStorable LlamaLogitBias
forall b. Ptr b -> Int -> IO LlamaLogitBias
forall b. Ptr b -> Int -> LlamaLogitBias -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> GStorable a
$cgsizeOf :: LlamaLogitBias -> Int
gsizeOf :: LlamaLogitBias -> Int
$cgalignment :: LlamaLogitBias -> Int
galignment :: LlamaLogitBias -> Int
$cgpeekByteOff :: forall b. Ptr b -> Int -> IO LlamaLogitBias
gpeekByteOff :: forall b. Ptr b -> Int -> IO LlamaLogitBias
$cgpokeByteOff :: forall b. Ptr b -> Int -> LlamaLogitBias -> IO ()
gpokeByteOff :: forall b. Ptr b -> Int -> LlamaLogitBias -> IO ()
GStorable)
newtype CLlamaAdapterLora = CLlamaAdapterLora (Ptr CLlamaAdapterLora)
deriving (Int -> CLlamaAdapterLora -> ShowS
[CLlamaAdapterLora] -> ShowS
CLlamaAdapterLora -> String
(Int -> CLlamaAdapterLora -> ShowS)
-> (CLlamaAdapterLora -> String)
-> ([CLlamaAdapterLora] -> ShowS)
-> Show CLlamaAdapterLora
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CLlamaAdapterLora -> ShowS
showsPrec :: Int -> CLlamaAdapterLora -> ShowS
$cshow :: CLlamaAdapterLora -> String
show :: CLlamaAdapterLora -> String
$cshowList :: [CLlamaAdapterLora] -> ShowS
showList :: [CLlamaAdapterLora] -> ShowS
Show, CLlamaAdapterLora -> CLlamaAdapterLora -> Bool
(CLlamaAdapterLora -> CLlamaAdapterLora -> Bool)
-> (CLlamaAdapterLora -> CLlamaAdapterLora -> Bool)
-> Eq CLlamaAdapterLora
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CLlamaAdapterLora -> CLlamaAdapterLora -> Bool
== :: CLlamaAdapterLora -> CLlamaAdapterLora -> Bool
$c/= :: CLlamaAdapterLora -> CLlamaAdapterLora -> Bool
/= :: CLlamaAdapterLora -> CLlamaAdapterLora -> Bool
Eq)
newtype CLlamaVocab = CLlamaVocab (Ptr CLlamaVocab)
deriving (Int -> CLlamaVocab -> ShowS
[CLlamaVocab] -> ShowS
CLlamaVocab -> String
(Int -> CLlamaVocab -> ShowS)
-> (CLlamaVocab -> String)
-> ([CLlamaVocab] -> ShowS)
-> Show CLlamaVocab
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CLlamaVocab -> ShowS
showsPrec :: Int -> CLlamaVocab -> ShowS
$cshow :: CLlamaVocab -> String
show :: CLlamaVocab -> String
$cshowList :: [CLlamaVocab] -> ShowS
showList :: [CLlamaVocab] -> ShowS
Show, CLlamaVocab -> CLlamaVocab -> Bool
(CLlamaVocab -> CLlamaVocab -> Bool)
-> (CLlamaVocab -> CLlamaVocab -> Bool) -> Eq CLlamaVocab
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CLlamaVocab -> CLlamaVocab -> Bool
== :: CLlamaVocab -> CLlamaVocab -> Bool
$c/= :: CLlamaVocab -> CLlamaVocab -> Bool
/= :: CLlamaVocab -> CLlamaVocab -> Bool
Eq)
newtype CLlamaModel = CLlamaModel (Ptr CLlamaModel)
deriving (Int -> CLlamaModel -> ShowS
[CLlamaModel] -> ShowS
CLlamaModel -> String
(Int -> CLlamaModel -> ShowS)
-> (CLlamaModel -> String)
-> ([CLlamaModel] -> ShowS)
-> Show CLlamaModel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CLlamaModel -> ShowS
showsPrec :: Int -> CLlamaModel -> ShowS
$cshow :: CLlamaModel -> String
show :: CLlamaModel -> String
$cshowList :: [CLlamaModel] -> ShowS
showList :: [CLlamaModel] -> ShowS
Show, CLlamaModel -> CLlamaModel -> Bool
(CLlamaModel -> CLlamaModel -> Bool)
-> (CLlamaModel -> CLlamaModel -> Bool) -> Eq CLlamaModel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CLlamaModel -> CLlamaModel -> Bool
== :: CLlamaModel -> CLlamaModel -> Bool
$c/= :: CLlamaModel -> CLlamaModel -> Bool
/= :: CLlamaModel -> CLlamaModel -> Bool
Eq)
newtype CLlamaContext = CLlamaContext (Ptr CLlamaContext)
deriving (Int -> CLlamaContext -> ShowS
[CLlamaContext] -> ShowS
CLlamaContext -> String
(Int -> CLlamaContext -> ShowS)
-> (CLlamaContext -> String)
-> ([CLlamaContext] -> ShowS)
-> Show CLlamaContext
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CLlamaContext -> ShowS
showsPrec :: Int -> CLlamaContext -> ShowS
$cshow :: CLlamaContext -> String
show :: CLlamaContext -> String
$cshowList :: [CLlamaContext] -> ShowS
showList :: [CLlamaContext] -> ShowS
Show, CLlamaContext -> CLlamaContext -> Bool
(CLlamaContext -> CLlamaContext -> Bool)
-> (CLlamaContext -> CLlamaContext -> Bool) -> Eq CLlamaContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CLlamaContext -> CLlamaContext -> Bool
== :: CLlamaContext -> CLlamaContext -> Bool
$c/= :: CLlamaContext -> CLlamaContext -> Bool
/= :: CLlamaContext -> CLlamaContext -> Bool
Eq)
newtype CLlamaKVCache = CLlamaKVCache (Ptr CLlamaKVCache)
deriving (Int -> CLlamaKVCache -> ShowS
[CLlamaKVCache] -> ShowS
CLlamaKVCache -> String
(Int -> CLlamaKVCache -> ShowS)
-> (CLlamaKVCache -> String)
-> ([CLlamaKVCache] -> ShowS)
-> Show CLlamaKVCache
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CLlamaKVCache -> ShowS
showsPrec :: Int -> CLlamaKVCache -> ShowS
$cshow :: CLlamaKVCache -> String
show :: CLlamaKVCache -> String
$cshowList :: [CLlamaKVCache] -> ShowS
showList :: [CLlamaKVCache] -> ShowS
Show, CLlamaKVCache -> CLlamaKVCache -> Bool
(CLlamaKVCache -> CLlamaKVCache -> Bool)
-> (CLlamaKVCache -> CLlamaKVCache -> Bool) -> Eq CLlamaKVCache
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CLlamaKVCache -> CLlamaKVCache -> Bool
== :: CLlamaKVCache -> CLlamaKVCache -> Bool
$c/= :: CLlamaKVCache -> CLlamaKVCache -> Bool
/= :: CLlamaKVCache -> CLlamaKVCache -> Bool
Eq)
newtype Batch = Batch (Ptr LlamaBatch)
deriving (Int -> Batch -> ShowS
[Batch] -> ShowS
Batch -> String
(Int -> Batch -> ShowS)
-> (Batch -> String) -> ([Batch] -> ShowS) -> Show Batch
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Batch -> ShowS
showsPrec :: Int -> Batch -> ShowS
$cshow :: Batch -> String
show :: Batch -> String
$cshowList :: [Batch] -> ShowS
showList :: [Batch] -> ShowS
Show, Batch -> Batch -> Bool
(Batch -> Batch -> Bool) -> (Batch -> Batch -> Bool) -> Eq Batch
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Batch -> Batch -> Bool
== :: Batch -> Batch -> Bool
$c/= :: Batch -> Batch -> Bool
/= :: Batch -> Batch -> Bool
Eq)
newtype Vocab = Vocab (ForeignPtr CLlamaVocab)
deriving (Int -> Vocab -> ShowS
[Vocab] -> ShowS
Vocab -> String
(Int -> Vocab -> ShowS)
-> (Vocab -> String) -> ([Vocab] -> ShowS) -> Show Vocab
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Vocab -> ShowS
showsPrec :: Int -> Vocab -> ShowS
$cshow :: Vocab -> String
show :: Vocab -> String
$cshowList :: [Vocab] -> ShowS
showList :: [Vocab] -> ShowS
Show, Vocab -> Vocab -> Bool
(Vocab -> Vocab -> Bool) -> (Vocab -> Vocab -> Bool) -> Eq Vocab
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Vocab -> Vocab -> Bool
== :: Vocab -> Vocab -> Bool
$c/= :: Vocab -> Vocab -> Bool
/= :: Vocab -> Vocab -> Bool
Eq)
newtype Model = Model (ForeignPtr CLlamaModel)
deriving (Int -> Model -> ShowS
[Model] -> ShowS
Model -> String
(Int -> Model -> ShowS)
-> (Model -> String) -> ([Model] -> ShowS) -> Show Model
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Model -> ShowS
showsPrec :: Int -> Model -> ShowS
$cshow :: Model -> String
show :: Model -> String
$cshowList :: [Model] -> ShowS
showList :: [Model] -> ShowS
Show, Model -> Model -> Bool
(Model -> Model -> Bool) -> (Model -> Model -> Bool) -> Eq Model
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Model -> Model -> Bool
== :: Model -> Model -> Bool
$c/= :: Model -> Model -> Bool
/= :: Model -> Model -> Bool
Eq)
newtype Context = Context (ForeignPtr CLlamaContext)
deriving (Int -> Context -> ShowS
[Context] -> ShowS
Context -> String
(Int -> Context -> ShowS)
-> (Context -> String) -> ([Context] -> ShowS) -> Show Context
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Context -> ShowS
showsPrec :: Int -> Context -> ShowS
$cshow :: Context -> String
show :: Context -> String
$cshowList :: [Context] -> ShowS
showList :: [Context] -> ShowS
Show, Context -> Context -> Bool
(Context -> Context -> Bool)
-> (Context -> Context -> Bool) -> Eq Context
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Context -> Context -> Bool
== :: Context -> Context -> Bool
$c/= :: Context -> Context -> Bool
/= :: Context -> Context -> Bool
Eq)
newtype Sampler = Sampler (ForeignPtr LlamaSampler)
deriving (Int -> Sampler -> ShowS
[Sampler] -> ShowS
Sampler -> String
(Int -> Sampler -> ShowS)
-> (Sampler -> String) -> ([Sampler] -> ShowS) -> Show Sampler
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Sampler -> ShowS
showsPrec :: Int -> Sampler -> ShowS
$cshow :: Sampler -> String
show :: Sampler -> String
$cshowList :: [Sampler] -> ShowS
showList :: [Sampler] -> ShowS
Show, Sampler -> Sampler -> Bool
(Sampler -> Sampler -> Bool)
-> (Sampler -> Sampler -> Bool) -> Eq Sampler
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Sampler -> Sampler -> Bool
== :: Sampler -> Sampler -> Bool
$c/= :: Sampler -> Sampler -> Bool
/= :: Sampler -> Sampler -> Bool
Eq)
newtype KVCache = KVCache (ForeignPtr CLlamaKVCache)
deriving (Int -> KVCache -> ShowS
[KVCache] -> ShowS
KVCache -> String
(Int -> KVCache -> ShowS)
-> (KVCache -> String) -> ([KVCache] -> ShowS) -> Show KVCache
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> KVCache -> ShowS
showsPrec :: Int -> KVCache -> ShowS
$cshow :: KVCache -> String
show :: KVCache -> String
$cshowList :: [KVCache] -> ShowS
showList :: [KVCache] -> ShowS
Show, KVCache -> KVCache -> Bool
(KVCache -> KVCache -> Bool)
-> (KVCache -> KVCache -> Bool) -> Eq KVCache
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: KVCache -> KVCache -> Bool
== :: KVCache -> KVCache -> Bool
$c/= :: KVCache -> KVCache -> Bool
/= :: KVCache -> KVCache -> Bool
Eq)
newtype AdapterLora = AdapterLora (ForeignPtr CLlamaAdapterLora)
deriving (Int -> AdapterLora -> ShowS
[AdapterLora] -> ShowS
AdapterLora -> String
(Int -> AdapterLora -> ShowS)
-> (AdapterLora -> String)
-> ([AdapterLora] -> ShowS)
-> Show AdapterLora
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AdapterLora -> ShowS
showsPrec :: Int -> AdapterLora -> ShowS
$cshow :: AdapterLora -> String
show :: AdapterLora -> String
$cshowList :: [AdapterLora] -> ShowS
showList :: [AdapterLora] -> ShowS
Show, AdapterLora -> AdapterLora -> Bool
(AdapterLora -> AdapterLora -> Bool)
-> (AdapterLora -> AdapterLora -> Bool) -> Eq AdapterLora
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AdapterLora -> AdapterLora -> Bool
== :: AdapterLora -> AdapterLora -> Bool
$c/= :: AdapterLora -> AdapterLora -> Bool
/= :: AdapterLora -> AdapterLora -> Bool
Eq)
type LlamaToken = CInt
type LlamaPos = CInt
type LlamaSeqId = CInt
data LlamaChatMessage = LlamaChatMessage
{ LlamaChatMessage -> CString
role :: CString
, LlamaChatMessage -> CString
content :: CString
}
deriving (Int -> LlamaChatMessage -> ShowS
[LlamaChatMessage] -> ShowS
LlamaChatMessage -> String
(Int -> LlamaChatMessage -> ShowS)
-> (LlamaChatMessage -> String)
-> ([LlamaChatMessage] -> ShowS)
-> Show LlamaChatMessage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LlamaChatMessage -> ShowS
showsPrec :: Int -> LlamaChatMessage -> ShowS
$cshow :: LlamaChatMessage -> String
show :: LlamaChatMessage -> String
$cshowList :: [LlamaChatMessage] -> ShowS
showList :: [LlamaChatMessage] -> ShowS
Show, LlamaChatMessage -> LlamaChatMessage -> Bool
(LlamaChatMessage -> LlamaChatMessage -> Bool)
-> (LlamaChatMessage -> LlamaChatMessage -> Bool)
-> Eq LlamaChatMessage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LlamaChatMessage -> LlamaChatMessage -> Bool
== :: LlamaChatMessage -> LlamaChatMessage -> Bool
$c/= :: LlamaChatMessage -> LlamaChatMessage -> Bool
/= :: LlamaChatMessage -> LlamaChatMessage -> Bool
Eq, (forall x. LlamaChatMessage -> Rep LlamaChatMessage x)
-> (forall x. Rep LlamaChatMessage x -> LlamaChatMessage)
-> Generic LlamaChatMessage
forall x. Rep LlamaChatMessage x -> LlamaChatMessage
forall x. LlamaChatMessage -> Rep LlamaChatMessage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LlamaChatMessage -> Rep LlamaChatMessage x
from :: forall x. LlamaChatMessage -> Rep LlamaChatMessage x
$cto :: forall x. Rep LlamaChatMessage x -> LlamaChatMessage
to :: forall x. Rep LlamaChatMessage x -> LlamaChatMessage
Generic, LlamaChatMessage -> Int
(LlamaChatMessage -> Int)
-> (LlamaChatMessage -> Int)
-> (forall b. Ptr b -> Int -> IO LlamaChatMessage)
-> (forall b. Ptr b -> Int -> LlamaChatMessage -> IO ())
-> GStorable LlamaChatMessage
forall b. Ptr b -> Int -> IO LlamaChatMessage
forall b. Ptr b -> Int -> LlamaChatMessage -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> GStorable a
$cgsizeOf :: LlamaChatMessage -> Int
gsizeOf :: LlamaChatMessage -> Int
$cgalignment :: LlamaChatMessage -> Int
galignment :: LlamaChatMessage -> Int
$cgpeekByteOff :: forall b. Ptr b -> Int -> IO LlamaChatMessage
gpeekByteOff :: forall b. Ptr b -> Int -> IO LlamaChatMessage
$cgpokeByteOff :: forall b. Ptr b -> Int -> LlamaChatMessage -> IO ()
gpokeByteOff :: forall b. Ptr b -> Int -> LlamaChatMessage -> IO ()
GStorable)
data LlamaTokenData = LlamaTokenData
{ LlamaTokenData -> LlamaToken
id :: LlamaToken
, LlamaTokenData -> CFloat
logit :: CFloat
, LlamaTokenData -> CFloat
p :: CFloat
}
deriving (Int -> LlamaTokenData -> ShowS
[LlamaTokenData] -> ShowS
LlamaTokenData -> String
(Int -> LlamaTokenData -> ShowS)
-> (LlamaTokenData -> String)
-> ([LlamaTokenData] -> ShowS)
-> Show LlamaTokenData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LlamaTokenData -> ShowS
showsPrec :: Int -> LlamaTokenData -> ShowS
$cshow :: LlamaTokenData -> String
show :: LlamaTokenData -> String
$cshowList :: [LlamaTokenData] -> ShowS
showList :: [LlamaTokenData] -> ShowS
Show, LlamaTokenData -> LlamaTokenData -> Bool
(LlamaTokenData -> LlamaTokenData -> Bool)
-> (LlamaTokenData -> LlamaTokenData -> Bool) -> Eq LlamaTokenData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LlamaTokenData -> LlamaTokenData -> Bool
== :: LlamaTokenData -> LlamaTokenData -> Bool
$c/= :: LlamaTokenData -> LlamaTokenData -> Bool
/= :: LlamaTokenData -> LlamaTokenData -> Bool
Eq, (forall x. LlamaTokenData -> Rep LlamaTokenData x)
-> (forall x. Rep LlamaTokenData x -> LlamaTokenData)
-> Generic LlamaTokenData
forall x. Rep LlamaTokenData x -> LlamaTokenData
forall x. LlamaTokenData -> Rep LlamaTokenData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LlamaTokenData -> Rep LlamaTokenData x
from :: forall x. LlamaTokenData -> Rep LlamaTokenData x
$cto :: forall x. Rep LlamaTokenData x -> LlamaTokenData
to :: forall x. Rep LlamaTokenData x -> LlamaTokenData
Generic, LlamaTokenData -> Int
(LlamaTokenData -> Int)
-> (LlamaTokenData -> Int)
-> (forall b. Ptr b -> Int -> IO LlamaTokenData)
-> (forall b. Ptr b -> Int -> LlamaTokenData -> IO ())
-> GStorable LlamaTokenData
forall b. Ptr b -> Int -> IO LlamaTokenData
forall b. Ptr b -> Int -> LlamaTokenData -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> GStorable a
$cgsizeOf :: LlamaTokenData -> Int
gsizeOf :: LlamaTokenData -> Int
$cgalignment :: LlamaTokenData -> Int
galignment :: LlamaTokenData -> Int
$cgpeekByteOff :: forall b. Ptr b -> Int -> IO LlamaTokenData
gpeekByteOff :: forall b. Ptr b -> Int -> IO LlamaTokenData
$cgpokeByteOff :: forall b. Ptr b -> Int -> LlamaTokenData -> IO ()
gpokeByteOff :: forall b. Ptr b -> Int -> LlamaTokenData -> IO ()
GStorable)
data LlamaTokenDataArray = LlamaTokenDataArray
{ LlamaTokenDataArray -> Ptr LlamaTokenData
data_ :: Ptr LlamaTokenData
, LlamaTokenDataArray -> CSize
size_ :: CSize
, LlamaTokenDataArray -> CLong
selected :: CLong
, LlamaTokenDataArray -> CBool
sorted :: CBool
}
deriving (LlamaTokenDataArray -> LlamaTokenDataArray -> Bool
(LlamaTokenDataArray -> LlamaTokenDataArray -> Bool)
-> (LlamaTokenDataArray -> LlamaTokenDataArray -> Bool)
-> Eq LlamaTokenDataArray
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LlamaTokenDataArray -> LlamaTokenDataArray -> Bool
== :: LlamaTokenDataArray -> LlamaTokenDataArray -> Bool
$c/= :: LlamaTokenDataArray -> LlamaTokenDataArray -> Bool
/= :: LlamaTokenDataArray -> LlamaTokenDataArray -> Bool
Eq, Int -> LlamaTokenDataArray -> ShowS
[LlamaTokenDataArray] -> ShowS
LlamaTokenDataArray -> String
(Int -> LlamaTokenDataArray -> ShowS)
-> (LlamaTokenDataArray -> String)
-> ([LlamaTokenDataArray] -> ShowS)
-> Show LlamaTokenDataArray
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LlamaTokenDataArray -> ShowS
showsPrec :: Int -> LlamaTokenDataArray -> ShowS
$cshow :: LlamaTokenDataArray -> String
show :: LlamaTokenDataArray -> String
$cshowList :: [LlamaTokenDataArray] -> ShowS
showList :: [LlamaTokenDataArray] -> ShowS
Show, (forall x. LlamaTokenDataArray -> Rep LlamaTokenDataArray x)
-> (forall x. Rep LlamaTokenDataArray x -> LlamaTokenDataArray)
-> Generic LlamaTokenDataArray
forall x. Rep LlamaTokenDataArray x -> LlamaTokenDataArray
forall x. LlamaTokenDataArray -> Rep LlamaTokenDataArray x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LlamaTokenDataArray -> Rep LlamaTokenDataArray x
from :: forall x. LlamaTokenDataArray -> Rep LlamaTokenDataArray x
$cto :: forall x. Rep LlamaTokenDataArray x -> LlamaTokenDataArray
to :: forall x. Rep LlamaTokenDataArray x -> LlamaTokenDataArray
Generic, LlamaTokenDataArray -> Int
(LlamaTokenDataArray -> Int)
-> (LlamaTokenDataArray -> Int)
-> (forall b. Ptr b -> Int -> IO LlamaTokenDataArray)
-> (forall b. Ptr b -> Int -> LlamaTokenDataArray -> IO ())
-> GStorable LlamaTokenDataArray
forall b. Ptr b -> Int -> IO LlamaTokenDataArray
forall b. Ptr b -> Int -> LlamaTokenDataArray -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> GStorable a
$cgsizeOf :: LlamaTokenDataArray -> Int
gsizeOf :: LlamaTokenDataArray -> Int
$cgalignment :: LlamaTokenDataArray -> Int
galignment :: LlamaTokenDataArray -> Int
$cgpeekByteOff :: forall b. Ptr b -> Int -> IO LlamaTokenDataArray
gpeekByteOff :: forall b. Ptr b -> Int -> IO LlamaTokenDataArray
$cgpokeByteOff :: forall b. Ptr b -> Int -> LlamaTokenDataArray -> IO ()
gpokeByteOff :: forall b. Ptr b -> Int -> LlamaTokenDataArray -> IO ()
GStorable)
data LlamaBatch = LlamaBatch
{ LlamaBatch -> LlamaToken
n_tokens :: CInt
, LlamaBatch -> Ptr LlamaToken
token :: Ptr CInt
, LlamaBatch -> Ptr CFloat
embd :: Ptr CFloat
, LlamaBatch -> Ptr LlamaToken
pos :: Ptr CInt
, LlamaBatch -> Ptr LlamaToken
n_seq_id :: Ptr CInt
, LlamaBatch -> Ptr (Ptr LlamaToken)
seq_id :: Ptr (Ptr CInt)
, LlamaBatch -> Ptr CSChar
logits :: Ptr CSChar
}
deriving ((forall x. LlamaBatch -> Rep LlamaBatch x)
-> (forall x. Rep LlamaBatch x -> LlamaBatch) -> Generic LlamaBatch
forall x. Rep LlamaBatch x -> LlamaBatch
forall x. LlamaBatch -> Rep LlamaBatch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LlamaBatch -> Rep LlamaBatch x
from :: forall x. LlamaBatch -> Rep LlamaBatch x
$cto :: forall x. Rep LlamaBatch x -> LlamaBatch
to :: forall x. Rep LlamaBatch x -> LlamaBatch
Generic, LlamaBatch -> Int
(LlamaBatch -> Int)
-> (LlamaBatch -> Int)
-> (forall b. Ptr b -> Int -> IO LlamaBatch)
-> (forall b. Ptr b -> Int -> LlamaBatch -> IO ())
-> GStorable LlamaBatch
forall b. Ptr b -> Int -> IO LlamaBatch
forall b. Ptr b -> Int -> LlamaBatch -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> GStorable a
$cgsizeOf :: LlamaBatch -> Int
gsizeOf :: LlamaBatch -> Int
$cgalignment :: LlamaBatch -> Int
galignment :: LlamaBatch -> Int
$cgpeekByteOff :: forall b. Ptr b -> Int -> IO LlamaBatch
gpeekByteOff :: forall b. Ptr b -> Int -> IO LlamaBatch
$cgpokeByteOff :: forall b. Ptr b -> Int -> LlamaBatch -> IO ()
gpokeByteOff :: forall b. Ptr b -> Int -> LlamaBatch -> IO ()
GStorable, LlamaBatch -> LlamaBatch -> Bool
(LlamaBatch -> LlamaBatch -> Bool)
-> (LlamaBatch -> LlamaBatch -> Bool) -> Eq LlamaBatch
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LlamaBatch -> LlamaBatch -> Bool
== :: LlamaBatch -> LlamaBatch -> Bool
$c/= :: LlamaBatch -> LlamaBatch -> Bool
/= :: LlamaBatch -> LlamaBatch -> Bool
Eq, Int -> LlamaBatch -> ShowS
[LlamaBatch] -> ShowS
LlamaBatch -> String
(Int -> LlamaBatch -> ShowS)
-> (LlamaBatch -> String)
-> ([LlamaBatch] -> ShowS)
-> Show LlamaBatch
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LlamaBatch -> ShowS
showsPrec :: Int -> LlamaBatch -> ShowS
$cshow :: LlamaBatch -> String
show :: LlamaBatch -> String
$cshowList :: [LlamaBatch] -> ShowS
showList :: [LlamaBatch] -> ShowS
Show)
newtype LlamaKvCacheViewCell = LlamaKvCacheViewCell
{ LlamaKvCacheViewCell -> LlamaToken
posKvCacheViewCell :: LlamaPos
}
deriving (Int -> LlamaKvCacheViewCell -> ShowS
[LlamaKvCacheViewCell] -> ShowS
LlamaKvCacheViewCell -> String
(Int -> LlamaKvCacheViewCell -> ShowS)
-> (LlamaKvCacheViewCell -> String)
-> ([LlamaKvCacheViewCell] -> ShowS)
-> Show LlamaKvCacheViewCell
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LlamaKvCacheViewCell -> ShowS
showsPrec :: Int -> LlamaKvCacheViewCell -> ShowS
$cshow :: LlamaKvCacheViewCell -> String
show :: LlamaKvCacheViewCell -> String
$cshowList :: [LlamaKvCacheViewCell] -> ShowS
showList :: [LlamaKvCacheViewCell] -> ShowS
Show, LlamaKvCacheViewCell -> LlamaKvCacheViewCell -> Bool
(LlamaKvCacheViewCell -> LlamaKvCacheViewCell -> Bool)
-> (LlamaKvCacheViewCell -> LlamaKvCacheViewCell -> Bool)
-> Eq LlamaKvCacheViewCell
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LlamaKvCacheViewCell -> LlamaKvCacheViewCell -> Bool
== :: LlamaKvCacheViewCell -> LlamaKvCacheViewCell -> Bool
$c/= :: LlamaKvCacheViewCell -> LlamaKvCacheViewCell -> Bool
/= :: LlamaKvCacheViewCell -> LlamaKvCacheViewCell -> Bool
Eq, (forall x. LlamaKvCacheViewCell -> Rep LlamaKvCacheViewCell x)
-> (forall x. Rep LlamaKvCacheViewCell x -> LlamaKvCacheViewCell)
-> Generic LlamaKvCacheViewCell
forall x. Rep LlamaKvCacheViewCell x -> LlamaKvCacheViewCell
forall x. LlamaKvCacheViewCell -> Rep LlamaKvCacheViewCell x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LlamaKvCacheViewCell -> Rep LlamaKvCacheViewCell x
from :: forall x. LlamaKvCacheViewCell -> Rep LlamaKvCacheViewCell x
$cto :: forall x. Rep LlamaKvCacheViewCell x -> LlamaKvCacheViewCell
to :: forall x. Rep LlamaKvCacheViewCell x -> LlamaKvCacheViewCell
Generic, LlamaKvCacheViewCell -> Int
(LlamaKvCacheViewCell -> Int)
-> (LlamaKvCacheViewCell -> Int)
-> (forall b. Ptr b -> Int -> IO LlamaKvCacheViewCell)
-> (forall b. Ptr b -> Int -> LlamaKvCacheViewCell -> IO ())
-> GStorable LlamaKvCacheViewCell
forall b. Ptr b -> Int -> IO LlamaKvCacheViewCell
forall b. Ptr b -> Int -> LlamaKvCacheViewCell -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> GStorable a
$cgsizeOf :: LlamaKvCacheViewCell -> Int
gsizeOf :: LlamaKvCacheViewCell -> Int
$cgalignment :: LlamaKvCacheViewCell -> Int
galignment :: LlamaKvCacheViewCell -> Int
$cgpeekByteOff :: forall b. Ptr b -> Int -> IO LlamaKvCacheViewCell
gpeekByteOff :: forall b. Ptr b -> Int -> IO LlamaKvCacheViewCell
$cgpokeByteOff :: forall b. Ptr b -> Int -> LlamaKvCacheViewCell -> IO ()
gpokeByteOff :: forall b. Ptr b -> Int -> LlamaKvCacheViewCell -> IO ()
GStorable)
data LlamaKvCacheView = LlamaKvCacheView
{ LlamaKvCacheView -> LlamaToken
n_cells :: CInt
, LlamaKvCacheView -> LlamaToken
n_seq_max :: CInt
, LlamaKvCacheView -> LlamaToken
token_count :: CInt
, LlamaKvCacheView -> LlamaToken
used_cells :: CInt
, LlamaKvCacheView -> LlamaToken
max_contiguous :: CInt
, LlamaKvCacheView -> LlamaToken
max_contiguous_idx :: CInt
, LlamaKvCacheView -> Ptr LlamaKvCacheViewCell
cells :: Ptr LlamaKvCacheViewCell
, LlamaKvCacheView -> Ptr LlamaToken
cells_sequences :: Ptr LlamaSeqId
}
deriving (Int -> LlamaKvCacheView -> ShowS
[LlamaKvCacheView] -> ShowS
LlamaKvCacheView -> String
(Int -> LlamaKvCacheView -> ShowS)
-> (LlamaKvCacheView -> String)
-> ([LlamaKvCacheView] -> ShowS)
-> Show LlamaKvCacheView
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LlamaKvCacheView -> ShowS
showsPrec :: Int -> LlamaKvCacheView -> ShowS
$cshow :: LlamaKvCacheView -> String
show :: LlamaKvCacheView -> String
$cshowList :: [LlamaKvCacheView] -> ShowS
showList :: [LlamaKvCacheView] -> ShowS
Show, LlamaKvCacheView -> LlamaKvCacheView -> Bool
(LlamaKvCacheView -> LlamaKvCacheView -> Bool)
-> (LlamaKvCacheView -> LlamaKvCacheView -> Bool)
-> Eq LlamaKvCacheView
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LlamaKvCacheView -> LlamaKvCacheView -> Bool
== :: LlamaKvCacheView -> LlamaKvCacheView -> Bool
$c/= :: LlamaKvCacheView -> LlamaKvCacheView -> Bool
/= :: LlamaKvCacheView -> LlamaKvCacheView -> Bool
Eq, (forall x. LlamaKvCacheView -> Rep LlamaKvCacheView x)
-> (forall x. Rep LlamaKvCacheView x -> LlamaKvCacheView)
-> Generic LlamaKvCacheView
forall x. Rep LlamaKvCacheView x -> LlamaKvCacheView
forall x. LlamaKvCacheView -> Rep LlamaKvCacheView x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LlamaKvCacheView -> Rep LlamaKvCacheView x
from :: forall x. LlamaKvCacheView -> Rep LlamaKvCacheView x
$cto :: forall x. Rep LlamaKvCacheView x -> LlamaKvCacheView
to :: forall x. Rep LlamaKvCacheView x -> LlamaKvCacheView
Generic, LlamaKvCacheView -> Int
(LlamaKvCacheView -> Int)
-> (LlamaKvCacheView -> Int)
-> (forall b. Ptr b -> Int -> IO LlamaKvCacheView)
-> (forall b. Ptr b -> Int -> LlamaKvCacheView -> IO ())
-> GStorable LlamaKvCacheView
forall b. Ptr b -> Int -> IO LlamaKvCacheView
forall b. Ptr b -> Int -> LlamaKvCacheView -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> GStorable a
$cgsizeOf :: LlamaKvCacheView -> Int
gsizeOf :: LlamaKvCacheView -> Int
$cgalignment :: LlamaKvCacheView -> Int
galignment :: LlamaKvCacheView -> Int
$cgpeekByteOff :: forall b. Ptr b -> Int -> IO LlamaKvCacheView
gpeekByteOff :: forall b. Ptr b -> Int -> IO LlamaKvCacheView
$cgpokeByteOff :: forall b. Ptr b -> Int -> LlamaKvCacheView -> IO ()
gpokeByteOff :: forall b. Ptr b -> Int -> LlamaKvCacheView -> IO ()
GStorable)
type LlamaSamplerContext = Ptr ()
data LlamaSamplerI = LlamaSamplerI
{ LlamaSamplerI -> FunPtr (Ptr LlamaSampler -> IO CString)
name :: FunPtr (Ptr LlamaSampler -> IO CString)
, LlamaSamplerI -> FunPtr (Ptr LlamaSampler -> LlamaToken -> IO ())
accept :: FunPtr (Ptr LlamaSampler -> LlamaToken -> IO ())
, LlamaSamplerI
-> FunPtr (Ptr LlamaSampler -> Ptr LlamaTokenDataArray -> IO ())
apply :: FunPtr (Ptr LlamaSampler -> Ptr LlamaTokenDataArray -> IO ())
, LlamaSamplerI -> FunPtr (Ptr LlamaSampler -> IO ())
reset :: FunPtr (Ptr LlamaSampler -> IO ())
, LlamaSamplerI -> FunPtr (Ptr LlamaSampler -> IO (Ptr LlamaSampler))
clone :: FunPtr (Ptr LlamaSampler -> IO (Ptr LlamaSampler))
, LlamaSamplerI -> FunPtr (Ptr LlamaSampler -> IO ())
free_ :: FunPtr (Ptr LlamaSampler -> IO ())
}
deriving (Int -> LlamaSamplerI -> ShowS
[LlamaSamplerI] -> ShowS
LlamaSamplerI -> String
(Int -> LlamaSamplerI -> ShowS)
-> (LlamaSamplerI -> String)
-> ([LlamaSamplerI] -> ShowS)
-> Show LlamaSamplerI
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LlamaSamplerI -> ShowS
showsPrec :: Int -> LlamaSamplerI -> ShowS
$cshow :: LlamaSamplerI -> String
show :: LlamaSamplerI -> String
$cshowList :: [LlamaSamplerI] -> ShowS
showList :: [LlamaSamplerI] -> ShowS
Show, LlamaSamplerI -> LlamaSamplerI -> Bool
(LlamaSamplerI -> LlamaSamplerI -> Bool)
-> (LlamaSamplerI -> LlamaSamplerI -> Bool) -> Eq LlamaSamplerI
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LlamaSamplerI -> LlamaSamplerI -> Bool
== :: LlamaSamplerI -> LlamaSamplerI -> Bool
$c/= :: LlamaSamplerI -> LlamaSamplerI -> Bool
/= :: LlamaSamplerI -> LlamaSamplerI -> Bool
Eq, (forall x. LlamaSamplerI -> Rep LlamaSamplerI x)
-> (forall x. Rep LlamaSamplerI x -> LlamaSamplerI)
-> Generic LlamaSamplerI
forall x. Rep LlamaSamplerI x -> LlamaSamplerI
forall x. LlamaSamplerI -> Rep LlamaSamplerI x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LlamaSamplerI -> Rep LlamaSamplerI x
from :: forall x. LlamaSamplerI -> Rep LlamaSamplerI x
$cto :: forall x. Rep LlamaSamplerI x -> LlamaSamplerI
to :: forall x. Rep LlamaSamplerI x -> LlamaSamplerI
Generic, LlamaSamplerI -> Int
(LlamaSamplerI -> Int)
-> (LlamaSamplerI -> Int)
-> (forall b. Ptr b -> Int -> IO LlamaSamplerI)
-> (forall b. Ptr b -> Int -> LlamaSamplerI -> IO ())
-> GStorable LlamaSamplerI
forall b. Ptr b -> Int -> IO LlamaSamplerI
forall b. Ptr b -> Int -> LlamaSamplerI -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> GStorable a
$cgsizeOf :: LlamaSamplerI -> Int
gsizeOf :: LlamaSamplerI -> Int
$cgalignment :: LlamaSamplerI -> Int
galignment :: LlamaSamplerI -> Int
$cgpeekByteOff :: forall b. Ptr b -> Int -> IO LlamaSamplerI
gpeekByteOff :: forall b. Ptr b -> Int -> IO LlamaSamplerI
$cgpokeByteOff :: forall b. Ptr b -> Int -> LlamaSamplerI -> IO ()
gpokeByteOff :: forall b. Ptr b -> Int -> LlamaSamplerI -> IO ()
GStorable)
data LlamaSampler = LlamaSampler
{ LlamaSampler -> Ptr LlamaSamplerI
iface :: Ptr LlamaSamplerI
, LlamaSampler -> LlamaSamplerContext
ctx :: LlamaSamplerContext
}
deriving ((forall x. LlamaSampler -> Rep LlamaSampler x)
-> (forall x. Rep LlamaSampler x -> LlamaSampler)
-> Generic LlamaSampler
forall x. Rep LlamaSampler x -> LlamaSampler
forall x. LlamaSampler -> Rep LlamaSampler x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LlamaSampler -> Rep LlamaSampler x
from :: forall x. LlamaSampler -> Rep LlamaSampler x
$cto :: forall x. Rep LlamaSampler x -> LlamaSampler
to :: forall x. Rep LlamaSampler x -> LlamaSampler
Generic, Int -> LlamaSampler -> ShowS
[LlamaSampler] -> ShowS
LlamaSampler -> String
(Int -> LlamaSampler -> ShowS)
-> (LlamaSampler -> String)
-> ([LlamaSampler] -> ShowS)
-> Show LlamaSampler
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LlamaSampler -> ShowS
showsPrec :: Int -> LlamaSampler -> ShowS
$cshow :: LlamaSampler -> String
show :: LlamaSampler -> String
$cshowList :: [LlamaSampler] -> ShowS
showList :: [LlamaSampler] -> ShowS
Show, LlamaSampler -> LlamaSampler -> Bool
(LlamaSampler -> LlamaSampler -> Bool)
-> (LlamaSampler -> LlamaSampler -> Bool) -> Eq LlamaSampler
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LlamaSampler -> LlamaSampler -> Bool
== :: LlamaSampler -> LlamaSampler -> Bool
$c/= :: LlamaSampler -> LlamaSampler -> Bool
/= :: LlamaSampler -> LlamaSampler -> Bool
Eq, LlamaSampler -> Int
(LlamaSampler -> Int)
-> (LlamaSampler -> Int)
-> (forall b. Ptr b -> Int -> IO LlamaSampler)
-> (forall b. Ptr b -> Int -> LlamaSampler -> IO ())
-> GStorable LlamaSampler
forall b. Ptr b -> Int -> IO LlamaSampler
forall b. Ptr b -> Int -> LlamaSampler -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> GStorable a
$cgsizeOf :: LlamaSampler -> Int
gsizeOf :: LlamaSampler -> Int
$cgalignment :: LlamaSampler -> Int
galignment :: LlamaSampler -> Int
$cgpeekByteOff :: forall b. Ptr b -> Int -> IO LlamaSampler
gpeekByteOff :: forall b. Ptr b -> Int -> IO LlamaSampler
$cgpokeByteOff :: forall b. Ptr b -> Int -> LlamaSampler -> IO ()
gpokeByteOff :: forall b. Ptr b -> Int -> LlamaSampler -> IO ()
GStorable)
data LlamaPerfContextData = LlamaPerfContextData
{ LlamaPerfContextData -> CDouble
t_start_ms :: CDouble
, LlamaPerfContextData -> CDouble
t_load_ms :: CDouble
, LlamaPerfContextData -> CDouble
t_p_eval_ms :: CDouble
, LlamaPerfContextData -> CDouble
t_eval_ms :: CDouble
, LlamaPerfContextData -> LlamaToken
n_p_eval :: CInt
, LlamaPerfContextData -> LlamaToken
n_eval :: CInt
}
deriving (Int -> LlamaPerfContextData -> ShowS
[LlamaPerfContextData] -> ShowS
LlamaPerfContextData -> String
(Int -> LlamaPerfContextData -> ShowS)
-> (LlamaPerfContextData -> String)
-> ([LlamaPerfContextData] -> ShowS)
-> Show LlamaPerfContextData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LlamaPerfContextData -> ShowS
showsPrec :: Int -> LlamaPerfContextData -> ShowS
$cshow :: LlamaPerfContextData -> String
show :: LlamaPerfContextData -> String
$cshowList :: [LlamaPerfContextData] -> ShowS
showList :: [LlamaPerfContextData] -> ShowS
Show, LlamaPerfContextData -> LlamaPerfContextData -> Bool
(LlamaPerfContextData -> LlamaPerfContextData -> Bool)
-> (LlamaPerfContextData -> LlamaPerfContextData -> Bool)
-> Eq LlamaPerfContextData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LlamaPerfContextData -> LlamaPerfContextData -> Bool
== :: LlamaPerfContextData -> LlamaPerfContextData -> Bool
$c/= :: LlamaPerfContextData -> LlamaPerfContextData -> Bool
/= :: LlamaPerfContextData -> LlamaPerfContextData -> Bool
Eq, (forall x. LlamaPerfContextData -> Rep LlamaPerfContextData x)
-> (forall x. Rep LlamaPerfContextData x -> LlamaPerfContextData)
-> Generic LlamaPerfContextData
forall x. Rep LlamaPerfContextData x -> LlamaPerfContextData
forall x. LlamaPerfContextData -> Rep LlamaPerfContextData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LlamaPerfContextData -> Rep LlamaPerfContextData x
from :: forall x. LlamaPerfContextData -> Rep LlamaPerfContextData x
$cto :: forall x. Rep LlamaPerfContextData x -> LlamaPerfContextData
to :: forall x. Rep LlamaPerfContextData x -> LlamaPerfContextData
Generic, LlamaPerfContextData -> Int
(LlamaPerfContextData -> Int)
-> (LlamaPerfContextData -> Int)
-> (forall b. Ptr b -> Int -> IO LlamaPerfContextData)
-> (forall b. Ptr b -> Int -> LlamaPerfContextData -> IO ())
-> GStorable LlamaPerfContextData
forall b. Ptr b -> Int -> IO LlamaPerfContextData
forall b. Ptr b -> Int -> LlamaPerfContextData -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> GStorable a
$cgsizeOf :: LlamaPerfContextData -> Int
gsizeOf :: LlamaPerfContextData -> Int
$cgalignment :: LlamaPerfContextData -> Int
galignment :: LlamaPerfContextData -> Int
$cgpeekByteOff :: forall b. Ptr b -> Int -> IO LlamaPerfContextData
gpeekByteOff :: forall b. Ptr b -> Int -> IO LlamaPerfContextData
$cgpokeByteOff :: forall b. Ptr b -> Int -> LlamaPerfContextData -> IO ()
gpokeByteOff :: forall b. Ptr b -> Int -> LlamaPerfContextData -> IO ()
GStorable)
data LlamaPerfSamplerData = LlamaPerfSamplerData
{ LlamaPerfSamplerData -> CDouble
t_sample_ms :: CDouble
, LlamaPerfSamplerData -> LlamaToken
n_sample :: CInt
}
deriving (Int -> LlamaPerfSamplerData -> ShowS
[LlamaPerfSamplerData] -> ShowS
LlamaPerfSamplerData -> String
(Int -> LlamaPerfSamplerData -> ShowS)
-> (LlamaPerfSamplerData -> String)
-> ([LlamaPerfSamplerData] -> ShowS)
-> Show LlamaPerfSamplerData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LlamaPerfSamplerData -> ShowS
showsPrec :: Int -> LlamaPerfSamplerData -> ShowS
$cshow :: LlamaPerfSamplerData -> String
show :: LlamaPerfSamplerData -> String
$cshowList :: [LlamaPerfSamplerData] -> ShowS
showList :: [LlamaPerfSamplerData] -> ShowS
Show, LlamaPerfSamplerData -> LlamaPerfSamplerData -> Bool
(LlamaPerfSamplerData -> LlamaPerfSamplerData -> Bool)
-> (LlamaPerfSamplerData -> LlamaPerfSamplerData -> Bool)
-> Eq LlamaPerfSamplerData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LlamaPerfSamplerData -> LlamaPerfSamplerData -> Bool
== :: LlamaPerfSamplerData -> LlamaPerfSamplerData -> Bool
$c/= :: LlamaPerfSamplerData -> LlamaPerfSamplerData -> Bool
/= :: LlamaPerfSamplerData -> LlamaPerfSamplerData -> Bool
Eq, (forall x. LlamaPerfSamplerData -> Rep LlamaPerfSamplerData x)
-> (forall x. Rep LlamaPerfSamplerData x -> LlamaPerfSamplerData)
-> Generic LlamaPerfSamplerData
forall x. Rep LlamaPerfSamplerData x -> LlamaPerfSamplerData
forall x. LlamaPerfSamplerData -> Rep LlamaPerfSamplerData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LlamaPerfSamplerData -> Rep LlamaPerfSamplerData x
from :: forall x. LlamaPerfSamplerData -> Rep LlamaPerfSamplerData x
$cto :: forall x. Rep LlamaPerfSamplerData x -> LlamaPerfSamplerData
to :: forall x. Rep LlamaPerfSamplerData x -> LlamaPerfSamplerData
Generic, LlamaPerfSamplerData -> Int
(LlamaPerfSamplerData -> Int)
-> (LlamaPerfSamplerData -> Int)
-> (forall b. Ptr b -> Int -> IO LlamaPerfSamplerData)
-> (forall b. Ptr b -> Int -> LlamaPerfSamplerData -> IO ())
-> GStorable LlamaPerfSamplerData
forall b. Ptr b -> Int -> IO LlamaPerfSamplerData
forall b. Ptr b -> Int -> LlamaPerfSamplerData -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> GStorable a
$cgsizeOf :: LlamaPerfSamplerData -> Int
gsizeOf :: LlamaPerfSamplerData -> Int
$cgalignment :: LlamaPerfSamplerData -> Int
galignment :: LlamaPerfSamplerData -> Int
$cgpeekByteOff :: forall b. Ptr b -> Int -> IO LlamaPerfSamplerData
gpeekByteOff :: forall b. Ptr b -> Int -> IO LlamaPerfSamplerData
$cgpokeByteOff :: forall b. Ptr b -> Int -> LlamaPerfSamplerData -> IO ()
gpokeByteOff :: forall b. Ptr b -> Int -> LlamaPerfSamplerData -> IO ()
GStorable)