{-# LINE 1 "src/Database/EJDB2/WAL.hsc" #-}
{-# LANGUAGE CPP #-}

module Database.EJDB2.WAL (Options(..), zero) where


import           Foreign
import           Foreign.C.String
import           Foreign.C.Types

import Database.EJDB2.Result



-- | Write ahead log (WAL) options.
data Options = Options { Options -> Bool
enabled :: !Bool -- ^ WAL enabled
                             , Options -> Bool
checkCRCOnCheckpoint :: !Bool -- ^ Check CRC32 sum of data blocks during checkpoint. Default: false
                             , Options -> Word32
savepointTimeoutSec :: !Word32 -- ^ Savepoint timeout seconds. Default: 10 sec
                             , Options -> Word32
checkpointTimeoutSec :: !Word32 -- ^ Checkpoint timeout seconds. Default: 300 sec (5 min);
                             , Options -> Word64
walBufferSz :: !Word64 -- ^ WAL file intermediate buffer size. Default: 8Mb
                             , Options -> Word8
checkpointBufferSz :: !Word8 -- ^ Checkpoint buffer size in bytes. Default: 1Gb
                             , Options -> FunPtr (CBool -> Ptr () -> IO RC)
walLockInterceptor :: !(FunPtr (CBool -> Ptr () -> IO RC)) -- ^ Optional function called before acquiring and after releasing.
-- exclusive database lock byAL checkpoint thread.
-- In the case of 'before loc first argument will be set to true
                             , Options -> Ptr ()
walLockInterceptorOpaque :: !(Ptr ()) -- ^ Opaque data for 'walLockInterceptor'
                             }

-- | Create default Options
zero :: Options
zero :: Options
zero = $WOptions :: Bool
-> Bool
-> Word32
-> Word32
-> Word64
-> Word8
-> FunPtr (CBool -> Ptr () -> IO RC)
-> Ptr ()
-> Options
Options { enabled :: Bool
enabled = Bool
False
                   , checkCRCOnCheckpoint :: Bool
checkCRCOnCheckpoint = Bool
False
                   , savepointTimeoutSec :: Word32
savepointTimeoutSec = 0
                   , checkpointTimeoutSec :: Word32
checkpointTimeoutSec = 0
                   , walBufferSz :: Word64
walBufferSz = 0
                   , checkpointBufferSz :: Word8
checkpointBufferSz = 0
                   , walLockInterceptor :: FunPtr (CBool -> Ptr () -> IO RC)
walLockInterceptor = FunPtr (CBool -> Ptr () -> IO RC)
forall a. FunPtr a
nullFunPtr
                   , walLockInterceptorOpaque :: Ptr ()
walLockInterceptorOpaque = Ptr ()
forall a. Ptr a
nullPtr
                   }

instance Storable Options where
        sizeOf :: Options -> Int
sizeOf _ = (48)
{-# LINE 41 "src/Database/EJDB2/WAL.hsc" #-}
        alignment :: Options -> Int
alignment _  = 8
{-# LINE 42 "src/Database/EJDB2/WAL.hsc" #-}
        peek :: Ptr Options -> IO Options
peek ptr :: Ptr Options
ptr = do
          Bool
enabled <- (\hsc_ptr :: Ptr Options
hsc_ptr -> Ptr Options -> Int -> IO Bool
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Options
hsc_ptr 0) Ptr Options
ptr
{-# LINE 44 "src/Database/EJDB2/WAL.hsc" #-}
          Bool
check_crc_on_checkpoint <- (\hsc_ptr :: Ptr Options
hsc_ptr -> Ptr Options -> Int -> IO Bool
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Options
hsc_ptr 1) Ptr Options
ptr
{-# LINE 45 "src/Database/EJDB2/WAL.hsc" #-}
          Word32
savepoint_timeout_sec <- (\hsc_ptr :: Ptr Options
hsc_ptr -> Ptr Options -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Options
hsc_ptr 4) Ptr Options
ptr
{-# LINE 46 "src/Database/EJDB2/WAL.hsc" #-}
          Word32
checkpoint_timeout_sec <- (\hsc_ptr :: Ptr Options
hsc_ptr -> Ptr Options -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Options
hsc_ptr 8) Ptr Options
ptr
{-# LINE 47 "src/Database/EJDB2/WAL.hsc" #-}
          Word64
wal_buffer_sz <- (\hsc_ptr :: Ptr Options
hsc_ptr -> Ptr Options -> Int -> IO Word64
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Options
hsc_ptr 16) Ptr Options
ptr
{-# LINE 48 "src/Database/EJDB2/WAL.hsc" #-}
          Word8
checkpoint_buffer_sz <- (\hsc_ptr :: Ptr Options
hsc_ptr -> Ptr Options -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Options
hsc_ptr 24) Ptr Options
ptr
{-# LINE 49 "src/Database/EJDB2/WAL.hsc" #-}
          FunPtr (CBool -> Ptr () -> IO RC)
wal_lock_interceptor <- (\hsc_ptr :: Ptr Options
hsc_ptr -> Ptr Options -> Int -> IO (FunPtr (CBool -> Ptr () -> IO RC))
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Options
hsc_ptr 32) Ptr Options
ptr
{-# LINE 50 "src/Database/EJDB2/WAL.hsc" #-}
          Ptr ()
wal_lock_interceptor_opaque <- (\hsc_ptr :: Ptr Options
hsc_ptr -> Ptr Options -> Int -> IO (Ptr ())
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Options
hsc_ptr 40) Ptr Options
ptr
{-# LINE 51 "src/Database/EJDB2/WAL.hsc" #-}
          Options -> IO Options
forall (m :: * -> *) a. Monad m => a -> m a
return (Options -> IO Options) -> Options -> IO Options
forall a b. (a -> b) -> a -> b
$ Bool
-> Bool
-> Word32
-> Word32
-> Word64
-> Word8
-> FunPtr (CBool -> Ptr () -> IO RC)
-> Ptr ()
-> Options
Options Bool
enabled Bool
check_crc_on_checkpoint Word32
savepoint_timeout_sec Word32
checkpoint_timeout_sec Word64
wal_buffer_sz Word8
checkpoint_buffer_sz FunPtr (CBool -> Ptr () -> IO RC)
wal_lock_interceptor Ptr ()
wal_lock_interceptor_opaque
        poke :: Ptr Options -> Options -> IO ()
poke ptr :: Ptr Options
ptr (Options enabled :: Bool
enabled check_crc_on_checkpoint :: Bool
check_crc_on_checkpoint savepoint_timeout_sec :: Word32
savepoint_timeout_sec checkpoint_timeout_sec :: Word32
checkpoint_timeout_sec wal_buffer_sz :: Word64
wal_buffer_sz checkpoint_buffer_sz :: Word8
checkpoint_buffer_sz wal_lock_interceptor :: FunPtr (CBool -> Ptr () -> IO RC)
wal_lock_interceptor wal_lock_interceptor_opaque :: Ptr ()
wal_lock_interceptor_opaque) = do
          (\hsc_ptr :: Ptr Options
hsc_ptr -> Ptr Options -> Int -> Bool -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Options
hsc_ptr 0) Ptr Options
ptr Bool
enabled
{-# LINE 54 "src/Database/EJDB2/WAL.hsc" #-}
          (\hsc_ptr :: Ptr Options
hsc_ptr -> Ptr Options -> Int -> Bool -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Options
hsc_ptr 1) Ptr Options
ptr Bool
check_crc_on_checkpoint
{-# LINE 55 "src/Database/EJDB2/WAL.hsc" #-}
          (\hsc_ptr :: Ptr Options
hsc_ptr -> Ptr Options -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Options
hsc_ptr 4) Ptr Options
ptr Word32
savepoint_timeout_sec
{-# LINE 56 "src/Database/EJDB2/WAL.hsc" #-}
          (\hsc_ptr :: Ptr Options
hsc_ptr -> Ptr Options -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Options
hsc_ptr 8) Ptr Options
ptr Word32
checkpoint_timeout_sec
{-# LINE 57 "src/Database/EJDB2/WAL.hsc" #-}
          (\hsc_ptr :: Ptr Options
hsc_ptr -> Ptr Options -> Int -> Word64 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Options
hsc_ptr 16) Ptr Options
ptr Word64
wal_buffer_sz
{-# LINE 58 "src/Database/EJDB2/WAL.hsc" #-}
          (\hsc_ptr :: Ptr Options
hsc_ptr -> Ptr Options -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Options
hsc_ptr 24) Ptr Options
ptr Word8
checkpoint_buffer_sz
{-# LINE 59 "src/Database/EJDB2/WAL.hsc" #-}
          (\hsc_ptr :: Ptr Options
hsc_ptr -> Ptr Options -> Int -> FunPtr (CBool -> Ptr () -> IO RC) -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Options
hsc_ptr 32) Ptr Options
ptr FunPtr (CBool -> Ptr () -> IO RC)
wal_lock_interceptor
{-# LINE 60 "src/Database/EJDB2/WAL.hsc" #-}
          (\hsc_ptr :: Ptr Options
hsc_ptr -> Ptr Options -> Int -> Ptr () -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Options
hsc_ptr 40) Ptr Options
ptr Ptr ()
wal_lock_interceptor_opaque
{-# LINE 61 "src/Database/EJDB2/WAL.hsc" #-}