Safe Haskell | None |
---|---|
Language | Haskell2010 |
Database.Sqlite.Easy
Description
Easy to use interface for SQLite3 using the direct-sqlite
library.
This can be useful for your toy, hobby projects.
Synopsis
- withDb :: ConnectionString -> SQLite a -> IO a
- withDatabase :: Database -> SQLite a -> IO a
- openWith :: ConnectionString -> [SQL] -> IO Database
- newtype ConnectionString = ConnectionString {}
- data Database
- data Pool a
- createSqlitePool :: ConnectionString -> IO (Pool Database)
- createSqlitePoolWith :: ConnectionString -> [SQL] -> IO (Pool Database)
- withPool :: Pool Database -> SQLite a -> IO a
- withResource :: Pool a -> (a -> IO r) -> IO r
- destroyAllResources :: Pool a -> IO ()
- run :: SQL -> SQLite [[SQLData]]
- runWith :: SQL -> [SQLData] -> SQLite [[SQLData]]
- runWithMany :: SQL -> [[SQLData]] -> SQLite [[[SQLData]]]
- data SQLite a
- liftIO :: MonadIO m => IO a -> m a
- fromString :: IsString a => String -> a
- data SQL
- data SQLData
- = SQLInteger !Int64
- | SQLFloat !Double
- | SQLText !Text
- | SQLBlob !ByteString
- | SQLNull
- data SQLError = SQLError {
- sqlError :: !Error
- sqlErrorDetails :: Text
- sqlErrorContext :: Text
- data ColumnType
- transaction :: Typeable a => SQLite a -> SQLite a
- rollback :: Typeable a => a -> SQLite a
- rollbackAll :: Typeable a => a -> SQLite a
- module Database.Sqlite.Easy.Migrant
- data MigrationName
- data MigrationDirection
- plan :: Driver d => [MigrationName] -> d -> IO [(MigrationDirection, MigrationName)]
- void :: Functor f => f a -> f ()
- data Int64
- data Text
- data ByteString
Connect to the database
The easiest way to run some statements on the database is using the
withDb
function. withDb
expects a connection string
(such as a file with flags or :memory:
, see sqlite3 docs:
https://www.sqlite.org/c3ref/open.html), and SQLite action(s),
such as queries and statements.
It will open the connection to the database and run the SQLite actions
on that database.
Example
do results <- withDb ":memory:" (run "select 1 + 1") case results of [[SQLInteger n]] -> print n _ -> error ("Got unexpected results: " <> show results)
Note: use fromString
to convert a String
to a ConnectionString
or to SQL
if you prefer not to use OverloadedStrings
.
withDb :: ConnectionString -> SQLite a -> IO a Source #
Open a database, run some stuff, close the database.
withDatabase :: Database -> SQLite a -> IO a Source #
Use an active database connection to run some stuff on a database.
openWith :: ConnectionString -> [SQL] -> IO Database Source #
Open a connection to a database, run the supplied statements, and return the connection.
newtype ConnectionString Source #
A SQLite3 connection string
Constructors
ConnectionString | |
Fields |
Instances
IsString ConnectionString Source # | |
Defined in Database.Sqlite.Easy.Internal Methods fromString :: String -> ConnectionString # | |
Show ConnectionString Source # | |
Defined in Database.Sqlite.Easy.Internal Methods showsPrec :: Int -> ConnectionString -> ShowS # show :: ConnectionString -> String # showList :: [ConnectionString] -> ShowS # |
Instances
Show Database | |
Eq Database | |
Driver Database Source # | |
Defined in Database.Sqlite.Easy.Migrant Methods withTransaction :: (Database -> IO a) -> Database -> IO a # initMigrations :: Database -> IO () # markUp :: MigrationName -> Database -> IO () # markDown :: MigrationName -> Database -> IO () # getMigrations :: Database -> IO [MigrationName] # |
Pooling connections
An alternative to withDb
is to create a resource Pool
.
A resource pool is an abstraction for automatically managing connections
to a resource (such as a database).
We can use the createSqlitePool
function to create a Pool
and pass that around until you are ready to use the database.Database
We can use withPool
like we did with withDb
but passing a Pool Database
instead of a ConnectionString
.
Example
do pool <- createSqlitePool ":memory:" results <- withPool pool (run "select 1 + 1") case results of [[SQLInteger n]] -> print n _ -> error ("Got unexpected results: " <> show results)
Note: a resource pool disconnects automatically after some time,
so if you are using :memory:
as your database, you will lose your
data when the connection closes!
Striped resource pool based on Control.Concurrent.QSem.
createSqlitePool :: ConnectionString -> IO (Pool Database) Source #
Create a pool of a sqlite3 db with a specific connection string. This also sets a few default pragmas.
createSqlitePoolWith :: ConnectionString -> [SQL] -> IO (Pool Database) Source #
Create a pool of a sqlite3 db with a specific connection string. This will also run the supplied SQL statements after establishing each connection.
withPool :: Pool Database -> SQLite a -> IO a Source #
Use a resource pool to run some stuff on a database.
withResource :: Pool a -> (a -> IO r) -> IO r #
Take a resource from the pool, perform an action with it and return it to the pool afterwards.
- If the pool has an idle resource available, it is used immediately.
- Otherwise, if the maximum number of resources has not yet been reached, a new resource is created and used.
- If the maximum number of resources has been reached, this function blocks until a resource becomes available.
If the action throws an exception of any type, the resource is destroyed and not returned to the pool.
It probably goes without saying that you should never manually destroy a pooled resource, as doing so will almost certainly cause a subsequent user (who expects the resource to be valid) to throw an exception.
destroyAllResources :: Pool a -> IO () #
Destroy all resources in all stripes in the pool.
Note that this will ignore any exceptions in the destroy function.
This function is useful when you detect that all resources in the pool are
broken. For example after a database has been restarted all connections
opened before the restart will be broken. In that case it's better to close
those connections so that takeResource
won't take a broken connection from
the pool but will open a new connection instead.
Another use-case for this function is that when you know you are done with the pool you can destroy all idle resources immediately instead of waiting on the garbage collector to destroy them, thus freeing up those resources sooner.
Running statements and queries
To execute a statement or query, use the run
or runWith
functions.
run
is used to execute a statement or query and fetch the results.
runWith
is similar to run
, but lets us place parameters instead of
places where we write ?
in the query.
If you want to pass user data, use runWith
to avoid SQL injection!
The list of lists of SQLData returned from these functions are
rows of columns of sqlite values. Sqlite only has a few possible
values: integers, floating-point numbers, text, bytes and null.
The SQLData
type encodes these options.
Example
do results <- withDb ":memory:" $ do [] <- run "CREATE TABLE characters(id INTEGER PRIMARY KEY AUTOINCREMENT, name TEXT)" [] <- run "INSERT INTO characters(name) VALUES ('Scanlan'),('Nott'),('Fresh Cut Grass')" runWith "SELECT * FROM characters WHERE id = ?" [SQLInteger 2] for_ results $ \case [SQLInteger id', SQLText name] -> putStrLn (show id' <> ", " <> show name) row -> hPutStrLn stderr ("Unexpected row: " <> show row)
runWith :: SQL -> [SQLData] -> SQLite [[SQLData]] Source #
Run a SQL statement with certain parameters on a database and fetch the results.
runWithMany :: SQL -> [[SQLData]] -> SQLite [[[SQLData]]] Source #
Run a SQL statement binding it to all given parameter rows and fetch all of the data. This can significantly improve speed for cases like bulk INSERTs.
Since: 1.1.1.0
The type of actions to run on a SQLite database.
In essence, it is almost the same as Database -> IO a
.
SQLite
actions can be created with the run
and runWith
functions, and can be composed using the type class instances.
SQLite
actions can be run with the withDb
, withDatabase
,
and withPool
functions.
Instances
MonadFail SQLite Source # | |
Defined in Database.Sqlite.Easy.Internal | |
MonadIO SQLite Source # | |
Defined in Database.Sqlite.Easy.Internal | |
Applicative SQLite Source # | |
Functor SQLite Source # | |
Monad SQLite Source # | |
MonadUnliftIO SQLite Source # | |
Defined in Database.Sqlite.Easy.Internal | |
Monoid a => Monoid (SQLite a) Source # | |
Semigroup a => Semigroup (SQLite a) Source # | |
liftIO :: MonadIO m => IO a -> m a #
Lift a computation from the IO
monad.
This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations
(i.e. IO
is the base monad for the stack).
Example
import Control.Monad.Trans.State -- from the "transformers" library printState :: Show s => StateT s IO () printState = do state <- get liftIO $ print state
Had we omitted
, we would have ended up with this error:liftIO
• Couldn't match type ‘IO’ with ‘StateT s IO’ Expected type: StateT s IO () Actual type: IO ()
The important part here is the mismatch between StateT s IO ()
and
.IO
()
Luckily, we know of a function that takes an
and returns an IO
a(m a)
:
,
enabling us to run the program and see the expected results:liftIO
> evalStateT printState "hello" "hello" > evalStateT printState 3 3
fromString :: IsString a => String -> a #
Database types
A SQL statement
Constructors
SQLInteger !Int64 | |
SQLFloat !Double | |
SQLText !Text | |
SQLBlob !ByteString | |
SQLNull |
Instances
Exception thrown when SQLite3 reports an error.
direct-sqlite may throw other types of exceptions if you misuse the API.
Constructors
SQLError | |
Fields
|
Instances
Exception SQLError | |||||
Defined in Database.SQLite3 Methods toException :: SQLError -> SomeException # fromException :: SomeException -> Maybe SQLError # displayException :: SQLError -> String # | |||||
Generic SQLError | |||||
Defined in Database.SQLite3 Associated Types
| |||||
Show SQLError | |||||
Eq SQLError | |||||
type Rep SQLError | |||||
Defined in Database.SQLite3 type Rep SQLError = D1 ('MetaData "SQLError" "Database.SQLite3" "direct-sqlite-2.3.29-293e1cab54a2eb41da583f03d5c78ee91f2c67007601fc46a05193129b1ad1db" 'False) (C1 ('MetaCons "SQLError" 'PrefixI 'True) (S1 ('MetaSel ('Just "sqlError") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Error) :*: (S1 ('MetaSel ('Just "sqlErrorDetails") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "sqlErrorContext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))) |
data ColumnType #
Constructors
IntegerColumn | |
FloatColumn | |
TextColumn | |
BlobColumn | |
NullColumn |
Instances
Show ColumnType | |
Defined in Database.SQLite3.Bindings.Types Methods showsPrec :: Int -> ColumnType -> ShowS # show :: ColumnType -> String # showList :: [ColumnType] -> ShowS # | |
Eq ColumnType | |
Defined in Database.SQLite3.Bindings.Types | |
FFIType ColumnType CColumnType | |
Defined in Database.SQLite3.Bindings.Types |
Running transactions
If you'd like to run multiple statements and queries atomically, use transaction
.
Example
withDb ":memory:" $ do ( transaction $ do [] <- run "CREATE TABLE t1(id INTEGER, name TEXT)" [] <- run "CREATE TABLE t2(id INTEGER, name TEXT)" [] <- run "CREATE TABLE t3id INTEGER, name TEXT)" -- whoops [] <- run "CREATE TABLE t4(id INTEGER, name TEXT)" pure () ) `catch` (\(SomeException e) -> liftIO $ print ("Transaction rolled back", e)) run "select * from t1" -- throws an exception (table not found) because the transaction was rolled back
You can also decide to rollback the current transaction yourself by supplying the result value
with rollback
, or rollback all transactions with rollbackAll
.
Note, catching an exception from within SQLite
as was done in the previous
snippet is not recommended because it can mix with rollback code,
but it can be done using the unliftio
package.
transaction :: Typeable a => SQLite a -> SQLite a Source #
Run operations as a transaction. If the action throws an error, the transaction is rolled back. For more information, visit: https://www.sqlite.org/lang_transaction.html
rollback :: Typeable a => a -> SQLite a Source #
Rollback the current (inner-most) transaction by supplying the return value. To be used inside transactions.
rollbackAll :: Typeable a => a -> SQLite a Source #
Rollback all transaction structure by supplying the return value. To be used inside transactions.
Migrations
Database migrations are a way to setup a database with the relevant information (such as table structure) needed for the application to start, and update it from a possible older version to a newer version (or even go the other direction).
Migrations are a list of statements we run in order to upgrade or downgrade a database.
We use the migrant
library to semi-automate this process - we write the upgrade
and downgrade steps, and it runs them. For more information, consult the migrant
documentation: https://github.com/tdammers/migrant.
To create a migration we need to write the following things:
1) A list of migration names
migrations :: [MigrationName] migrations = [ "user-table" , "article-table" ]
2) Migration up steps - a mapping from migration name to what to do.
migrateUp :: MigrationName -> SQLite () migrateUp = \case "user-table" -> void (run "CREATE TABLE user(id INTEGER, name TEXT)") "article-table" -> void (run "CREATE TABLE article(id integer, title TEXT, content TEXT, author_id integer)") unknown -> error ("Unexpected migration: " <> show unknown)
3) Migration down steps
migrateDown :: MigrationName -> SQLite () migrateDown = \case "user-table" -> void (run "DROP TABLE user") "article-table" -> void (run "DROP TABLE article") unknown -> error ("Unexpected migration: " <> show unknown)
After doing that, we can run a migration with the migrate
function:
runMigrations :: SQLite () runMigrations = migrate migrations migrateUp migrateDown
module Database.Sqlite.Easy.Migrant
data MigrationName #
Instances
IsString MigrationName | |
Defined in Database.Migrant.MigrationName Methods fromString :: String -> MigrationName # | |
Show MigrationName | |
Defined in Database.Migrant.MigrationName Methods showsPrec :: Int -> MigrationName -> ShowS # show :: MigrationName -> String # showList :: [MigrationName] -> ShowS # | |
PrintfArg MigrationName | |
Defined in Database.Migrant.MigrationName Methods | |
Eq MigrationName | |
Defined in Database.Migrant.MigrationName Methods (==) :: MigrationName -> MigrationName -> Bool # (/=) :: MigrationName -> MigrationName -> Bool # |
data MigrationDirection #
Instances
Bounded MigrationDirection | |
Defined in Database.Migrant.Run | |
Enum MigrationDirection | |
Defined in Database.Migrant.Run Methods succ :: MigrationDirection -> MigrationDirection # pred :: MigrationDirection -> MigrationDirection # toEnum :: Int -> MigrationDirection # fromEnum :: MigrationDirection -> Int # enumFrom :: MigrationDirection -> [MigrationDirection] # enumFromThen :: MigrationDirection -> MigrationDirection -> [MigrationDirection] # enumFromTo :: MigrationDirection -> MigrationDirection -> [MigrationDirection] # enumFromThenTo :: MigrationDirection -> MigrationDirection -> MigrationDirection -> [MigrationDirection] # | |
Show MigrationDirection | |
Defined in Database.Migrant.Run Methods showsPrec :: Int -> MigrationDirection -> ShowS # show :: MigrationDirection -> String # showList :: [MigrationDirection] -> ShowS # | |
Eq MigrationDirection | |
Defined in Database.Migrant.Run Methods (==) :: MigrationDirection -> MigrationDirection -> Bool # (/=) :: MigrationDirection -> MigrationDirection -> Bool # | |
Ord MigrationDirection | |
Defined in Database.Migrant.Run Methods compare :: MigrationDirection -> MigrationDirection -> Ordering # (<) :: MigrationDirection -> MigrationDirection -> Bool # (<=) :: MigrationDirection -> MigrationDirection -> Bool # (>) :: MigrationDirection -> MigrationDirection -> Bool # (>=) :: MigrationDirection -> MigrationDirection -> Bool # max :: MigrationDirection -> MigrationDirection -> MigrationDirection # min :: MigrationDirection -> MigrationDirection -> MigrationDirection # |
plan :: Driver d => [MigrationName] -> d -> IO [(MigrationDirection, MigrationName)] #
Create a migration plan based on the current situation on the database, and the specified target.
void :: Functor f => f a -> f () #
discards or ignores the result of evaluation, such
as the return value of an void
valueIO
action.
Examples
Replace the contents of a
with unit:Maybe
Int
>>>
void Nothing
Nothing>>>
void (Just 3)
Just ()
Replace the contents of an
with unit, resulting in an Either
Int
Int
:Either
Int
()
>>>
void (Left 8675309)
Left 8675309>>>
void (Right 8675309)
Right ()
Replace every element of a list with unit:
>>>
void [1,2,3]
[(),(),()]
Replace the second element of a pair with unit:
>>>
void (1,2)
(1,())
Discard the result of an IO
action:
>>>
mapM print [1,2]
1 2 [(),()]>>>
void $ mapM print [1,2]
1 2
Fun types to export
64-bit signed integer type
Instances
Data Int64 | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int64 -> c Int64 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int64 # dataTypeOf :: Int64 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int64) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int64) # gmapT :: (forall b. Data b => b -> b) -> Int64 -> Int64 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int64 -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int64 -> r # gmapQ :: (forall d. Data d => d -> u) -> Int64 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Int64 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 # | |
Storable Int64 | Since: base-2.1 |
Bits Int64 | Since: base-2.1 |
Defined in GHC.Int Methods (.&.) :: Int64 -> Int64 -> Int64 # (.|.) :: Int64 -> Int64 -> Int64 # xor :: Int64 -> Int64 -> Int64 # complement :: Int64 -> Int64 # shift :: Int64 -> Int -> Int64 # rotate :: Int64 -> Int -> Int64 # setBit :: Int64 -> Int -> Int64 # clearBit :: Int64 -> Int -> Int64 # complementBit :: Int64 -> Int -> Int64 # testBit :: Int64 -> Int -> Bool # bitSizeMaybe :: Int64 -> Maybe Int # shiftL :: Int64 -> Int -> Int64 # unsafeShiftL :: Int64 -> Int -> Int64 # shiftR :: Int64 -> Int -> Int64 # unsafeShiftR :: Int64 -> Int -> Int64 # rotateL :: Int64 -> Int -> Int64 # | |
FiniteBits Int64 | Since: base-4.6.0.0 |
Defined in GHC.Int Methods finiteBitSize :: Int64 -> Int # countLeadingZeros :: Int64 -> Int # countTrailingZeros :: Int64 -> Int # | |
Bounded Int64 | Since: base-2.1 |
Enum Int64 | Since: base-2.1 |
Ix Int64 | Since: base-2.1 |
Num Int64 | Since: base-2.1 |
Read Int64 | Since: base-2.1 |
Integral Int64 | Since: base-2.1 |
Real Int64 | Since: base-2.1 |
Defined in GHC.Int Methods toRational :: Int64 -> Rational # | |
Show Int64 | Since: base-2.1 |
PrintfArg Int64 | Since: base-2.1 |
Defined in Text.Printf | |
NFData Int64 | |
Defined in Control.DeepSeq | |
Eq Int64 | Since: base-2.1 |
Ord Int64 | Since: base-2.1 |
Hashable Int64 | |
Defined in Data.Hashable.Class | |
Lift Int64 | |
A space efficient, packed, unboxed Unicode text type.
data ByteString #
A space-efficient representation of a Word8
vector, supporting many
efficient operations.
A ByteString
contains 8-bit bytes, or by using the operations from
Data.ByteString.Char8 it can be interpreted as containing 8-bit
characters.
Instances
Data ByteString | |||||
Defined in Data.ByteString.Internal.Type Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ByteString -> c ByteString # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteString # toConstr :: ByteString -> Constr # dataTypeOf :: ByteString -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ByteString) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteString) # gmapT :: (forall b. Data b => b -> b) -> ByteString -> ByteString # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r # gmapQ :: (forall d. Data d => d -> u) -> ByteString -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ByteString -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString # | |||||
IsString ByteString | Beware: | ||||
Defined in Data.ByteString.Internal.Type Methods fromString :: String -> ByteString # | |||||
Monoid ByteString | |||||
Defined in Data.ByteString.Internal.Type Methods mempty :: ByteString # mappend :: ByteString -> ByteString -> ByteString # mconcat :: [ByteString] -> ByteString # | |||||
Semigroup ByteString | |||||
Defined in Data.ByteString.Internal.Type Methods (<>) :: ByteString -> ByteString -> ByteString # sconcat :: NonEmpty ByteString -> ByteString # stimes :: Integral b => b -> ByteString -> ByteString # | |||||
IsList ByteString | Since: bytestring-0.10.12.0 | ||||
Defined in Data.ByteString.Internal.Type Associated Types
Methods fromList :: [Item ByteString] -> ByteString # fromListN :: Int -> [Item ByteString] -> ByteString # toList :: ByteString -> [Item ByteString] # | |||||
Read ByteString | |||||
Defined in Data.ByteString.Internal.Type Methods readsPrec :: Int -> ReadS ByteString # readList :: ReadS [ByteString] # readPrec :: ReadPrec ByteString # readListPrec :: ReadPrec [ByteString] # | |||||
Show ByteString | |||||
Defined in Data.ByteString.Internal.Type Methods showsPrec :: Int -> ByteString -> ShowS # show :: ByteString -> String # showList :: [ByteString] -> ShowS # | |||||
NFData ByteString | |||||
Defined in Data.ByteString.Internal.Type Methods rnf :: ByteString -> () # | |||||
Eq ByteString | |||||
Defined in Data.ByteString.Internal.Type | |||||
Ord ByteString | |||||
Defined in Data.ByteString.Internal.Type Methods compare :: ByteString -> ByteString -> Ordering # (<) :: ByteString -> ByteString -> Bool # (<=) :: ByteString -> ByteString -> Bool # (>) :: ByteString -> ByteString -> Bool # (>=) :: ByteString -> ByteString -> Bool # max :: ByteString -> ByteString -> ByteString # min :: ByteString -> ByteString -> ByteString # | |||||
Hashable ByteString | |||||
Defined in Data.Hashable.Class | |||||
Lift ByteString | Since: bytestring-0.11.2.0 | ||||
Defined in Data.ByteString.Internal.Type Methods lift :: Quote m => ByteString -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => ByteString -> Code m ByteString # | |||||
type Item ByteString | |||||
Defined in Data.ByteString.Internal.Type |
Suggestions
A suggestion for the architecture of your database interactions: use the handle pattern!
1. Create a type for your API
Think about what actions you want to perform on your database:
For example:
data DB = DB { getPost :: Id -> IO (Id, Post) , getPosts :: IO [(Id, Post)] , insertPost :: Post -> IO Id , deletePostById :: Id -> IO () }
Note how we don't mention the database connection here!
2. Create a smart constructor
This function should:
- Create a resource pool with the database
- Run the database migrations
- Return a
DB
such that each function in the API is a closure over the pool
For example:
mkDB :: ConnectionString -> IO DB mkDB connectionString = do pool <- createSqlitePool connectionString withPool pool runMigrations pure $ DB { getPost = withPool pool . getPostFromDb , getPosts = withPool pool getPostsFromDb , insertPost = withPool pool . insertPostToDb , deletePostById = withPool pool . deletePostByIdFromDb }
Where:
getPostFromDb :: Id -> SQLite (Id, Post)
insertPostToDb :: Post -> SQLite Id
and so on.
3. Use the handle from your application code
When you start the application, run mkDB
and get a handle, and pass it around
(or use ReaderT
). When you need to run a database command, call a field from DB
:
-- A page for a specific post [ Twain.get "/post/:id" $ do postId <- Twain.param "id" post <- liftIO $ getPost db postId -- (*) Twain.send (displayPost post) ]
Or, with OverloadedRecordDot
,
post <- liftIO $ db.getPost postId
Complete Example
Visit this link for a more complete example: https://github.com/soupi/sqlite-easy-example-todo