module Database.EJDB2.Query
( Query(..)
, BindM
, withQuery
, noBind
, setBool
, setBoolAtIndex
, setI64
, setI64AtIndex
, setF64
, setF64AtIndex
, setString
, setStringAtIndex
, setRegex
, setRegexAtIndex
, setNull
, setNullAtIndex
) where
import Control.Monad.IO.Class
import Control.Monad.State.Lazy
import qualified Data.Bool as Bool
import Data.IORef
import Data.Int
import Database.EJDB2.Bindings.JQL
import Database.EJDB2.Result
import Foreign
import Foreign.C.String
import Foreign.C.Types
import Foreign.Marshal.Alloc
data Query a = Query String
(BindM a)
data BindState = BindState JQL [CString]
type BindM a = StateT BindState IO a
bind :: BindM a -> BindState -> IO BindState
bind bindM state = execStateT bindM state
getJQL :: BindM JQL
getJQL = get >>= \(BindState jql _) -> return jql
noBind :: BindM ()
noBind = return ()
freeBindState :: BindState -> IO BindState
freeBindState (BindState jql cStrings) = mapM_ free cStrings
>> return (BindState jql [])
withQuery :: Query a -> (JQL -> IO b) -> IO b
withQuery (Query query bindM) f = do
(jqlPtr, jql) <- createQuery query
bindState <- bind bindM (BindState jql [])
result <- f jql
destroyQuery jqlPtr
freeBindState bindState
return result
createQuery :: String
-> IO (Ptr JQL, JQL)
createQuery string = do
jqlPtr <- malloc
withCString string $ \cString -> do
c_jql_create jqlPtr nullPtr cString >>= checkRC
jql <- peek jqlPtr
return (jqlPtr, jql)
destroyQuery :: Ptr JQL -> IO ()
destroyQuery jqlPtr = c_jql_destroy jqlPtr >> free jqlPtr
setBool :: Bool
-> String
-> BindM ()
setBool bool placeholder =
getJQL >>= \jql -> liftIO $ withCString placeholder $ \cPlaceholder ->
c_jql_set_bool jql cPlaceholder 0 (CBool (Bool.bool 0 1 bool)) >>= checkRC
setBoolAtIndex :: Bool
-> Int
-> BindM ()
setBoolAtIndex bool index = getJQL >>= \jql -> liftIO $
c_jql_set_bool jql
nullPtr
(CInt $ fromIntegral index)
(CBool (Bool.bool 0 1 bool)) >>= checkRC
setI64 :: Int64
-> String
-> BindM ()
setI64 number placeholder =
getJQL >>= \jql -> liftIO $ withCString placeholder $ \cPlaceholder ->
c_jql_set_i64 jql cPlaceholder 0 (CIntMax number) >>= checkRC
setI64AtIndex :: Int64
-> Int
-> BindM ()
setI64AtIndex number index = getJQL >>= \jql -> liftIO $
c_jql_set_i64 jql nullPtr (CInt $ fromIntegral index) (CIntMax number)
>>= checkRC
setF64 :: Double
-> String
-> BindM ()
setF64 number placeholder =
getJQL >>= \jql -> liftIO $ withCString placeholder $ \cPlaceholder ->
c_jql_set_f64 jql cPlaceholder 0 (CDouble number) >>= checkRC
setF64AtIndex :: Double
-> Int
-> BindM ()
setF64AtIndex number index = getJQL >>= \jql -> liftIO $
c_jql_set_f64 jql nullPtr (CInt $ fromIntegral index) (CDouble number)
>>= checkRC
newCStringInBindState :: String -> BindM CString
newCStringInBindState string = get >>= \(BindState jql strings) ->
liftIO (newCString string) >>= \cString ->
put (BindState jql (cString : strings)) >> return cString
setString :: String
-> String
-> BindM ()
setString string placeholder = newCStringInBindState string
>>= \cString -> getJQL >>= \jql -> liftIO $ withCString placeholder $
\cPlaceholder -> c_jql_set_str jql cPlaceholder 0 cString >>= checkRC
setStringAtIndex :: String
-> Int
-> BindM ()
setStringAtIndex string index =
newCStringInBindState string >>= \cString -> getJQL >>= \jql -> liftIO $
c_jql_set_str jql nullPtr (CInt $ fromIntegral index) cString >>= checkRC
setRegex :: String
-> String
-> BindM ()
setRegex string placeholder = newCStringInBindState string
>>= \cString -> getJQL >>= \jql -> liftIO $ withCString placeholder $
\cPlaceholder -> c_jql_set_regexp jql cPlaceholder 0 cString >>= checkRC
setRegexAtIndex :: String
-> Int
-> BindM ()
setRegexAtIndex string index =
newCStringInBindState string >>= \cString -> getJQL >>= \jql -> liftIO $
c_jql_set_regexp jql nullPtr (CInt $ fromIntegral index) cString >>= checkRC
setNull :: String
-> BindM ()
setNull placeholder = getJQL >>= \jql -> liftIO $ withCString placeholder $
\cPlaceholder -> c_jql_set_null jql cPlaceholder 0 >>= checkRC
setNullAtIndex :: Int
-> BindM ()
setNullAtIndex index = getJQL >>= \jql -> liftIO $
c_jql_set_null jql nullPtr (CInt $ fromIntegral index) >>= checkRC