Skip to content

Commit 0c10951

Browse files
committed
add module
1 parent 89e09de commit 0c10951

File tree

1 file changed

+41
-0
lines changed
  • src/Simplex/Messaging/Agent/Store/SQLite

1 file changed

+41
-0
lines changed
Lines changed: 41 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,41 @@
1+
module Simplex.Messaging.Agent.Store.SQLite.Util where
2+
3+
import Control.Exception (SomeException, catch, mask_)
4+
import Data.ByteString (ByteString)
5+
import qualified Data.ByteString as B
6+
import Database.SQLite3.Direct (Database (..), FuncArgs (..), FuncContext (..))
7+
import Database.SQLite3.Bindings
8+
import Foreign.C.String
9+
import Foreign.Ptr
10+
import Foreign.StablePtr
11+
12+
data CFuncPtrs = CFuncPtrs (FunPtr CFunc) (FunPtr CFunc) (FunPtr CFuncFinal)
13+
14+
type SQLiteFunc = Ptr CContext -> CArgCount -> Ptr (Ptr CValue) -> IO ()
15+
16+
mkSQLiteFunc :: (FuncContext -> FuncArgs -> IO ()) -> SQLiteFunc
17+
mkSQLiteFunc f cxt nArgs cvals = catchAsResultError cxt $ f (FuncContext cxt) (FuncArgs nArgs cvals)
18+
{-# INLINE mkSQLiteFunc #-}
19+
20+
-- Based on createFunction from Database.SQLite3.Direct, but uses static function pointer to avoid dynamic wrapper that triggers DCL.
21+
createStaticFunction :: Database -> ByteString -> CArgCount -> Bool -> FunPtr SQLiteFunc -> IO (Either Error ())
22+
createStaticFunction (Database db) name nArgs isDet funPtr = mask_ $ do
23+
u <- newStablePtr $ CFuncPtrs funPtr nullFunPtr nullFunPtr
24+
let flags = if isDet then c_SQLITE_DETERMINISTIC else 0
25+
B.useAsCString name $ \namePtr ->
26+
toResult () <$> c_sqlite3_create_function_v2 db namePtr nArgs flags (castStablePtrToPtr u) funPtr nullFunPtr nullFunPtr nullFunPtr
27+
28+
-- Convert a 'CError' to a 'Either Error', in the common case where
29+
-- SQLITE_OK signals success and anything else signals an error.
30+
--
31+
-- Note that SQLITE_OK == 0.
32+
toResult :: a -> CError -> Either Error a
33+
toResult a (CError 0) = Right a
34+
toResult _ code = Left $ decodeError code
35+
36+
-- call c_sqlite3_result_error in the event of an error
37+
catchAsResultError :: Ptr CContext -> IO () -> IO ()
38+
catchAsResultError ctx action = catch action $ \exn -> do
39+
let msg = show (exn :: SomeException)
40+
withCAStringLen msg $ \(ptr, len) ->
41+
c_sqlite3_result_error ctx ptr (fromIntegral len)

0 commit comments

Comments
 (0)