Sqlite.hs 25 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688
  1. {-# LANGUAGE FlexibleContexts #-}
  2. {-# LANGUAGE OverloadedStrings #-}
  3. {-# LANGUAGE PatternGuards #-}
  4. {-# LANGUAGE ScopedTypeVariables #-}
  5. {-# LANGUAGE TemplateHaskell #-}
  6. {-# LANGUAGE TupleSections #-}
  7. {-# LANGUAGE TypeFamilies #-}
  8. -- | A sqlite backend for persistent.
  9. --
  10. -- Note: If you prepend @WAL=off @ to your connection string, it will disable
  11. -- the write-ahead log. This functionality is now deprecated in favour of using SqliteConnectionInfo.
  12. module Database.Persist.Sqlite
  13. ( withSqlitePool
  14. , withSqlitePoolInfo
  15. , withSqliteConn
  16. , withSqliteConnInfo
  17. , createSqlitePool
  18. , createSqlitePoolFromInfo
  19. , module Database.Persist.Sql
  20. , SqliteConf (..)
  21. , SqliteConnectionInfo
  22. , mkSqliteConnectionInfo
  23. , sqlConnectionStr
  24. , walEnabled
  25. , fkEnabled
  26. , extraPragmas
  27. , runSqlite
  28. , runSqliteInfo
  29. , wrapConnection
  30. , wrapConnectionInfo
  31. , mockMigration
  32. , retryOnBusy
  33. , waitForDatabase
  34. ) where
  35. import Control.Concurrent (threadDelay)
  36. import qualified Control.Exception as E
  37. import Control.Monad (forM_)
  38. import Control.Monad.IO.Unlift (MonadIO (..), MonadUnliftIO, withUnliftIO, unliftIO, withRunInIO)
  39. import Control.Monad.Logger (NoLoggingT, runNoLoggingT, MonadLogger, logWarn, runLoggingT)
  40. import Control.Monad.Trans.Reader (ReaderT, runReaderT)
  41. import Control.Monad.Trans.Writer (runWriterT)
  42. import Data.Acquire (Acquire, mkAcquire, with)
  43. import Data.Aeson
  44. import Data.Aeson.Types (modifyFailure)
  45. import Data.Conduit
  46. import qualified Data.Conduit.List as CL
  47. import qualified Data.HashMap.Lazy as HashMap
  48. import Data.Int (Int64)
  49. import Data.IORef
  50. import qualified Data.Map as Map
  51. import Data.Monoid ((<>))
  52. import Data.Pool (Pool)
  53. import Data.Text (Text)
  54. import qualified Data.Text as T
  55. import qualified Data.Text.IO as TIO
  56. import Lens.Micro.TH (makeLenses)
  57. import UnliftIO.Resource (ResourceT, runResourceT)
  58. import Database.Persist.Sql
  59. import Database.Persist.Sql.Types.Internal (mkPersistBackend)
  60. import qualified Database.Persist.Sql.Util as Util
  61. import qualified Database.Sqlite as Sqlite
  62. -- | Create a pool of SQLite connections.
  63. --
  64. -- Note that this should not be used with the @:memory:@ connection string, as
  65. -- the pool will regularly remove connections, destroying your database.
  66. -- Instead, use 'withSqliteConn'.
  67. createSqlitePool :: (MonadLogger m, MonadUnliftIO m)
  68. => Text -> Int -> m (Pool SqlBackend)
  69. createSqlitePool = createSqlitePoolFromInfo . conStringToInfo
  70. -- | Create a pool of SQLite connections.
  71. --
  72. -- Note that this should not be used with the @:memory:@ connection string, as
  73. -- the pool will regularly remove connections, destroying your database.
  74. -- Instead, use 'withSqliteConn'.
  75. --
  76. -- @since 2.6.2
  77. createSqlitePoolFromInfo :: (MonadLogger m, MonadUnliftIO m)
  78. => SqliteConnectionInfo -> Int -> m (Pool SqlBackend)
  79. createSqlitePoolFromInfo connInfo = createSqlPool $ open' connInfo
  80. -- | Run the given action with a connection pool.
  81. --
  82. -- Like 'createSqlitePool', this should not be used with @:memory:@.
  83. withSqlitePool :: (MonadUnliftIO m, MonadLogger m)
  84. => Text
  85. -> Int -- ^ number of connections to open
  86. -> (Pool SqlBackend -> m a) -> m a
  87. withSqlitePool connInfo = withSqlPool . open' $ conStringToInfo connInfo
  88. -- | Run the given action with a connection pool.
  89. --
  90. -- Like 'createSqlitePool', this should not be used with @:memory:@.
  91. --
  92. -- @since 2.6.2
  93. withSqlitePoolInfo :: (MonadUnliftIO m, MonadLogger m)
  94. => SqliteConnectionInfo
  95. -> Int -- ^ number of connections to open
  96. -> (Pool SqlBackend -> m a) -> m a
  97. withSqlitePoolInfo connInfo = withSqlPool $ open' connInfo
  98. withSqliteConn :: (MonadUnliftIO m, MonadLogger m)
  99. => Text -> (SqlBackend -> m a) -> m a
  100. withSqliteConn = withSqliteConnInfo . conStringToInfo
  101. -- | @since 2.6.2
  102. withSqliteConnInfo :: (MonadUnliftIO m, MonadLogger m)
  103. => SqliteConnectionInfo -> (SqlBackend -> m a) -> m a
  104. withSqliteConnInfo = withSqlConn . open'
  105. open' :: SqliteConnectionInfo -> LogFunc -> IO SqlBackend
  106. open' connInfo logFunc = do
  107. conn <- Sqlite.open $ _sqlConnectionStr connInfo
  108. wrapConnectionInfo connInfo conn logFunc `E.onException` Sqlite.close conn
  109. -- | Wrap up a raw 'Sqlite.Connection' as a Persistent SQL 'Connection'.
  110. --
  111. -- === __Example usage__
  112. --
  113. -- > {-# LANGUAGE GADTs #-}
  114. -- > {-# LANGUAGE ScopedTypeVariables #-}
  115. -- > {-# LANGUAGE OverloadedStrings #-}
  116. -- > {-# LANGUAGE MultiParamTypeClasses #-}
  117. -- > {-# LANGUAGE TypeFamilies #-}
  118. -- > {-# LANGUAGE TemplateHaskell #-}
  119. -- > {-# LANGUAGE QuasiQuotes #-}
  120. -- > {-# LANGUAGE GeneralizedNewtypeDeriving #-}
  121. -- >
  122. -- > import Control.Monad.IO.Class (liftIO)
  123. -- > import Database.Persist
  124. -- > import Database.Sqlite
  125. -- > import Database.Persist.Sqlite
  126. -- > import Database.Persist.TH
  127. -- >
  128. -- > share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase|
  129. -- > Person
  130. -- > name String
  131. -- > age Int Maybe
  132. -- > deriving Show
  133. -- > |]
  134. -- >
  135. -- > main :: IO ()
  136. -- > main = do
  137. -- > conn <- open "/home/sibi/test.db"
  138. -- > (backend :: SqlBackend) <- wrapConnection conn (\_ _ _ _ -> return ())
  139. -- > flip runSqlPersistM backend $ do
  140. -- > runMigration migrateAll
  141. -- > insert_ $ Person "John doe" $ Just 35
  142. -- > insert_ $ Person "Hema" $ Just 36
  143. -- > (pers :: [Entity Person]) <- selectList [] []
  144. -- > liftIO $ print pers
  145. -- > close' backend
  146. --
  147. -- On executing it, you get this output:
  148. --
  149. -- > Migrating: CREATE TABLE "person"("id" INTEGER PRIMARY KEY,"name" VARCHAR NOT NULL,"age" INTEGER NULL)
  150. -- > [Entity {entityKey = PersonKey {unPersonKey = SqlBackendKey {unSqlBackendKey = 1}}, entityVal = Person {personName = "John doe", personAge = Just 35}},Entity {entityKey = PersonKey {unPersonKey = SqlBackendKey {unSqlBackendKey = 2}}, entityVal = Person {personName = "Hema", personAge = Just 36}}]
  151. --
  152. -- @since 1.1.5
  153. wrapConnection :: Sqlite.Connection -> LogFunc -> IO SqlBackend
  154. wrapConnection = wrapConnectionInfo (mkSqliteConnectionInfo "")
  155. -- | Retry if a Busy is thrown, following an exponential backoff strategy.
  156. --
  157. -- @since 2.9.3
  158. retryOnBusy :: (MonadUnliftIO m, MonadLogger m) => m a -> m a
  159. retryOnBusy action =
  160. start $ take 20 $ delays 1000
  161. where
  162. delays x
  163. | x >= 1000000 = repeat x
  164. | otherwise = x : delays (x * 2)
  165. start [] = do
  166. $logWarn "Out of retry attempts"
  167. action
  168. start (x:xs) = do
  169. -- Using try instead of catch to avoid creating a stack overflow
  170. eres <- withRunInIO $ \run -> E.try $ run action
  171. case eres of
  172. Left (Sqlite.SqliteException { Sqlite.seError = Sqlite.ErrorBusy }) -> do
  173. $logWarn "Encountered an SQLITE_BUSY, going to retry..."
  174. liftIO $ threadDelay x
  175. start xs
  176. Left e -> liftIO $ E.throwIO e
  177. Right y -> return y
  178. -- | Wait until some noop action on the database does not return an 'Sqlite.ErrorBusy'. See 'retryOnBusy'.
  179. --
  180. -- @since 2.9.3
  181. waitForDatabase
  182. :: (MonadUnliftIO m, MonadLogger m, BackendCompatible SqlBackend backend)
  183. => ReaderT backend m ()
  184. waitForDatabase = retryOnBusy $ rawExecute "SELECT 42" []
  185. -- | Wrap up a raw 'Sqlite.Connection' as a Persistent SQL
  186. -- 'Connection', allowing full control over WAL and FK constraints.
  187. --
  188. -- @since 2.6.2
  189. wrapConnectionInfo
  190. :: SqliteConnectionInfo
  191. -> Sqlite.Connection
  192. -> LogFunc
  193. -> IO SqlBackend
  194. wrapConnectionInfo connInfo conn logFunc = do
  195. let
  196. -- Turn on the write-ahead log
  197. -- https://github.com/yesodweb/persistent/issues/363
  198. walPragma
  199. | _walEnabled connInfo = (("PRAGMA journal_mode=WAL;", True):)
  200. | otherwise = id
  201. -- Turn on foreign key constraints
  202. -- https://github.com/yesodweb/persistent/issues/646
  203. fkPragma
  204. | _fkEnabled connInfo = (("PRAGMA foreign_keys = on;", False):)
  205. | otherwise = id
  206. -- Allow arbitrary additional pragmas to be set
  207. -- https://github.com/commercialhaskell/stack/issues/4247
  208. pragmas = walPragma $ fkPragma $ map (, False) $ _extraPragmas connInfo
  209. forM_ pragmas $ \(pragma, shouldRetry) -> flip runLoggingT logFunc $
  210. (if shouldRetry then retryOnBusy else id) $ liftIO $ do
  211. stmt <- Sqlite.prepare conn pragma
  212. _ <- Sqlite.stepConn conn stmt
  213. Sqlite.reset conn stmt
  214. Sqlite.finalize stmt
  215. smap <- newIORef $ Map.empty
  216. return $ SqlBackend
  217. { connPrepare = prepare' conn
  218. , connStmtMap = smap
  219. , connInsertSql = insertSql'
  220. , connUpsertSql = Nothing
  221. , connPutManySql = Just putManySql
  222. , connInsertManySql = Nothing
  223. , connClose = Sqlite.close conn
  224. , connMigrateSql = migrate'
  225. , connBegin = \f _ -> helper "BEGIN" f
  226. , connCommit = helper "COMMIT"
  227. , connRollback = ignoreExceptions . helper "ROLLBACK"
  228. , connEscapeName = escape
  229. , connNoLimit = "LIMIT -1"
  230. , connRDBMS = "sqlite"
  231. , connLimitOffset = decorateSQLWithLimitOffset "LIMIT -1"
  232. , connLogFunc = logFunc
  233. , connMaxParams = Just 999
  234. , connRepsertManySql = Just repsertManySql
  235. , connInsertUniqueSql = Nothing
  236. }
  237. where
  238. helper t getter = do
  239. stmt <- getter t
  240. _ <- stmtExecute stmt []
  241. stmtReset stmt
  242. ignoreExceptions = E.handle (\(_ :: E.SomeException) -> return ())
  243. -- | A convenience helper which creates a new database connection and runs the
  244. -- given block, handling @MonadResource@ and @MonadLogger@ requirements. Note
  245. -- that all log messages are discarded.
  246. --
  247. -- @since 1.1.4
  248. runSqlite :: (MonadUnliftIO m)
  249. => Text -- ^ connection string
  250. -> ReaderT SqlBackend (NoLoggingT (ResourceT m)) a -- ^ database action
  251. -> m a
  252. runSqlite connstr = runResourceT
  253. . runNoLoggingT
  254. . withSqliteConn connstr
  255. . runSqlConn
  256. -- | A convenience helper which creates a new database connection and runs the
  257. -- given block, handling @MonadResource@ and @MonadLogger@ requirements. Note
  258. -- that all log messages are discarded.
  259. --
  260. -- @since 2.6.2
  261. runSqliteInfo :: (MonadUnliftIO m)
  262. => SqliteConnectionInfo
  263. -> ReaderT SqlBackend (NoLoggingT (ResourceT m)) a -- ^ database action
  264. -> m a
  265. runSqliteInfo conInfo = runResourceT
  266. . runNoLoggingT
  267. . withSqliteConnInfo conInfo
  268. . runSqlConn
  269. prepare' :: Sqlite.Connection -> Text -> IO Statement
  270. prepare' conn sql = do
  271. stmt <- Sqlite.prepare conn sql
  272. return Statement
  273. { stmtFinalize = Sqlite.finalize stmt
  274. , stmtReset = Sqlite.reset conn stmt
  275. , stmtExecute = execute' conn stmt
  276. , stmtQuery = withStmt' conn stmt
  277. }
  278. insertSql' :: EntityDef -> [PersistValue] -> InsertSqlResult
  279. insertSql' ent vals =
  280. case entityPrimary ent of
  281. Just _ ->
  282. ISRManyKeys sql vals
  283. where sql = T.concat
  284. [ "INSERT INTO "
  285. , escape $ entityDB ent
  286. , "("
  287. , T.intercalate "," $ map (escape . fieldDB) $ entityFields ent
  288. , ") VALUES("
  289. , T.intercalate "," (map (const "?") $ entityFields ent)
  290. , ")"
  291. ]
  292. Nothing ->
  293. ISRInsertGet ins sel
  294. where
  295. sel = T.concat
  296. [ "SELECT "
  297. , escape $ fieldDB (entityId ent)
  298. , " FROM "
  299. , escape $ entityDB ent
  300. , " WHERE _ROWID_=last_insert_rowid()"
  301. ]
  302. ins = T.concat
  303. [ "INSERT INTO "
  304. , escape $ entityDB ent
  305. , if null (entityFields ent)
  306. then " VALUES(null)"
  307. else T.concat
  308. [ "("
  309. , T.intercalate "," $ map (escape . fieldDB) $ entityFields ent
  310. , ") VALUES("
  311. , T.intercalate "," (map (const "?") $ entityFields ent)
  312. , ")"
  313. ]
  314. ]
  315. execute' :: Sqlite.Connection -> Sqlite.Statement -> [PersistValue] -> IO Int64
  316. execute' conn stmt vals = flip finally (liftIO $ Sqlite.reset conn stmt) $ do
  317. Sqlite.bind stmt vals
  318. _ <- Sqlite.stepConn conn stmt
  319. Sqlite.changes conn
  320. withStmt'
  321. :: MonadIO m
  322. => Sqlite.Connection
  323. -> Sqlite.Statement
  324. -> [PersistValue]
  325. -> Acquire (ConduitM () [PersistValue] m ())
  326. withStmt' conn stmt vals = do
  327. _ <- mkAcquire
  328. (Sqlite.bind stmt vals >> return stmt)
  329. (Sqlite.reset conn)
  330. return pull
  331. where
  332. pull = do
  333. x <- liftIO $ Sqlite.stepConn conn stmt
  334. case x of
  335. Sqlite.Done -> return ()
  336. Sqlite.Row -> do
  337. cols <- liftIO $ Sqlite.columns stmt
  338. yield cols
  339. pull
  340. showSqlType :: SqlType -> Text
  341. showSqlType SqlString = "VARCHAR"
  342. showSqlType SqlInt32 = "INTEGER"
  343. showSqlType SqlInt64 = "INTEGER"
  344. showSqlType SqlReal = "REAL"
  345. showSqlType (SqlNumeric precision scale) = T.concat [ "NUMERIC(", T.pack (show precision), ",", T.pack (show scale), ")" ]
  346. showSqlType SqlDay = "DATE"
  347. showSqlType SqlTime = "TIME"
  348. showSqlType SqlDayTime = "TIMESTAMP"
  349. showSqlType SqlBlob = "BLOB"
  350. showSqlType SqlBool = "BOOLEAN"
  351. showSqlType (SqlOther t) = t
  352. migrate' :: [EntityDef]
  353. -> (Text -> IO Statement)
  354. -> EntityDef
  355. -> IO (Either [Text] [(Bool, Text)])
  356. migrate' allDefs getter val = do
  357. let (cols, uniqs, _) = mkColumns allDefs val
  358. let newSql = mkCreateTable False def (filter (not . safeToRemove val . cName) cols, uniqs)
  359. stmt <- getter "SELECT sql FROM sqlite_master WHERE type='table' AND name=?"
  360. oldSql' <- with (stmtQuery stmt [PersistText $ unDBName table])
  361. (\src -> runConduit $ src .| go)
  362. case oldSql' of
  363. Nothing -> return $ Right [(False, newSql)]
  364. Just oldSql -> do
  365. if oldSql == newSql
  366. then return $ Right []
  367. else do
  368. sql <- getCopyTable allDefs getter val
  369. return $ Right sql
  370. where
  371. def = val
  372. table = entityDB def
  373. go = do
  374. x <- CL.head
  375. case x of
  376. Nothing -> return Nothing
  377. Just [PersistText y] -> return $ Just y
  378. Just y -> error $ "Unexpected result from sqlite_master: " ++ show y
  379. -- | Mock a migration even when the database is not present.
  380. -- This function performs the same functionality of 'printMigration'
  381. -- with the difference that an actual database isn't needed for it.
  382. mockMigration :: Migration -> IO ()
  383. mockMigration mig = do
  384. smap <- newIORef $ Map.empty
  385. let sqlbackend = SqlBackend
  386. { connPrepare = \_ -> do
  387. return Statement
  388. { stmtFinalize = return ()
  389. , stmtReset = return ()
  390. , stmtExecute = undefined
  391. , stmtQuery = \_ -> return $ return ()
  392. }
  393. , connStmtMap = smap
  394. , connInsertSql = insertSql'
  395. , connInsertManySql = Nothing
  396. , connClose = undefined
  397. , connMigrateSql = migrate'
  398. , connBegin = \f _ -> helper "BEGIN" f
  399. , connCommit = helper "COMMIT"
  400. , connRollback = ignoreExceptions . helper "ROLLBACK"
  401. , connEscapeName = escape
  402. , connNoLimit = "LIMIT -1"
  403. , connRDBMS = "sqlite"
  404. , connLimitOffset = decorateSQLWithLimitOffset "LIMIT -1"
  405. , connLogFunc = undefined
  406. , connUpsertSql = undefined
  407. , connPutManySql = undefined
  408. , connMaxParams = Just 999
  409. , connRepsertManySql = Nothing
  410. , connInsertUniqueSql = Nothing
  411. }
  412. result = runReaderT . runWriterT . runWriterT $ mig
  413. resp <- result sqlbackend
  414. mapM_ TIO.putStrLn $ map snd $ snd resp
  415. where
  416. helper t getter = do
  417. stmt <- getter t
  418. _ <- stmtExecute stmt []
  419. stmtReset stmt
  420. ignoreExceptions = E.handle (\(_ :: E.SomeException) -> return ())
  421. -- | Check if a column name is listed as the "safe to remove" in the entity
  422. -- list.
  423. safeToRemove :: EntityDef -> DBName -> Bool
  424. safeToRemove def (DBName colName)
  425. = any (elem "SafeToRemove" . fieldAttrs)
  426. $ filter ((== DBName colName) . fieldDB)
  427. $ entityFields def
  428. getCopyTable :: [EntityDef]
  429. -> (Text -> IO Statement)
  430. -> EntityDef
  431. -> IO [(Bool, Text)]
  432. getCopyTable allDefs getter def = do
  433. stmt <- getter $ T.concat [ "PRAGMA table_info(", escape table, ")" ]
  434. oldCols' <- with (stmtQuery stmt []) (\src -> runConduit $ src .| getCols)
  435. let oldCols = map DBName $ filter (/= "id") oldCols' -- need to update for table id attribute ?
  436. let newCols = filter (not . safeToRemove def) $ map cName cols
  437. let common = filter (`elem` oldCols) newCols
  438. let id_ = fieldDB (entityId def)
  439. return [ (False, tmpSql)
  440. , (False, copyToTemp $ id_ : common)
  441. , (common /= filter (not . safeToRemove def) oldCols, dropOld)
  442. , (False, newSql)
  443. , (False, copyToFinal $ id_ : newCols)
  444. , (False, dropTmp)
  445. ]
  446. where
  447. getCols = do
  448. x <- CL.head
  449. case x of
  450. Nothing -> return []
  451. Just (_:PersistText name:_) -> do
  452. names <- getCols
  453. return $ name : names
  454. Just y -> error $ "Invalid result from PRAGMA table_info: " ++ show y
  455. table = entityDB def
  456. tableTmp = DBName $ unDBName table <> "_backup"
  457. (cols, uniqs, _) = mkColumns allDefs def
  458. cols' = filter (not . safeToRemove def . cName) cols
  459. newSql = mkCreateTable False def (cols', uniqs)
  460. tmpSql = mkCreateTable True def { entityDB = tableTmp } (cols', uniqs)
  461. dropTmp = "DROP TABLE " <> escape tableTmp
  462. dropOld = "DROP TABLE " <> escape table
  463. copyToTemp common = T.concat
  464. [ "INSERT INTO "
  465. , escape tableTmp
  466. , "("
  467. , T.intercalate "," $ map escape common
  468. , ") SELECT "
  469. , T.intercalate "," $ map escape common
  470. , " FROM "
  471. , escape table
  472. ]
  473. copyToFinal newCols = T.concat
  474. [ "INSERT INTO "
  475. , escape table
  476. , " SELECT "
  477. , T.intercalate "," $ map escape newCols
  478. , " FROM "
  479. , escape tableTmp
  480. ]
  481. mkCreateTable :: Bool -> EntityDef -> ([Column], [UniqueDef]) -> Text
  482. mkCreateTable isTemp entity (cols, uniqs) =
  483. case entityPrimary entity of
  484. Just pdef ->
  485. T.concat
  486. [ "CREATE"
  487. , if isTemp then " TEMP" else ""
  488. , " TABLE "
  489. , escape $ entityDB entity
  490. , "("
  491. , T.drop 1 $ T.concat $ map (sqlColumn isTemp) cols
  492. , ", PRIMARY KEY "
  493. , "("
  494. , T.intercalate "," $ map (escape . fieldDB) $ compositeFields pdef
  495. , ")"
  496. , ")"
  497. ]
  498. Nothing -> T.concat
  499. [ "CREATE"
  500. , if isTemp then " TEMP" else ""
  501. , " TABLE "
  502. , escape $ entityDB entity
  503. , "("
  504. , escape $ fieldDB (entityId entity)
  505. , " "
  506. , showSqlType $ fieldSqlType $ entityId entity
  507. ," PRIMARY KEY"
  508. , mayDefault $ defaultAttribute $ fieldAttrs $ entityId entity
  509. , T.concat $ map (sqlColumn isTemp) cols
  510. , T.concat $ map sqlUnique uniqs
  511. , ")"
  512. ]
  513. mayDefault :: Maybe Text -> Text
  514. mayDefault def = case def of
  515. Nothing -> ""
  516. Just d -> " DEFAULT " <> d
  517. sqlColumn :: Bool -> Column -> Text
  518. sqlColumn noRef (Column name isNull typ def _cn _maxLen ref) = T.concat
  519. [ ","
  520. , escape name
  521. , " "
  522. , showSqlType typ
  523. , if isNull then " NULL" else " NOT NULL"
  524. , mayDefault def
  525. , case ref of
  526. Nothing -> ""
  527. Just (table, _) -> if noRef then "" else " REFERENCES " <> escape table
  528. ]
  529. sqlUnique :: UniqueDef -> Text
  530. sqlUnique (UniqueDef _ cname cols _) = T.concat
  531. [ ",CONSTRAINT "
  532. , escape cname
  533. , " UNIQUE ("
  534. , T.intercalate "," $ map (escape . snd) cols
  535. , ")"
  536. ]
  537. escape :: DBName -> Text
  538. escape (DBName s) =
  539. T.concat [q, T.concatMap go s, q]
  540. where
  541. q = T.singleton '"'
  542. go '"' = "\"\""
  543. go c = T.singleton c
  544. putManySql :: EntityDef -> Int -> Text
  545. putManySql ent n = putManySql' conflictColumns fields ent n
  546. where
  547. fields = entityFields ent
  548. conflictColumns = concatMap (map (escape . snd) . uniqueFields) (entityUniques ent)
  549. repsertManySql :: EntityDef -> Int -> Text
  550. repsertManySql ent n = putManySql' conflictColumns fields ent n
  551. where
  552. fields = keyAndEntityFields ent
  553. conflictColumns = escape . fieldDB <$> entityKeyFields ent
  554. putManySql' :: [Text] -> [FieldDef] -> EntityDef -> Int -> Text
  555. putManySql' conflictColumns fields ent n = q
  556. where
  557. fieldDbToText = escape . fieldDB
  558. mkAssignment f = T.concat [f, "=EXCLUDED.", f]
  559. table = escape . entityDB $ ent
  560. columns = Util.commaSeparated $ map fieldDbToText fields
  561. placeholders = map (const "?") fields
  562. updates = map (mkAssignment . fieldDbToText) fields
  563. q = T.concat
  564. [ "INSERT INTO "
  565. , table
  566. , Util.parenWrapped columns
  567. , " VALUES "
  568. , Util.commaSeparated . replicate n
  569. . Util.parenWrapped . Util.commaSeparated $ placeholders
  570. , " ON CONFLICT "
  571. , Util.parenWrapped . Util.commaSeparated $ conflictColumns
  572. , " DO UPDATE SET "
  573. , Util.commaSeparated updates
  574. ]
  575. -- | Information required to setup a connection pool.
  576. data SqliteConf = SqliteConf
  577. { sqlDatabase :: Text
  578. , sqlPoolSize :: Int
  579. }
  580. | SqliteConfInfo
  581. { sqlConnInfo :: SqliteConnectionInfo
  582. , sqlPoolSize :: Int
  583. } deriving Show
  584. instance FromJSON SqliteConf where
  585. parseJSON v = modifyFailure ("Persistent: error loading Sqlite conf: " ++) $ flip (withObject "SqliteConf") v parser where
  586. parser o = if HashMap.member "database" o
  587. then SqliteConf
  588. <$> o .: "database"
  589. <*> o .: "poolsize"
  590. else SqliteConfInfo
  591. <$> o .: "connInfo"
  592. <*> o .: "poolsize"
  593. instance PersistConfig SqliteConf where
  594. type PersistConfigBackend SqliteConf = SqlPersistT
  595. type PersistConfigPool SqliteConf = ConnectionPool
  596. createPoolConfig (SqliteConf cs size) = runNoLoggingT $ createSqlitePoolFromInfo (conStringToInfo cs) size -- FIXME
  597. createPoolConfig (SqliteConfInfo info size) = runNoLoggingT $ createSqlitePoolFromInfo info size -- FIXME
  598. runPool _ = runSqlPool
  599. loadConfig = parseJSON
  600. finally :: MonadUnliftIO m
  601. => m a -- ^ computation to run first
  602. -> m b -- ^ computation to run afterward (even if an exception was raised)
  603. -> m a
  604. finally a sequel = withUnliftIO $ \u ->
  605. E.finally (unliftIO u a)
  606. (unliftIO u sequel)
  607. {-# INLINABLE finally #-}
  608. -- | Creates a SqliteConnectionInfo from a connection string, with the
  609. -- default settings.
  610. --
  611. -- @since 2.6.2
  612. mkSqliteConnectionInfo :: Text -> SqliteConnectionInfo
  613. mkSqliteConnectionInfo fp = SqliteConnectionInfo fp True True []
  614. -- | Parses connection options from a connection string. Used only to provide deprecated API.
  615. conStringToInfo :: Text -> SqliteConnectionInfo
  616. conStringToInfo connStr = SqliteConnectionInfo connStr' enableWal True [] where
  617. (connStr', enableWal) = case () of
  618. ()
  619. | Just cs <- T.stripPrefix "WAL=on " connStr -> (cs, True)
  620. | Just cs <- T.stripPrefix "WAL=off " connStr -> (cs, False)
  621. | otherwise -> (connStr, True)
  622. -- | Information required to connect to a sqlite database. We export
  623. -- lenses instead of fields to avoid being limited to the current
  624. -- implementation.
  625. --
  626. -- @since 2.6.2
  627. data SqliteConnectionInfo = SqliteConnectionInfo
  628. { _sqlConnectionStr :: Text -- ^ connection string for the database. Use @:memory:@ for an in-memory database.
  629. , _walEnabled :: Bool -- ^ if the write-ahead log is enabled - see https://github.com/yesodweb/persistent/issues/363.
  630. , _fkEnabled :: Bool -- ^ if foreign-key constraints are enabled.
  631. , _extraPragmas :: [Text] -- ^ additional pragmas to be set on initialization
  632. } deriving Show
  633. makeLenses ''SqliteConnectionInfo
  634. instance FromJSON SqliteConnectionInfo where
  635. parseJSON v = modifyFailure ("Persistent: error loading SqliteConnectionInfo: " ++) $
  636. flip (withObject "SqliteConnectionInfo") v $ \o -> SqliteConnectionInfo
  637. <$> o .: "connectionString"
  638. <*> o .: "walEnabled"
  639. <*> o .: "fkEnabled"
  640. <*> o .:? "extraPragmas" .!= []