sqlite-easy-0.2.0.1: A primitive yet easy to use sqlite library.
Safe HaskellSafe-Inferred
LanguageHaskell2010

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

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.

newtype ConnectionString Source #

A SQLite3 connection string

Constructors

ConnectionString 

data Database #

Instances

Instances details
Show Database 
Instance details

Defined in Database.SQLite3.Direct

Eq Database 
Instance details

Defined in Database.SQLite3.Direct

Driver Database Source # 
Instance details

Defined in Database.Sqlite.Easy.Migrant

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 Database and pass that around until you are ready to use the 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!

data Pool a #

createSqlitePool :: ConnectionString -> IO (Pool Database) Source #

Create a pool of a sqlite3 db with a specific connection string.

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 #

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)

run :: SQL -> SQLite [[SQLData]] Source #

Run a SQL statement on a database and fetch the results.

runWith :: SQL -> [SQLData] -> SQLite [[SQLData]] Source #

Run a SQL statement with certain parameters on a database and fetch the results.

data SQLite a Source #

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

Instances details
MonadFail SQLite Source # 
Instance details

Defined in Database.Sqlite.Easy.Internal

Methods

fail :: String -> SQLite a #

MonadIO SQLite Source # 
Instance details

Defined in Database.Sqlite.Easy.Internal

Methods

liftIO :: IO a -> SQLite a #

Applicative SQLite Source # 
Instance details

Defined in Database.Sqlite.Easy.Internal

Methods

pure :: a -> SQLite a #

(<*>) :: SQLite (a -> b) -> SQLite a -> SQLite b #

liftA2 :: (a -> b -> c) -> SQLite a -> SQLite b -> SQLite c #

(*>) :: SQLite a -> SQLite b -> SQLite b #

(<*) :: SQLite a -> SQLite b -> SQLite a #

Functor SQLite Source # 
Instance details

Defined in Database.Sqlite.Easy.Internal

Methods

fmap :: (a -> b) -> SQLite a -> SQLite b #

(<$) :: a -> SQLite b -> SQLite a #

Monad SQLite Source # 
Instance details

Defined in Database.Sqlite.Easy.Internal

Methods

(>>=) :: SQLite a -> (a -> SQLite b) -> SQLite b #

(>>) :: SQLite a -> SQLite b -> SQLite b #

return :: a -> SQLite a #

MonadUnliftIO SQLite Source # 
Instance details

Defined in Database.Sqlite.Easy.Internal

Methods

withRunInIO :: ((forall a. SQLite a -> IO a) -> IO b) -> SQLite b

Monoid a => Monoid (SQLite a) Source # 
Instance details

Defined in Database.Sqlite.Easy.Internal

Methods

mempty :: SQLite a #

mappend :: SQLite a -> SQLite a -> SQLite a #

mconcat :: [SQLite a] -> SQLite a #

Semigroup a => Semigroup (SQLite a) Source # 
Instance details

Defined in Database.Sqlite.Easy.Internal

Methods

(<>) :: SQLite a -> SQLite a -> SQLite a #

sconcat :: NonEmpty (SQLite a) -> SQLite a #

stimes :: Integral b => b -> SQLite a -> SQLite a #

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

Expand
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 liftIO, we would have ended up with this error:

• 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 IO a and returns an (m a): liftIO, enabling us to run the program and see the expected results:

> evalStateT printState "hello"
"hello"

> evalStateT printState 3
3

Database types

data SQL Source #

A SQL statement

Instances

Instances details
IsString SQL Source # 
Instance details

Defined in Database.Sqlite.Easy.Internal

Methods

fromString :: String -> SQL #

Semigroup SQL Source # 
Instance details

Defined in Database.Sqlite.Easy.Internal

Methods

(<>) :: SQL -> SQL -> SQL #

sconcat :: NonEmpty SQL -> SQL #

stimes :: Integral b => b -> SQL -> SQL #

Show SQL Source # 
Instance details

Defined in Database.Sqlite.Easy.Internal

Methods

showsPrec :: Int -> SQL -> ShowS #

show :: SQL -> String #

showList :: [SQL] -> ShowS #

data SQLData #

Instances

Instances details
Show SQLData 
Instance details

Defined in Database.SQLite3

Eq SQLData 
Instance details

Defined in Database.SQLite3

Methods

(==) :: SQLData -> SQLData -> Bool #

(/=) :: SQLData -> SQLData -> Bool #

data SQLError #

Constructors

SQLError 

Instances

Instances details
Exception SQLError 
Instance details

Defined in Database.SQLite3

Show SQLError 
Instance details

Defined in Database.SQLite3

Eq SQLError 
Instance details

Defined in Database.SQLite3

data ColumnType #

Instances

Instances details
Show ColumnType 
Instance details

Defined in Database.SQLite3.Bindings.Types

Eq ColumnType 
Instance details

Defined in Database.SQLite3.Bindings.Types

FFIType ColumnType CColumnType 
Instance details

Defined in Database.SQLite3.Bindings.Types

Methods

toFFI :: ColumnType -> CColumnType

fromFFI :: CColumnType -> ColumnType

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 :: forall a. 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

class Driver d where #

Methods

withTransaction :: (d -> IO a) -> d -> IO a #

initMigrations :: d -> IO () #

markUp :: MigrationName -> d -> IO () #

markDown :: MigrationName -> d -> IO () #

getMigrations :: d -> IO [MigrationName] #

data MigrationDirection #

Instances

Instances details
Bounded MigrationDirection 
Instance details

Defined in Database.Migrant.Run

Enum MigrationDirection 
Instance details

Defined in Database.Migrant.Run

Show MigrationDirection 
Instance details

Defined in Database.Migrant.Run

Eq MigrationDirection 
Instance details

Defined in Database.Migrant.Run

Ord MigrationDirection 
Instance details

Defined in Database.Migrant.Run

migrate :: [MigrationName] -> (MigrationName -> SQLite ()) -> (MigrationName -> SQLite ()) -> SQLite () Source #

Execute a migration against the database. A wrapper around migrant's migrate for SQLite.

void :: Functor f => f a -> f () #

void value discards or ignores the result of evaluation, such as the return value of an IO action.

Examples

Expand

Replace the contents of a Maybe Int with unit:

>>> void Nothing
Nothing
>>> void (Just 3)
Just ()

Replace the contents of an Either Int Int with unit, resulting in an 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

data Int64 #

64-bit signed integer type

Instances

Instances details
Bits Int64

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int64

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

Bounded Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Ix Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Num Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Read Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Integral Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int64 -> Rational #

Show Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int64 -> ShowS #

show :: Int64 -> String #

showList :: [Int64] -> ShowS #

Eq Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

(==) :: Int64 -> Int64 -> Bool #

(/=) :: Int64 -> Int64 -> Bool #

Ord Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

compare :: Int64 -> Int64 -> Ordering #

(<) :: Int64 -> Int64 -> Bool #

(<=) :: Int64 -> Int64 -> Bool #

(>) :: Int64 -> Int64 -> Bool #

(>=) :: Int64 -> Int64 -> Bool #

max :: Int64 -> Int64 -> Int64 #

min :: Int64 -> Int64 -> Int64 #

data Text #

A space efficient, packed, unboxed Unicode text type.

Instances

Instances details
type Item Text 
Instance details

Defined in Data.Text

type Item Text = Char

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

Instances details
Data ByteString 
Instance details

Defined in Data.ByteString.Internal

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: fromString truncates multi-byte characters to octets. e.g. "枯朶に烏のとまりけり秋の暮" becomes �6k�nh~�Q��n�

Instance details

Defined in Data.ByteString.Internal

Monoid ByteString 
Instance details

Defined in Data.ByteString.Internal

Semigroup ByteString 
Instance details

Defined in Data.ByteString.Internal

IsList ByteString

Since: bytestring-0.10.12.0

Instance details

Defined in Data.ByteString.Internal

Associated Types

type Item ByteString #

Read ByteString 
Instance details

Defined in Data.ByteString.Internal

Show ByteString 
Instance details

Defined in Data.ByteString.Internal

NFData ByteString 
Instance details

Defined in Data.ByteString.Internal

Methods

rnf :: ByteString -> () #

Eq ByteString 
Instance details

Defined in Data.ByteString.Internal

Ord ByteString 
Instance details

Defined in Data.ByteString.Internal

Lift ByteString

Since: bytestring-0.11.2.0

Instance details

Defined in Data.ByteString.Internal

Methods

lift :: Quote m => ByteString -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => ByteString -> Code m ByteString #

type Item ByteString 
Instance details

Defined in Data.ByteString.Internal

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:

  1. Create a resource pool with the database
  2. Run the database migrations
  3. 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