module Bindings.Sophia where
import Foreign.Ptr (FunPtr, Ptr)
import Foreign.C.Types (CInt(..), CUInt(..), CSize(..), CDouble(..))
import Foreign.C.String (CString)
import Data.Word (Word32)
type C'sporder = CUInt
c'SPGT = 0
c'SPGT :: (Num a) => a
c'SPGTE = 1
c'SPGTE :: (Num a) => a
c'SPLT = 2
c'SPLT :: (Num a) => a
c'SPLTE = 3
c'SPLTE :: (Num a) => a
c'SPO_RDWR = 2
c'SPO_RDWR :: (Num a) => a
c'SPO_RDONLY = 1
c'SPO_RDONLY :: (Num a) => a
c'SPO_CREAT = 4
c'SPO_CREAT :: (Num a) => a
c'SPO_SYNC = 8
c'SPO_SYNC :: (Num a) => a
type Handle = Ptr ()
type Env = Handle
type Db = Handle
type Cursor = Handle
type Flags = Word32
type ErrorCode = CInt
type Key = Ptr ()
type Val = Ptr ()
foreign import ccall unsafe "sp_env" unsafe'c'sp_env
:: IO Env
foreign import ccall unsafe "&sp_env" unsafe'p'sp_env
:: FunPtr (IO Env)
foreign import ccall unsafe "sp_destroy" unsafe'c'sp_destroy
:: Handle -> IO ErrorCode
foreign import ccall unsafe "&sp_destroy" unsafe'p'sp_destroy
:: FunPtr (Handle -> IO ErrorCode)
foreign import ccall unsafe "sp_open" unsafe'c'sp_open
:: Env -> IO Db
foreign import ccall unsafe "&sp_open" unsafe'p'sp_open
:: FunPtr (Env -> IO Db)
foreign import ccall unsafe "sp_error" unsafe'c'sp_error
:: Handle -> IO CString
foreign import ccall unsafe "&sp_error" unsafe'p'sp_error
:: FunPtr (Handle -> IO CString)
foreign import ccall unsafe "sp_set" unsafe'c'sp_set
:: Db -> Key -> CSize -> Val -> CSize -> IO ErrorCode
foreign import ccall unsafe "&sp_set" unsafe'p'sp_set
:: FunPtr (Db -> Key -> CSize -> Val -> CSize -> IO ErrorCode)
foreign import ccall unsafe "sp_get" unsafe'c'sp_get
:: Db -> Key -> CSize -> Ptr Val -> Ptr CSize -> IO ErrorCode
foreign import ccall unsafe "&sp_get" unsafe'p'sp_get
:: FunPtr (Db -> Key -> CSize -> Ptr Val -> Ptr CSize -> IO ErrorCode)
foreign import ccall unsafe "sp_delete" unsafe'c'sp_delete
:: Db -> Key -> CSize -> IO ErrorCode
foreign import ccall unsafe "&sp_delete" unsafe'p'sp_delete
:: FunPtr (Db -> Key -> CSize -> IO ErrorCode)
foreign import ccall unsafe "sp_cursor" unsafe'c'sp_cursor
:: Db -> C'sporder -> Key -> CSize -> IO Cursor
foreign import ccall unsafe "&sp_cursor" unsafe'p'sp_cursor
:: FunPtr (Db -> C'sporder -> Key -> CSize -> IO Cursor)
foreign import ccall unsafe "sp_fetch" unsafe'c'sp_fetch
:: Cursor -> IO CInt
foreign import ccall unsafe "&sp_fetch" unsafe'p'sp_fetch
:: FunPtr (Cursor -> IO CInt)
foreign import ccall unsafe "sp_key" unsafe'c'sp_key
:: Cursor -> IO Key
foreign import ccall unsafe "&sp_key" unsafe'p'sp_key
:: FunPtr (Cursor -> IO Key)
foreign import ccall unsafe "sp_keysize" unsafe'c'sp_keysize
:: Cursor -> IO CSize
foreign import ccall unsafe "&sp_keysize" unsafe'p'sp_keysize
:: FunPtr (Cursor -> IO CSize)
foreign import ccall unsafe "sp_value" unsafe'c'sp_value
:: Cursor -> IO Val
foreign import ccall unsafe "&sp_value" unsafe'p'sp_value
:: FunPtr (Cursor -> IO Val)
foreign import ccall unsafe "sp_valuesize" unsafe'c'sp_valuesize
:: Cursor -> IO CSize
foreign import ccall unsafe "&sp_valuesize" unsafe'p'sp_valuesize
:: FunPtr (Cursor -> IO CSize)
foreign import ccall unsafe "sp_dir" unsafe'c'sp_dir
:: Env -> Flags -> CString -> IO ErrorCode
foreign import ccall unsafe "&sp_dir" unsafe'p'sp_dir
:: FunPtr (Env -> Flags -> CString -> IO ErrorCode)
type SpCmpF = FunPtr (CString -> CSize -> CString -> CSize -> Ptr () -> IO CInt)
foreign import ccall unsafe "sp_set_key_comparison" unsafe'c'sp_set_key_comparison
:: Env -> SpCmpF -> Ptr () -> IO ErrorCode
foreign import ccall unsafe "&sp_set_key_comparison" unsafe'p'sp_set_key_comparison
:: FunPtr (Env -> SpCmpF -> Ptr () -> IO ErrorCode)
foreign import ccall unsafe "sp_set_keys_per_page" unsafe'c'sp_set_keys_per_page
:: Env -> Word32 -> IO ErrorCode
foreign import ccall unsafe "&sp_set_keys_per_page" unsafe'p'sp_set_keys_per_page
:: FunPtr (Env -> Word32 -> IO ErrorCode)
foreign import ccall unsafe "sp_set_gc_enabled" unsafe'c'sp_set_gc_enabled
:: Env -> CInt -> IO ErrorCode
foreign import ccall unsafe "&sp_set_gc_enabled" unsafe'p'sp_set_gc_enabled
:: FunPtr (Env -> CInt -> IO ErrorCode)
foreign import ccall unsafe "sp_set_gcf" unsafe'c'sp_set_gcf
:: Env -> CDouble -> IO ErrorCode
foreign import ccall unsafe "&sp_set_gcf" unsafe'p'sp_set_gcf
:: FunPtr (Env -> CDouble -> IO ErrorCode)
foreign import ccall unsafe "sp_grow" unsafe'c'sp_grow
:: Env -> Word32 -> CDouble -> IO ErrorCode
foreign import ccall unsafe "&sp_grow" unsafe'p'sp_grow
:: FunPtr (Env -> Word32 -> CDouble -> IO ErrorCode)
foreign import ccall unsafe "sp_set_merge_enabled" unsafe'c'sp_set_merge_enabled
:: Env -> CInt -> IO ErrorCode
foreign import ccall unsafe "&sp_set_merge_enabled" unsafe'p'sp_set_merge_enabled
:: FunPtr (Env -> CInt -> IO ErrorCode)
foreign import ccall unsafe "sp_set_merge_watermark" unsafe'c'sp_set_merge_watermark
:: Env -> Word32 -> IO ErrorCode
foreign import ccall unsafe "&sp_set_merge_watermark" unsafe'p'sp_set_merge_watermark
:: FunPtr (Env -> Word32 -> IO ErrorCode)
foreign import ccall unsafe "sp_get_version" unsafe'c'sp_get_version
:: Env -> Ptr Word32 -> Ptr Word32 -> IO ErrorCode
foreign import ccall unsafe "&sp_get_version" unsafe'p'sp_get_version
:: FunPtr (Env -> Ptr Word32 -> Ptr Word32 -> IO ErrorCode)