Sqlite.hs 28 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722
  1. {-# LANGUAGE DeriveDataTypeable #-}
  2. {-# LANGUAGE ForeignFunctionInterface #-}
  3. {-# LANGUAGE OverloadedStrings #-}
  4. -- | A port of the direct-sqlite package for dealing directly with
  5. -- 'PersistValue's.
  6. module Database.Sqlite (
  7. Connection,
  8. Statement,
  9. Error(..),
  10. SqliteException(..),
  11. StepResult(Row, Done),
  12. Config(ConfigLogFn),
  13. LogFunction,
  14. SqliteStatus (..),
  15. SqliteStatusVerb (..),
  16. -- * Basic usage guide
  17. -- |
  18. --
  19. -- Note that the example code shown here is a low level interface
  20. -- usage. Let's create a small demo sqlite3 database which we will
  21. -- use in our program:
  22. --
  23. -- > $ sqlite3 ~/test.db
  24. -- > sqlite> create table t1(a,b);
  25. -- > sqlite> insert into t1(a,b) values (1,1);
  26. -- > sqlite> insert into t1(a,b) values (2,2);
  27. -- > sqlite> select * from t1;
  28. -- > 1|1
  29. -- > 2|2
  30. --
  31. -- Now let's write code using the functions in this module to
  32. -- fetch the rows from the table:
  33. --
  34. -- > {-#LANGUAGE OverloadedStrings#-}
  35. -- >
  36. -- > import Database.Sqlite
  37. -- > import Data.Text
  38. -- >
  39. -- > main :: IO ()
  40. -- > main = do
  41. -- > conn <- open "/home/sibi/test.db"
  42. -- > smt <- prepare conn "select * from t1;"
  43. -- > row1 <- step smt >> columns smt
  44. -- > row2 <- step smt >> columns smt
  45. -- > print (row1, row2)
  46. -- > finalize smt
  47. -- > close conn
  48. --
  49. -- On executing the above code:
  50. --
  51. -- > $ ./demo-program
  52. -- > $ ([PersistInt64 1,PersistInt64 1],[PersistInt64 2,PersistInt64 2])
  53. open,
  54. close,
  55. prepare,
  56. step,
  57. stepConn,
  58. reset,
  59. finalize,
  60. bindBlob,
  61. bindDouble,
  62. bindInt,
  63. bindInt64,
  64. bindNull,
  65. bindText,
  66. bind,
  67. column,
  68. columns,
  69. changes,
  70. mkLogFunction,
  71. freeLogFunction,
  72. config,
  73. status,
  74. softHeapLimit,
  75. enableExtendedResultCodes,
  76. disableExtendedResultCodes
  77. )
  78. where
  79. import Prelude hiding (error)
  80. import qualified Prelude as P
  81. import Control.Exception (Exception, throwIO)
  82. import qualified Data.ByteString as BS
  83. import qualified Data.ByteString.Unsafe as BSU
  84. import qualified Data.ByteString.Internal as BSI
  85. import Data.Fixed (Pico)
  86. import Data.IORef (IORef, newIORef, readIORef, writeIORef)
  87. import Data.Monoid (mappend, mconcat)
  88. import Data.Text (Text, pack, unpack)
  89. import Data.Text.Encoding (encodeUtf8, decodeUtf8With)
  90. import Data.Text.Encoding.Error (lenientDecode)
  91. import Data.Time (defaultTimeLocale, formatTime, UTCTime)
  92. import Data.Typeable (Typeable)
  93. import Foreign
  94. import Foreign.C
  95. import Database.Persist (PersistValue (..), listToJSON, mapToJSON)
  96. data Connection = Connection !(IORef Bool) Connection'
  97. newtype Connection' = Connection' (Ptr ())
  98. newtype Statement = Statement (Ptr ())
  99. -- | A custom exception type to make it easier to catch exceptions.
  100. --
  101. -- @since 2.1.3
  102. data SqliteException = SqliteException
  103. { seError :: !Error
  104. , seFunctionName :: !Text
  105. , seDetails :: !Text
  106. }
  107. deriving (Typeable)
  108. instance Show SqliteException where
  109. show (SqliteException error functionName details) = unpack $ Data.Monoid.mconcat
  110. ["SQLite3 returned "
  111. , pack $ show error
  112. , " while attempting to perform "
  113. , functionName
  114. , details
  115. ]
  116. instance Exception SqliteException
  117. data Error = ErrorOK
  118. | ErrorError
  119. | ErrorInternal
  120. | ErrorPermission
  121. | ErrorAbort
  122. | ErrorBusy
  123. | ErrorLocked
  124. | ErrorNoMemory
  125. | ErrorReadOnly
  126. | ErrorInterrupt
  127. | ErrorIO
  128. | ErrorNotFound
  129. | ErrorCorrupt
  130. | ErrorFull
  131. | ErrorCan'tOpen
  132. | ErrorProtocol
  133. | ErrorEmpty
  134. | ErrorSchema
  135. | ErrorTooBig
  136. | ErrorConstraint
  137. | ErrorMismatch
  138. | ErrorMisuse
  139. | ErrorNoLargeFileSupport
  140. | ErrorAuthorization
  141. | ErrorFormat
  142. | ErrorRange
  143. | ErrorNotAConnection
  144. | ErrorRow
  145. | ErrorDone
  146. deriving (Eq, Show)
  147. data StepResult = Row | Done deriving (Eq, Show)
  148. data ColumnType = IntegerColumn
  149. | FloatColumn
  150. | TextColumn
  151. | BlobColumn
  152. | NullColumn
  153. deriving (Eq, Show)
  154. decodeError :: Int -> Error
  155. decodeError 0 = ErrorOK
  156. decodeError 1 = ErrorError
  157. decodeError 2 = ErrorInternal
  158. decodeError 3 = ErrorPermission
  159. decodeError 4 = ErrorAbort
  160. decodeError 5 = ErrorBusy
  161. decodeError 6 = ErrorLocked
  162. decodeError 7 = ErrorNoMemory
  163. decodeError 8 = ErrorReadOnly
  164. decodeError 9 = ErrorInterrupt
  165. decodeError 10 = ErrorIO
  166. decodeError 11 = ErrorNotFound
  167. decodeError 12 = ErrorCorrupt
  168. decodeError 13 = ErrorFull
  169. decodeError 14 = ErrorCan'tOpen
  170. decodeError 15 = ErrorProtocol
  171. decodeError 16 = ErrorEmpty
  172. decodeError 17 = ErrorSchema
  173. decodeError 18 = ErrorTooBig
  174. decodeError 19 = ErrorConstraint
  175. decodeError 20 = ErrorMismatch
  176. decodeError 21 = ErrorMisuse
  177. decodeError 22 = ErrorNoLargeFileSupport
  178. decodeError 23 = ErrorAuthorization
  179. decodeError 24 = ErrorFormat
  180. decodeError 25 = ErrorRange
  181. decodeError 26 = ErrorNotAConnection
  182. decodeError 100 = ErrorRow
  183. decodeError 101 = ErrorDone
  184. decodeError i = P.error $ "decodeError " ++ show i
  185. decodeColumnType :: Int -> ColumnType
  186. decodeColumnType 1 = IntegerColumn
  187. decodeColumnType 2 = FloatColumn
  188. decodeColumnType 3 = TextColumn
  189. decodeColumnType 4 = BlobColumn
  190. decodeColumnType 5 = NullColumn
  191. decodeColumnType i = P.error $ "decodeColumnType " ++ show i
  192. foreign import ccall "sqlite3_errmsg"
  193. errmsgC :: Ptr () -> IO CString
  194. errmsg :: Connection -> IO Text
  195. errmsg (Connection _ (Connection' database)) = do
  196. message <- errmsgC database
  197. byteString <- BS.packCString message
  198. return $ decodeUtf8With lenientDecode byteString
  199. sqlError :: Maybe Connection -> Text -> Error -> IO a
  200. sqlError maybeConnection functionName error = do
  201. details <- case maybeConnection of
  202. Just database -> do
  203. details <- errmsg database
  204. return $ ": " `Data.Monoid.mappend` details
  205. Nothing -> return "."
  206. throwIO SqliteException
  207. { seError = error
  208. , seFunctionName = functionName
  209. , seDetails = details
  210. }
  211. foreign import ccall "sqlite3_open_v2"
  212. openC :: CString -> Ptr (Ptr ()) -> Int -> CString -> IO Int
  213. openError :: Text -> IO (Either Connection Error)
  214. openError path' = do
  215. let flag = sqliteFlagReadWrite .|. sqliteFlagCreate .|. sqliteFlagUri
  216. BS.useAsCString (encodeUtf8 path') $ \path -> alloca $ \database -> do
  217. err <- decodeError <$> openC path database flag nullPtr
  218. case err of
  219. ErrorOK -> do database' <- peek database
  220. active <- newIORef True
  221. return $ Left $ Connection active $ Connection' database'
  222. _ -> return $ Right err
  223. where
  224. -- for all sqlite flags, check out https://www.sqlite.org/c3ref/open.html
  225. sqliteFlagReadWrite = 0x2
  226. sqliteFlagCreate = 0x4
  227. sqliteFlagUri = 0x40
  228. open :: Text -> IO Connection
  229. open path = do
  230. databaseOrError <- openError path
  231. case databaseOrError of
  232. Left database -> return database
  233. Right error -> sqlError Nothing ("open " `mappend` (pack $ show path)) error
  234. foreign import ccall "sqlite3_close"
  235. closeC :: Ptr () -> IO Int
  236. closeError :: Connection -> IO Error
  237. closeError (Connection iactive (Connection' database)) = do
  238. writeIORef iactive False
  239. error <- closeC database
  240. return $ decodeError error
  241. close :: Connection -> IO ()
  242. close database = do
  243. error <- closeError database
  244. case error of
  245. ErrorOK -> return ()
  246. _ -> sqlError (Just database) "close" error
  247. foreign import ccall "sqlite3_extended_result_codes"
  248. sqlite3_extended_result_codesC :: Ptr () -> Int -> IO Int
  249. -- @since 2.9.2
  250. enableExtendedResultCodes :: Connection -> IO ()
  251. enableExtendedResultCodes con@(Connection _ (Connection' database)) = do
  252. error <- sqlite3_extended_result_codesC database 1
  253. let err = decodeError error
  254. case err of
  255. ErrorOK -> return ()
  256. _ -> sqlError (Just con) "enableExtendedResultCodes" err
  257. -- @since 2.9.2
  258. disableExtendedResultCodes :: Connection -> IO ()
  259. disableExtendedResultCodes con@(Connection _ (Connection' database)) = do
  260. error <- sqlite3_extended_result_codesC database 0
  261. let err = decodeError error
  262. case err of
  263. ErrorOK -> return ()
  264. _ -> sqlError (Just con) "disableExtendedResultCodes" err
  265. foreign import ccall "sqlite3_prepare_v2"
  266. prepareC :: Ptr () -> CString -> Int -> Ptr (Ptr ()) -> Ptr (Ptr ()) -> IO Int
  267. prepareError :: Connection -> Text -> IO (Either Statement Error)
  268. prepareError (Connection _ (Connection' database)) text' = do
  269. BS.useAsCString (encodeUtf8 text')
  270. (\text -> do
  271. alloca (\statement -> do
  272. error' <- prepareC database text (-1) statement nullPtr
  273. error <- return $ decodeError error'
  274. case error of
  275. ErrorOK -> do
  276. statement' <- peek statement
  277. return $ Left $ Statement statement'
  278. _ -> return $ Right error))
  279. prepare :: Connection -> Text -> IO Statement
  280. prepare database text = do
  281. statementOrError <- prepareError database text
  282. case statementOrError of
  283. Left statement -> return statement
  284. Right error -> sqlError (Just database) ("prepare " `mappend` (pack $ show text)) error
  285. foreign import ccall "sqlite3_step"
  286. stepC :: Ptr () -> IO Int
  287. stepError :: Statement -> IO Error
  288. stepError (Statement statement) = do
  289. error <- stepC statement
  290. return $ decodeError error
  291. -- | Execute a database statement. It's recommended to use 'stepConn' instead, because it gives better error messages.
  292. step :: Statement -> IO StepResult
  293. step statement = do
  294. error <- stepError statement
  295. case error of
  296. ErrorRow -> return Row
  297. ErrorDone -> return Done
  298. _ -> sqlError Nothing "step" error
  299. -- | Execute a database statement. This function uses the 'Connection' passed to it to give better error messages than 'step'.
  300. --
  301. -- @since 2.6.4
  302. stepConn :: Connection -> Statement -> IO StepResult
  303. stepConn database statement = do
  304. error <- stepError statement
  305. case error of
  306. ErrorRow -> return Row
  307. ErrorDone -> return Done
  308. _ -> sqlError (Just database) "step" error
  309. foreign import ccall "sqlite3_reset"
  310. resetC :: Ptr () -> IO Int
  311. resetError :: Statement -> IO Error
  312. resetError (Statement statement) = do
  313. error <- resetC statement
  314. return $ decodeError error
  315. reset :: Connection -> Statement -> IO ()
  316. reset (Connection iactive _) statement = do
  317. active <- readIORef iactive
  318. if active
  319. then do
  320. error <- resetError statement
  321. case error of
  322. ErrorOK -> return ()
  323. _ -> return () -- FIXME confirm this is correct sqlError Nothing "reset" error
  324. else return ()
  325. foreign import ccall "sqlite3_finalize"
  326. finalizeC :: Ptr () -> IO Int
  327. finalizeError :: Statement -> IO Error
  328. finalizeError (Statement statement) = do
  329. error <- finalizeC statement
  330. return $ decodeError error
  331. finalize :: Statement -> IO ()
  332. finalize statement = do
  333. error <- finalizeError statement
  334. case error of
  335. ErrorOK -> return ()
  336. _ -> return () -- sqlError Nothing "finalize" error
  337. -- Taken from: https://github.com/IreneKnapp/direct-sqlite/blob/master/Database/SQLite3/Direct.hs
  338. -- | Like 'unsafeUseAsCStringLen', but if the string is empty,
  339. -- never pass the callback a null pointer.
  340. unsafeUseAsCStringLenNoNull
  341. :: BS.ByteString
  342. -> (CString -> Int -> IO a)
  343. -> IO a
  344. unsafeUseAsCStringLenNoNull bs cb
  345. | BS.null bs = cb (intPtrToPtr 1) 0
  346. | otherwise = BSU.unsafeUseAsCStringLen bs $ \(ptr, len) ->
  347. cb ptr (fromIntegral len)
  348. foreign import ccall "sqlite3_bind_blob"
  349. bindBlobC :: Ptr () -> Int -> Ptr () -> Int -> Ptr () -> IO Int
  350. bindBlobError :: Statement -> Int -> BS.ByteString -> IO Error
  351. bindBlobError (Statement statement) parameterIndex byteString =
  352. unsafeUseAsCStringLenNoNull byteString $ \dataC size -> do
  353. error <- bindBlobC statement parameterIndex (castPtr dataC) size
  354. (intPtrToPtr (-1))
  355. return $ decodeError error
  356. bindBlob :: Statement -> Int -> BS.ByteString -> IO ()
  357. bindBlob statement parameterIndex byteString = do
  358. error <- bindBlobError statement parameterIndex byteString
  359. case error of
  360. ErrorOK -> return ()
  361. _ -> sqlError Nothing "bind blob" error
  362. foreign import ccall "sqlite3_bind_double"
  363. bindDoubleC :: Ptr () -> Int -> Double -> IO Int
  364. bindDoubleError :: Statement -> Int -> Double -> IO Error
  365. bindDoubleError (Statement statement) parameterIndex datum = do
  366. error <- bindDoubleC statement parameterIndex datum
  367. return $ decodeError error
  368. bindDouble :: Statement -> Int -> Double -> IO ()
  369. bindDouble statement parameterIndex datum = do
  370. error <- bindDoubleError statement parameterIndex datum
  371. case error of
  372. ErrorOK -> return ()
  373. _ -> sqlError Nothing "bind double" error
  374. foreign import ccall "sqlite3_bind_int"
  375. bindIntC :: Ptr () -> Int -> Int -> IO Int
  376. bindIntError :: Statement -> Int -> Int -> IO Error
  377. bindIntError (Statement statement) parameterIndex datum = do
  378. error <- bindIntC statement parameterIndex datum
  379. return $ decodeError error
  380. bindInt :: Statement -> Int -> Int -> IO ()
  381. bindInt statement parameterIndex datum = do
  382. error <- bindIntError statement parameterIndex datum
  383. case error of
  384. ErrorOK -> return ()
  385. _ -> sqlError Nothing "bind int" error
  386. foreign import ccall "sqlite3_bind_int64"
  387. bindInt64C :: Ptr () -> Int -> Int64 -> IO Int
  388. bindInt64Error :: Statement -> Int -> Int64 -> IO Error
  389. bindInt64Error (Statement statement) parameterIndex datum = do
  390. error <- bindInt64C statement parameterIndex datum
  391. return $ decodeError error
  392. bindInt64 :: Statement -> Int -> Int64 -> IO ()
  393. bindInt64 statement parameterIndex datum = do
  394. error <- bindInt64Error statement parameterIndex datum
  395. case error of
  396. ErrorOK -> return ()
  397. _ -> sqlError Nothing "bind int64" error
  398. foreign import ccall "sqlite3_bind_null"
  399. bindNullC :: Ptr () -> Int -> IO Int
  400. bindNullError :: Statement -> Int -> IO Error
  401. bindNullError (Statement statement) parameterIndex = do
  402. error <- bindNullC statement parameterIndex
  403. return $ decodeError error
  404. bindNull :: Statement -> Int -> IO ()
  405. bindNull statement parameterIndex = do
  406. error <- bindNullError statement parameterIndex
  407. case error of
  408. ErrorOK -> return ()
  409. _ -> sqlError Nothing "bind null" error
  410. foreign import ccall "sqlite3_bind_text"
  411. bindTextC :: Ptr () -> Int -> CString -> Int -> Ptr () -> IO Int
  412. bindTextError :: Statement -> Int -> Text -> IO Error
  413. bindTextError (Statement statement) parameterIndex text =
  414. unsafeUseAsCStringLenNoNull (encodeUtf8 text) $ \dataC size -> do
  415. error <- bindTextC statement parameterIndex dataC size (intPtrToPtr (-1))
  416. return $ decodeError error
  417. bindText :: Statement -> Int -> Text -> IO ()
  418. bindText statement parameterIndex text = do
  419. error <- bindTextError statement parameterIndex text
  420. case error of
  421. ErrorOK -> return ()
  422. _ -> sqlError Nothing "bind text" error
  423. bind :: Statement -> [PersistValue] -> IO ()
  424. bind statement sqlData = do
  425. mapM_ (\(parameterIndex, datum) -> do
  426. case datum of
  427. PersistInt64 int64 -> bindInt64 statement parameterIndex int64
  428. PersistDouble double -> bindDouble statement parameterIndex double
  429. PersistRational rational -> bindText statement parameterIndex $ pack $ show (fromRational rational :: Pico)
  430. PersistBool b -> bindInt64 statement parameterIndex $
  431. if b then 1 else 0
  432. PersistText text -> bindText statement parameterIndex text
  433. PersistByteString blob -> bindBlob statement parameterIndex blob
  434. PersistNull -> bindNull statement parameterIndex
  435. PersistDay d -> bindText statement parameterIndex $ pack $ show d
  436. PersistTimeOfDay d -> bindText statement parameterIndex $ pack $ show d
  437. PersistUTCTime d -> bindText statement parameterIndex $ pack $ format8601 d
  438. PersistList l -> bindText statement parameterIndex $ listToJSON l
  439. PersistMap m -> bindText statement parameterIndex $ mapToJSON m
  440. PersistDbSpecific s -> bindText statement parameterIndex $ decodeUtf8With lenientDecode s
  441. PersistArray a -> bindText statement parameterIndex $ listToJSON a -- copy of PersistList's definition
  442. PersistObjectId _ -> P.error "Refusing to serialize a PersistObjectId to a SQLite value"
  443. )
  444. $ zip [1..] sqlData
  445. return ()
  446. format8601 :: UTCTime -> String
  447. format8601 = formatTime defaultTimeLocale "%FT%T%Q"
  448. foreign import ccall "sqlite3_column_type"
  449. columnTypeC :: Ptr () -> Int -> IO Int
  450. columnType :: Statement -> Int -> IO ColumnType
  451. columnType (Statement statement) columnIndex = do
  452. result <- columnTypeC statement columnIndex
  453. return $ decodeColumnType result
  454. foreign import ccall "sqlite3_column_bytes"
  455. columnBytesC :: Ptr () -> Int -> IO Int
  456. foreign import ccall "sqlite3_column_blob"
  457. columnBlobC :: Ptr () -> Int -> IO (Ptr ())
  458. columnBlob :: Statement -> Int -> IO BS.ByteString
  459. columnBlob (Statement statement) columnIndex = do
  460. size <- columnBytesC statement columnIndex
  461. BSI.create size (\resultPtr -> do
  462. dataPtr <- columnBlobC statement columnIndex
  463. if dataPtr /= nullPtr
  464. then BSI.memcpy resultPtr (castPtr dataPtr) (fromIntegral size)
  465. else return ())
  466. foreign import ccall "sqlite3_column_int64"
  467. columnInt64C :: Ptr () -> Int -> IO Int64
  468. columnInt64 :: Statement -> Int -> IO Int64
  469. columnInt64 (Statement statement) columnIndex = do
  470. columnInt64C statement columnIndex
  471. foreign import ccall "sqlite3_column_double"
  472. columnDoubleC :: Ptr () -> Int -> IO Double
  473. columnDouble :: Statement -> Int -> IO Double
  474. columnDouble (Statement statement) columnIndex = do
  475. columnDoubleC statement columnIndex
  476. foreign import ccall "sqlite3_column_text"
  477. columnTextC :: Ptr () -> Int -> IO CString
  478. columnText :: Statement -> Int -> IO Text
  479. columnText (Statement statement) columnIndex = do
  480. text <- columnTextC statement columnIndex
  481. byteString <- BS.packCString text
  482. return $ decodeUtf8With lenientDecode byteString
  483. foreign import ccall "sqlite3_column_count"
  484. columnCountC :: Ptr () -> IO Int
  485. columnCount :: Statement -> IO Int
  486. columnCount (Statement statement) = do
  487. columnCountC statement
  488. column :: Statement -> Int -> IO PersistValue
  489. column statement columnIndex = do
  490. theType <- columnType statement columnIndex
  491. case theType of
  492. IntegerColumn -> do
  493. int64 <- columnInt64 statement columnIndex
  494. return $ PersistInt64 int64
  495. FloatColumn -> do
  496. double <- columnDouble statement columnIndex
  497. return $ PersistDouble double
  498. TextColumn -> do
  499. text <- columnText statement columnIndex
  500. return $ PersistText text
  501. BlobColumn -> do
  502. byteString <- columnBlob statement columnIndex
  503. return $ PersistByteString byteString
  504. NullColumn -> return PersistNull
  505. columns :: Statement -> IO [PersistValue]
  506. columns statement = do
  507. count <- columnCount statement
  508. mapM (\i -> column statement i) [0..count-1]
  509. foreign import ccall "sqlite3_changes"
  510. changesC :: Connection' -> IO Int
  511. changes :: Connection -> IO Int64
  512. changes (Connection _ c) = fmap fromIntegral $ changesC c
  513. -- | Log function callback. Arguments are error code and log message.
  514. --
  515. -- @since 2.1.4
  516. type RawLogFunction = Ptr () -> Int -> CString -> IO ()
  517. foreign import ccall "wrapper"
  518. mkRawLogFunction :: RawLogFunction -> IO (FunPtr RawLogFunction)
  519. -- |
  520. -- @since 2.1.4
  521. newtype LogFunction = LogFunction (FunPtr RawLogFunction)
  522. -- | Wraps a given function to a 'LogFunction' to be further used with 'ConfigLogFn'.
  523. -- First argument of given function will take error code, second - log message.
  524. -- Returned value should be released with 'freeLogFunction' when no longer required.
  525. mkLogFunction :: (Int -> String -> IO ()) -> IO LogFunction
  526. mkLogFunction fn = fmap LogFunction . mkRawLogFunction $ \_ errCode cmsg -> do
  527. msg <- peekCString cmsg
  528. fn errCode msg
  529. -- | Releases a native FunPtr for the 'LogFunction'.
  530. --
  531. -- @since 2.1.4
  532. freeLogFunction :: LogFunction -> IO ()
  533. freeLogFunction (LogFunction fn) = freeHaskellFunPtr fn
  534. -- | Configuration option for SQLite to be used together with the 'config' function.
  535. --
  536. -- @since 2.1.4
  537. data Config
  538. -- | A function to be used for logging
  539. = ConfigLogFn LogFunction
  540. foreign import ccall "persistent_sqlite_set_log"
  541. set_logC :: FunPtr RawLogFunction -> Ptr () -> IO Int
  542. -- | Sets SQLite global configuration parameter. See SQLite documentation for the <https://www.sqlite.org/c3ref/config.html sqlite3_config> function.
  543. -- In short, this must be called prior to any other SQLite function if you want the call to succeed.
  544. --
  545. -- @since 2.1.4
  546. config :: Config -> IO ()
  547. config c = case c of
  548. ConfigLogFn (LogFunction rawLogFn) -> do
  549. e <- fmap decodeError $ set_logC rawLogFn nullPtr
  550. case e of
  551. ErrorOK -> return ()
  552. _ -> sqlError Nothing "sqlite3_config" e
  553. -- | Return type of the 'status' function
  554. --
  555. -- @since 2.6.1
  556. data SqliteStatus = SqliteStatus
  557. { sqliteStatusCurrent :: Maybe Int
  558. -- ^ The current value of the parameter. Some parameters do not record current value.
  559. , sqliteStatusHighwater :: Maybe Int
  560. -- ^ The highest recorded value. Some parameters do not record the highest value.
  561. } deriving (Eq, Show)
  562. -- | Run-time status parameter that can be returned by 'status' function.
  563. --
  564. -- @since 2.6.1
  565. data SqliteStatusVerb
  566. -- | This parameter is the current amount of memory checked out using sqlite3_malloc(),
  567. -- either directly or indirectly. The figure includes calls made to sqlite3_malloc()
  568. -- by the application and internal memory usage by the SQLite library. Scratch memory
  569. -- controlled by SQLITE_CONFIG_SCRATCH and auxiliary page-cache memory controlled by
  570. -- SQLITE_CONFIG_PAGECACHE is not included in this parameter. The amount returned is
  571. -- the sum of the allocation sizes as reported by the xSize method in sqlite3_mem_methods.
  572. = SqliteStatusMemoryUsed
  573. -- | This parameter returns the number of pages used out of the pagecache memory
  574. -- allocator that was configured using SQLITE_CONFIG_PAGECACHE. The value returned
  575. -- is in pages, not in bytes.
  576. | SqliteStatusPagecacheUsed
  577. -- | This parameter returns the number of bytes of page cache allocation which
  578. -- could not be satisfied by the SQLITE_CONFIG_PAGECACHE buffer and where forced
  579. -- to overflow to sqlite3_malloc(). The returned value includes allocations that
  580. -- overflowed because they where too large (they were larger than the "sz"
  581. -- parameter to SQLITE_CONFIG_PAGECACHE) and allocations that overflowed because
  582. -- no space was left in the page cache.
  583. | SqliteStatusPagecacheOverflow
  584. -- | This parameter returns the number of allocations used out of the scratch
  585. -- memory allocator configured using SQLITE_CONFIG_SCRATCH. The value returned
  586. -- is in allocations, not in bytes. Since a single thread may only have one
  587. -- scratch allocation outstanding at time, this parameter also reports the
  588. -- number of threads using scratch memory at the same time.
  589. | SqliteStatusScratchUsed
  590. -- | This parameter returns the number of bytes of scratch memory allocation
  591. -- which could not be satisfied by the SQLITE_CONFIG_SCRATCH buffer and where
  592. -- forced to overflow to sqlite3_malloc(). The values returned include overflows
  593. -- because the requested allocation was too larger (that is, because the requested
  594. -- allocation was larger than the "sz" parameter to SQLITE_CONFIG_SCRATCH) and
  595. -- because no scratch buffer slots were available.
  596. | SqliteStatusScratchOverflow
  597. -- | This parameter records the largest memory allocation request handed to
  598. -- sqlite3_malloc() or sqlite3_realloc() (or their internal equivalents). Only
  599. -- the value returned in 'sqliteStatusHighwater' field of 'SqliteStatus' record
  600. -- is of interest. The value written into the 'sqliteStatusCurrent' field is Nothing.
  601. | SqliteStatusMallocSize
  602. -- | This parameter records the largest memory allocation request handed to
  603. -- pagecache memory allocator. Only the value returned in the 'sqliteStatusHighwater'
  604. -- field of 'SqliteStatus' record is of interest. The value written into the
  605. -- 'sqliteStatusCurrent' field is Nothing.
  606. | SqliteStatusPagecacheSize
  607. -- | This parameter records the largest memory allocation request handed to
  608. -- scratch memory allocator. Only the value returned in the 'sqliteStatusHighwater'
  609. -- field of 'SqliteStatus' record is of interest. The value written into the
  610. -- 'sqliteStatusCurrent' field is Nothing.
  611. | SqliteStatusScratchSize
  612. -- | This parameter records the number of separate memory allocations currently
  613. -- checked out.
  614. | SqliteStatusMallocCount
  615. -- Internal function to convert status parameter to a triple of its integral
  616. -- constant and two bools indicating if native sqlite3_status function actually
  617. -- modifies values at pCurrent and pHighwater pointers.
  618. statusVerbInfo :: SqliteStatusVerb -> (CInt, Bool, Bool)
  619. statusVerbInfo v = case v of
  620. SqliteStatusMemoryUsed -> (0, True, True)
  621. SqliteStatusPagecacheUsed -> (1, True, True)
  622. SqliteStatusPagecacheOverflow -> (2, True, True)
  623. SqliteStatusScratchUsed -> (3, True, True)
  624. SqliteStatusScratchOverflow -> (4, True, True)
  625. SqliteStatusMallocSize -> (5, False, True)
  626. SqliteStatusPagecacheSize -> (7, False, True)
  627. SqliteStatusScratchSize -> (8, False, True)
  628. SqliteStatusMallocCount -> (9, True, True)
  629. foreign import ccall "sqlite3_status"
  630. statusC :: CInt -> Ptr CInt -> Ptr CInt -> CInt -> IO Int
  631. -- | Retrieves runtime status information about the performance of SQLite,
  632. -- and optionally resets various highwater marks. The first argument is a
  633. -- status parameter to measure, the second is reset flag. If reset flag is
  634. -- True then the highest recorded value is reset after being returned from
  635. -- this function.
  636. --
  637. -- @since 2.6.1
  638. status :: SqliteStatusVerb -> Bool -> IO SqliteStatus
  639. status verb reset' = alloca $ \pCurrent -> alloca $ \pHighwater -> do
  640. let (code, hasCurrent, hasHighwater) = statusVerbInfo verb
  641. e <- decodeError <$> statusC code pCurrent pHighwater (if reset' then 1 else 0)
  642. case e of
  643. ErrorOK -> do
  644. current <- if hasCurrent then Just . fromIntegral <$> peek pCurrent else return Nothing
  645. highwater <- if hasHighwater then Just . fromIntegral <$> peek pHighwater else return Nothing
  646. return $ SqliteStatus current highwater
  647. _ -> sqlError Nothing "sqlite3_status" e
  648. foreign import ccall "sqlite3_soft_heap_limit64"
  649. softHeapLimit64C :: CLLong -> IO CLLong
  650. -- | Sets and/or queries the soft limit on the amount of heap memory that may be
  651. -- allocated by SQLite. If the argument is zero then the soft heap limit is disabled.
  652. -- If the argument is negative then no change is made to the soft heap limit. Hence,
  653. -- the current size of the soft heap limit can be determined by invoking
  654. -- this function with a negative argument.
  655. --
  656. -- @since 2.6.1
  657. softHeapLimit :: Int64 -> IO Int64
  658. softHeapLimit x = fromIntegral <$> softHeapLimit64C (CLLong x)