{-# LINE 1 "src/Database/EJDB2/HTTP.hsc" #-}
{-# LANGUAGE CPP #-}
module Database.EJDB2.HTTP
( Options(..)
, zero
, OptionsB
, options
, build
) where
import Foreign
import Foreign.C.String
import Foreign.C.Types
import Foreign.Marshal.Utils
import Data.Int
data Options = Options { Options -> Bool
enabled :: !Bool
, Options -> Int32
port :: !Int32
, Options -> Maybe String
bind :: Maybe String
, Options -> Maybe String
accessToken :: Maybe String
, Options -> Bool
blocking :: !Bool
, Options -> Bool
readAnon :: !Bool
, Options -> Word64
maxBodySize :: !Word64
}
zero :: Options
zero :: Options
zero = Options :: Bool
-> Int32
-> Maybe String
-> Maybe String
-> Bool
-> Bool
-> Word64
-> Options
Options { enabled :: Bool
enabled = Bool
False
, port :: Int32
port = Int32
0
, bind :: Maybe String
bind = Maybe String
forall a. Maybe a
Nothing
, accessToken :: Maybe String
accessToken = Maybe String
forall a. Maybe a
Nothing
, blocking :: Bool
blocking = Bool
False
, readAnon :: Bool
readAnon = Bool
False
, maxBodySize :: Word64
maxBodySize = Word64
0
}
data OptionsB = OptionsB { OptionsB -> Options
options :: Options
, OptionsB -> ForeignPtr CChar
bindPtr :: ForeignPtr CChar
, OptionsB -> ForeignPtr CChar
accessTokenPtr :: ForeignPtr CChar
, OptionsB -> CSize
accessTokenLen :: CSize
}
build :: Options -> IO OptionsB
build :: Options -> IO OptionsB
build Options
options = do
ForeignPtr CChar
bindPtr <- (String -> IO (Ptr CChar)) -> Maybe String -> IO (Ptr CChar)
forall a b. (a -> IO (Ptr b)) -> Maybe a -> IO (Ptr b)
maybeNew String -> IO (Ptr CChar)
newCString (Options -> Maybe String
bind Options
options)
IO (Ptr CChar)
-> (Ptr CChar -> IO (ForeignPtr CChar)) -> IO (ForeignPtr CChar)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FinalizerPtr CChar -> Ptr CChar -> IO (ForeignPtr CChar)
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FinalizerPtr CChar
forall a. FinalizerPtr a
finalizerFree
(Ptr CChar
accessTokenPtr, Int
accessTokenLen) <- case (Options -> Maybe String
accessToken Options
options) of
Maybe String
Nothing -> (Ptr CChar, Int) -> IO (Ptr CChar, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr CChar
forall a. Ptr a
nullPtr, Int
0)
Just String
value -> String -> IO (Ptr CChar, Int)
newCStringLen String
value
ForeignPtr CChar
accessTokenFPtr <- FinalizerPtr CChar -> Ptr CChar -> IO (ForeignPtr CChar)
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FinalizerPtr CChar
forall a. FinalizerPtr a
finalizerFree Ptr CChar
accessTokenPtr
OptionsB -> IO OptionsB
forall (m :: * -> *) a. Monad m => a -> m a
return OptionsB :: Options
-> ForeignPtr CChar -> ForeignPtr CChar -> CSize -> OptionsB
OptionsB { options :: Options
options = Options
options
, bindPtr :: ForeignPtr CChar
bindPtr = ForeignPtr CChar
bindPtr
, accessTokenPtr :: ForeignPtr CChar
accessTokenPtr = ForeignPtr CChar
accessTokenFPtr
, accessTokenLen :: CSize
accessTokenLen = Word64 -> CSize
CSize (Word64 -> CSize) -> Word64 -> CSize
forall a b. (a -> b) -> a -> b
$ Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
accessTokenLen
}
instance Storable OptionsB where
sizeOf :: OptionsB -> Int
sizeOf OptionsB
_ = (Int
48)
{-# LINE 67 "src/Database/EJDB2/HTTP.hsc" #-}
alignment :: OptionsB -> Int
alignment OptionsB
_ = Int
8
{-# LINE 68 "src/Database/EJDB2/HTTP.hsc" #-}
peek :: Ptr OptionsB -> IO OptionsB
peek Ptr OptionsB
ptr = do
CInt
enabled <- (\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr OptionsB
hsc_ptr Int
0) Ptr OptionsB
ptr :: IO CInt
{-# LINE 70 "src/Database/EJDB2/HTTP.hsc" #-}
Int32
port <- (\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> IO Int32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr OptionsB
hsc_ptr Int
4) Ptr OptionsB
ptr
{-# LINE 71 "src/Database/EJDB2/HTTP.hsc" #-}
Ptr CChar
bindPtr <- (\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> IO (Ptr CChar)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr OptionsB
hsc_ptr Int
8) Ptr OptionsB
ptr
{-# LINE 72 "src/Database/EJDB2/HTTP.hsc" #-}
ForeignPtr CChar
bindFPtr <- FinalizerPtr CChar -> Ptr CChar -> IO (ForeignPtr CChar)
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FinalizerPtr CChar
forall a. FinalizerPtr a
finalizerFree Ptr CChar
forall a. Ptr a
nullPtr
Maybe String
bind <- (Ptr CChar -> IO String) -> Ptr CChar -> IO (Maybe String)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek Ptr CChar -> IO String
peekCString Ptr CChar
bindPtr
Ptr CChar
access_token <- (\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> IO (Ptr CChar)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr OptionsB
hsc_ptr Int
16) Ptr OptionsB
ptr
{-# LINE 75 "src/Database/EJDB2/HTTP.hsc" #-}
Int
access_token_len <- (\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> IO Int
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr OptionsB
hsc_ptr Int
24) Ptr OptionsB
ptr
{-# LINE 76 "src/Database/EJDB2/HTTP.hsc" #-}
ForeignPtr CChar
accessTokenFPtr <- FinalizerPtr CChar -> Ptr CChar -> IO (ForeignPtr CChar)
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FinalizerPtr CChar
forall a. FinalizerPtr a
finalizerFree Ptr CChar
forall a. Ptr a
nullPtr
Maybe String
accessToken <- (Ptr CChar -> IO String) -> Ptr CChar -> IO (Maybe String)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\Ptr CChar
ptr -> (Ptr CChar, Int) -> IO String
peekCStringLen (Ptr CChar
ptr, Int
access_token_len)) Ptr CChar
access_token
CInt
blocking <- (\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr OptionsB
hsc_ptr Int
32) Ptr OptionsB
ptr :: IO CInt
{-# LINE 79 "src/Database/EJDB2/HTTP.hsc" #-}
CInt
read_anon <- (\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr OptionsB
hsc_ptr Int
33) Ptr OptionsB
ptr :: IO CInt
{-# LINE 80 "src/Database/EJDB2/HTTP.hsc" #-}
Word64
max_body_size <- (\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> IO Word64
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr OptionsB
hsc_ptr Int
40) Ptr OptionsB
ptr
{-# LINE 81 "src/Database/EJDB2/HTTP.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
-> ForeignPtr CChar -> ForeignPtr CChar -> CSize -> OptionsB
OptionsB
(Bool
-> Int32
-> Maybe String
-> Maybe String
-> Bool
-> Bool
-> Word64
-> Options
Options
(CInt -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool CInt
enabled)
Int32
port
Maybe String
bind
Maybe String
accessToken
(CInt -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool CInt
blocking)
(CInt -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool CInt
read_anon)
Word64
max_body_size)
ForeignPtr CChar
bindFPtr ForeignPtr CChar
accessTokenFPtr (Word64 -> CSize
CSize (Word64 -> CSize) -> Word64 -> CSize
forall a b. (a -> b) -> a -> b
$ Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
access_token_len)
poke :: Ptr OptionsB -> OptionsB -> IO ()
poke Ptr OptionsB
ptr (OptionsB
(Options Bool
enabled Int32
port Maybe String
_ Maybe String
_ Bool
blocking Bool
read_anon Word64
max_body_size)
ForeignPtr CChar
bindPtr ForeignPtr CChar
accessTokenPtr CSize
accessTokenLen) = do
(\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr OptionsB
hsc_ptr Int
0) Ptr OptionsB
ptr (Bool -> CInt
forall a. Num a => Bool -> a
fromBool Bool
enabled :: CInt)
{-# LINE 95 "src/Database/EJDB2/HTTP.hsc" #-}
(\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> Int32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr OptionsB
hsc_ptr Int
4) Ptr OptionsB
ptr Int32
port
{-# LINE 96 "src/Database/EJDB2/HTTP.hsc" #-}
ForeignPtr CChar -> (Ptr CChar -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr CChar
bindPtr ((Ptr CChar -> IO ()) -> IO ()) -> (Ptr CChar -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
cBind ->
(\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> Ptr CChar -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr OptionsB
hsc_ptr Int
8) Ptr OptionsB
ptr Ptr CChar
cBind
{-# LINE 98 "src/Database/EJDB2/HTTP.hsc" #-}
ForeignPtr CChar -> (Ptr CChar -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr CChar
accessTokenPtr ((Ptr CChar -> IO ()) -> IO ()) -> (Ptr CChar -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
access_token ->
(\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> Ptr CChar -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr OptionsB
hsc_ptr Int
16) Ptr OptionsB
ptr Ptr CChar
access_token
{-# LINE 100 "src/Database/EJDB2/HTTP.hsc" #-}
(\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> CSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr OptionsB
hsc_ptr Int
24) Ptr OptionsB
ptr CSize
accessTokenLen
{-# LINE 101 "src/Database/EJDB2/HTTP.hsc" #-}
(\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr OptionsB
hsc_ptr Int
32) Ptr OptionsB
ptr (Bool -> CInt
forall a. Num a => Bool -> a
fromBool Bool
blocking :: CInt)
{-# LINE 102 "src/Database/EJDB2/HTTP.hsc" #-}
(\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr OptionsB
hsc_ptr Int
33) Ptr OptionsB
ptr (Bool -> CInt
forall a. Num a => Bool -> a
fromBool Bool
read_anon :: CInt)
{-# LINE 103 "src/Database/EJDB2/HTTP.hsc" #-}
(\Ptr OptionsB
hsc_ptr -> Ptr OptionsB -> Int -> Word64 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr OptionsB
hsc_ptr Int
40) Ptr OptionsB
ptr Word64
max_body_size
{-# LINE 104 "src/Database/EJDB2/HTTP.hsc" #-}