{-# LINE 1 "src/Database/EJDB2/Options.hsc" #-}
{-# LANGUAGE CPP #-}
module Database.EJDB2.Options
( Options(..), zero, OptionsB, options, build ) where
import Data.ByteString.Char8
import Foreign
import Foreign.C.String
import Foreign.C.Types
import qualified Database.EJDB2.KV as KV
import qualified Database.EJDB2.HTTP as HTTP
data Options = Options { Options -> Options
kv :: !KV.Options
, Options -> Options
http :: !HTTP.Options
, Options -> Bool
noWal :: !Bool
, Options -> Word32
sortBufferSz :: !Word32
, Options -> Word32
documentBufferSz :: !Word32
}
zero :: Options
zero :: Options
zero = Options :: Options -> Options -> Bool -> Word32 -> Word32 -> Options
Options { kv :: Options
kv = Options
KV.zero
, http :: Options
http = Options
HTTP.zero
, noWal :: Bool
noWal = Bool
False
, sortBufferSz :: Word32
sortBufferSz = Word32
0
, documentBufferSz :: Word32
documentBufferSz = Word32
0
}
data OptionsB = OptionsB { OptionsB -> Options
options :: Options
, OptionsB -> OptionsB
kvB :: !KV.OptionsB
, OptionsB -> OptionsB
httpB :: !HTTP.OptionsB
}
build :: Options -> IO OptionsB
build :: Options -> IO OptionsB
build Options
options = do
OptionsB
kvB <- Options -> IO OptionsB
KV.build (Options -> Options
kv Options
options)
OptionsB
httpB <- Options -> IO OptionsB
HTTP.build (Options -> Options
http Options
options)
OptionsB -> IO OptionsB
forall (m :: * -> *) a. Monad m => a -> m a
return (OptionsB -> IO OptionsB) -> OptionsB -> IO OptionsB
forall a b. (a -> b) -> a -> b
$ Options -> OptionsB -> OptionsB -> OptionsB
OptionsB Options
options OptionsB
kvB OptionsB
httpB
instance Storable OptionsB where
sizeOf :: OptionsB -> Int
sizeOf OptionsB
_ = (Int
136)
{-# LINE 49 "src/Database/EJDB2/Options.hsc" #-}
alignment :: OptionsB -> Int
alignment OptionsB
_ = Int
8
{-# LINE 50 "src/Database/EJDB2/Options.hsc" #-}
peek :: Ptr OptionsB -> IO OptionsB
peek Ptr OptionsB
ptr = do
OptionsB
kvB <- (\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> IO OptionsB
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr OptionsB
hsc_ptr Int
0) Ptr OptionsB
ptr
{-# LINE 52 "src/Database/EJDB2/Options.hsc" #-}
let kv :: Options
kv = OptionsB -> Options
KV.options OptionsB
kvB
OptionsB
httpB <- (\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> IO OptionsB
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr OptionsB
hsc_ptr Int
72) Ptr OptionsB
ptr
{-# LINE 54 "src/Database/EJDB2/Options.hsc" #-}
let http :: Options
http = OptionsB -> Options
HTTP.options OptionsB
httpB
(CBool Word8
no_wal) <- (\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> IO CBool
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr OptionsB
hsc_ptr Int
120) Ptr OptionsB
ptr
{-# LINE 56 "src/Database/EJDB2/Options.hsc" #-}
(CUInt Word32
sort_buffer_sz) <- (\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr OptionsB
hsc_ptr Int
124) Ptr OptionsB
ptr
{-# LINE 57 "src/Database/EJDB2/Options.hsc" #-}
(CUInt Word32
document_buffer_sz) <- (\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> IO CUInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr OptionsB
hsc_ptr Int
128) Ptr OptionsB
ptr
{-# LINE 58 "src/Database/EJDB2/Options.hsc" #-}
OptionsB -> IO OptionsB
forall (m :: * -> *) a. Monad m => a -> m a
return (OptionsB -> IO OptionsB) -> OptionsB -> IO OptionsB
forall a b. (a -> b) -> a -> b
$ Options -> OptionsB -> OptionsB -> OptionsB
OptionsB (Options -> Options -> Bool -> Word32 -> Word32 -> Options
Options Options
kv Options
http (Word8 -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool Word8
no_wal) Word32
sort_buffer_sz Word32
document_buffer_sz) OptionsB
kvB OptionsB
httpB
poke :: Ptr OptionsB -> OptionsB -> IO ()
poke Ptr OptionsB
ptr (OptionsB (Options Options
_ Options
http Bool
noWal Word32
sort_buffer_sz Word32
document_buffer_sz) OptionsB
kvB OptionsB
httpB) = do
(\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> OptionsB -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr OptionsB
hsc_ptr Int
0) Ptr OptionsB
ptr OptionsB
kvB
{-# LINE 61 "src/Database/EJDB2/Options.hsc" #-}
(\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> OptionsB -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr OptionsB
hsc_ptr Int
72) Ptr OptionsB
ptr OptionsB
httpB
{-# LINE 62 "src/Database/EJDB2/Options.hsc" #-}
(\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> CBool -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr OptionsB
hsc_ptr Int
120) Ptr OptionsB
ptr (Word8 -> CBool
CBool (Word8 -> CBool) -> Word8 -> CBool
forall a b. (a -> b) -> a -> b
$ Bool -> Word8
forall a. Num a => Bool -> a
fromBool Bool
noWal)
{-# LINE 63 "src/Database/EJDB2/Options.hsc" #-}
(\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> CUInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr OptionsB
hsc_ptr Int
124) Ptr OptionsB
ptr (Word32 -> CUInt
CUInt Word32
sort_buffer_sz)
{-# LINE 64 "src/Database/EJDB2/Options.hsc" #-}
(\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> CUInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr OptionsB
hsc_ptr Int
128) Ptr OptionsB
ptr (Word32 -> CUInt
CUInt Word32
document_buffer_sz)
{-# LINE 65 "src/Database/EJDB2/Options.hsc" #-}