persistent-sqlite-2.13.1.1: Backend for the persistent library using sqlite3.
Safe Haskell None
Language Haskell2010

Database.Persist.Sqlite

Description

A sqlite backend for persistent.

Note: If you prepend WAL=off to your connection string, it will disable the write-ahead log. This functionality is now deprecated in favour of using SqliteConnectionInfo.

Synopsis

Documentation

withSqlitePool Source #

Arguments

:: ( MonadUnliftIO m, MonadLoggerIO m)
=> Text
-> Int

number of connections to open

-> ( Pool SqlBackend -> m a)
-> m a

Run the given action with a connection pool.

Like createSqlitePool , this should not be used with :memory: .

withSqlitePoolInfo Source #

Arguments

:: ( MonadUnliftIO m, MonadLoggerIO m)
=> SqliteConnectionInfo
-> Int

number of connections to open

-> ( Pool SqlBackend -> m a)
-> m a

Run the given action with a connection pool.

Like createSqlitePool , this should not be used with :memory: .

Since: 2.6.2

createSqlitePool :: ( MonadLoggerIO m, MonadUnliftIO m) => Text -> Int -> m ( Pool SqlBackend ) Source #

Create a pool of SQLite connections.

Note that this should not be used with the :memory: connection string, as the pool will regularly remove connections, destroying your database. Instead, use withSqliteConn .

createSqlitePoolFromInfo :: ( MonadLoggerIO m, MonadUnliftIO m) => SqliteConnectionInfo -> Int -> m ( Pool SqlBackend ) Source #

Create a pool of SQLite connections.

Note that this should not be used with the :memory: connection string, as the pool will regularly remove connections, destroying your database. Instead, use withSqliteConn .

Since: 2.6.2

mkSqliteConnectionInfo :: Text -> SqliteConnectionInfo Source #

Creates a SqliteConnectionInfo from a connection string, with the default settings.

Since: 2.6.2

runSqlite Source #

Arguments

:: MonadUnliftIO m
=> Text

connection string

-> ReaderT SqlBackend ( NoLoggingT ( ResourceT m)) a

database action

-> m a

A convenience helper which creates a new database connection and runs the given block, handling MonadResource and MonadLogger requirements. Note that all log messages are discarded.

Since: 1.1.4

runSqliteInfo Source #

A convenience helper which creates a new database connection and runs the given block, handling MonadResource and MonadLogger requirements. Note that all log messages are discarded.

Since: 2.6.2

wrapConnection :: Connection -> LogFunc -> IO SqlBackend Source #

Wrap up a raw Connection as a Persistent SQL Connection .

Example usage

Expand
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}

import Control.Monad.IO.Class  (liftIO)
import Database.Persist
import Database.Sqlite
import Database.Persist.Sqlite
import Database.Persist.TH

share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase|
Person
  name String
  age Int Maybe
  deriving Show
|]

main :: IO ()
main = do
  conn <- open "/home/sibi/test.db"
  (backend :: SqlBackend) <- wrapConnection conn (\_ _ _ _ -> return ())
  flip runSqlPersistM backend $ do
         runMigration migrateAll
         insert_ $ Person "John doe" $ Just 35
         insert_ $ Person "Hema" $ Just 36
         (pers :: [Entity Person]) <- selectList [] []
         liftIO $ print pers
  close' backend

On executing it, you get this output:

Migrating: CREATE TABLE "person"("id" INTEGER PRIMARY KEY,"name" VARCHAR NOT NULL,"age" INTEGER NULL)
[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}}]

Since: 1.1.5

wrapConnectionInfo :: SqliteConnectionInfo -> Connection -> LogFunc -> IO SqlBackend Source #

Wrap up a raw Connection as a Persistent SQL Connection , allowing full control over WAL and FK constraints.

Since: 2.6.2

mockMigration :: Migration -> IO () Source #

Mock a migration even when the database is not present. This function performs the same functionality of printMigration with the difference that an actual database isn't needed for it.

retryOnBusy :: ( MonadUnliftIO m, MonadLoggerIO m) => m a -> m a Source #

Retry if a Busy is thrown, following an exponential backoff strategy.

Since: 2.9.3

waitForDatabase :: ( MonadUnliftIO m, MonadLoggerIO m, BackendCompatible SqlBackend backend) => ReaderT backend m () Source #

Wait until some noop action on the database does not return an ErrorBusy . See retryOnBusy .

Since: 2.9.3

checkForeignKeys :: ( MonadResource m, MonadReader env m, BackendCompatible SqlBackend env) => ConduitM () ForeignKeyViolation m () Source #

Outputs all (if any) the violated foreign key constraints in the database.

The main use is to validate that no foreign key constraints were broken/corrupted by anyone operating on the database with foreign keys disabled. See fkEnabled .

Since: 2.11.1

data RawSqlite backend Source #

Wrapper for persistent SqlBackends that carry the corresponding Connection .

Since: 2.10.2

Instances

Instances details
BackendCompatible b ( RawSqlite b) Source #
Instance details

Defined in Database.Persist.Sqlite

( PersistCore b, PersistCore ( RawSqlite b), Bounded ( BackendKey b)) => Bounded ( BackendKey ( RawSqlite b)) Source #
Instance details

Defined in Database.Persist.Sqlite

( PersistCore b, PersistCore ( RawSqlite b), Enum ( BackendKey b)) => Enum ( BackendKey ( RawSqlite b)) Source #
Instance details

Defined in Database.Persist.Sqlite

( PersistCore b, PersistCore ( RawSqlite b), Eq ( BackendKey b)) => Eq ( BackendKey ( RawSqlite b)) Source #
Instance details

Defined in Database.Persist.Sqlite

( PersistCore b, PersistCore ( RawSqlite b), Integral ( BackendKey b)) => Integral ( BackendKey ( RawSqlite b)) Source #
Instance details

Defined in Database.Persist.Sqlite

( PersistCore b, PersistCore ( RawSqlite b), Num ( BackendKey b)) => Num ( BackendKey ( RawSqlite b)) Source #
Instance details

Defined in Database.Persist.Sqlite

( PersistCore b, PersistCore ( RawSqlite b), Ord ( BackendKey b)) => Ord ( BackendKey ( RawSqlite b)) Source #
Instance details

Defined in Database.Persist.Sqlite

( PersistCore b, PersistCore ( RawSqlite b), Read ( BackendKey b)) => Read ( BackendKey ( RawSqlite b)) Source #
Instance details

Defined in Database.Persist.Sqlite

( PersistCore b, PersistCore ( RawSqlite b), Real ( BackendKey b)) => Real ( BackendKey ( RawSqlite b)) Source #
Instance details

Defined in Database.Persist.Sqlite

( PersistCore b, PersistCore ( RawSqlite b), Show ( BackendKey b)) => Show ( BackendKey ( RawSqlite b)) Source #
Instance details

Defined in Database.Persist.Sqlite

( PersistCore b, PersistCore ( RawSqlite b), ToJSON ( BackendKey b)) => ToJSON ( BackendKey ( RawSqlite b)) Source #
Instance details

Defined in Database.Persist.Sqlite

( PersistCore b, PersistCore ( RawSqlite b), FromJSON ( BackendKey b)) => FromJSON ( BackendKey ( RawSqlite b)) Source #
Instance details

Defined in Database.Persist.Sqlite

( PersistCore b, PersistCore ( RawSqlite b), PersistFieldSql ( BackendKey b)) => PersistFieldSql ( BackendKey ( RawSqlite b)) Source #
Instance details

Defined in Database.Persist.Sqlite

( HasPersistBackend b, PersistQueryRead b) => PersistQueryRead ( RawSqlite b) Source #
Instance details

Defined in Database.Persist.Sqlite

( HasPersistBackend b, PersistQueryWrite b) => PersistQueryWrite ( RawSqlite b) Source #
Instance details

Defined in Database.Persist.Sqlite

( HasPersistBackend b, PersistUniqueRead b) => PersistUniqueRead ( RawSqlite b) Source #
Instance details

Defined in Database.Persist.Sqlite

( HasPersistBackend b, PersistUniqueWrite b) => PersistUniqueWrite ( RawSqlite b) Source #
Instance details

Defined in Database.Persist.Sqlite

Methods

deleteBy :: forall record (m :: Type -> Type ). ( MonadIO m, PersistRecordBackend record ( RawSqlite b)) => Unique record -> ReaderT ( RawSqlite b) m () Source #

insertUnique :: forall record (m :: Type -> Type ). ( MonadIO m, PersistRecordBackend record ( RawSqlite b)) => record -> ReaderT ( RawSqlite b) m ( Maybe ( Key record)) Source #

upsert :: forall record (m :: Type -> Type ). ( MonadIO m, PersistRecordBackend record ( RawSqlite b), OnlyOneUniqueKey record) => record -> [ Update record] -> ReaderT ( RawSqlite b) m ( Entity record) Source #

upsertBy :: forall record (m :: Type -> Type ). ( MonadIO m, PersistRecordBackend record ( RawSqlite b)) => Unique record -> record -> [ Update record] -> ReaderT ( RawSqlite b) m ( Entity record) Source #

putMany :: forall record (m :: Type -> Type ). ( MonadIO m, PersistRecordBackend record ( RawSqlite b)) => [record] -> ReaderT ( RawSqlite b) m () Source #

HasPersistBackend b => HasPersistBackend ( RawSqlite b) Source #
Instance details

Defined in Database.Persist.Sqlite

Associated Types

type BaseBackend ( RawSqlite b) Source #

PersistCore b => PersistCore ( RawSqlite b) Source #
Instance details

Defined in Database.Persist.Sqlite

Associated Types

data BackendKey ( RawSqlite b) Source #

( HasPersistBackend b, PersistStoreRead b) => PersistStoreRead ( RawSqlite b) Source #
Instance details

Defined in Database.Persist.Sqlite

Methods

get :: forall record (m :: Type -> Type ). ( MonadIO m, PersistRecordBackend record ( RawSqlite b)) => Key record -> ReaderT ( RawSqlite b) m ( Maybe record) Source #

getMany :: forall record (m :: Type -> Type ). ( MonadIO m, PersistRecordBackend record ( RawSqlite b)) => [ Key record] -> ReaderT ( RawSqlite b) m ( Map ( Key record) record) Source #

( HasPersistBackend b, PersistStoreWrite b) => PersistStoreWrite ( RawSqlite b) Source #
Instance details

Defined in Database.Persist.Sqlite

Methods

insert :: forall record (m :: Type -> Type ). ( MonadIO m, PersistRecordBackend record ( RawSqlite b)) => record -> ReaderT ( RawSqlite b) m ( Key record) Source #

insert_ :: forall record (m :: Type -> Type ). ( MonadIO m, PersistRecordBackend record ( RawSqlite b)) => record -> ReaderT ( RawSqlite b) m () Source #

insertMany :: forall record (m :: Type -> Type ). ( MonadIO m, PersistRecordBackend record ( RawSqlite b)) => [record] -> ReaderT ( RawSqlite b) m [ Key record] Source #

insertMany_ :: forall record (m :: Type -> Type ). ( MonadIO m, PersistRecordBackend record ( RawSqlite b)) => [record] -> ReaderT ( RawSqlite b) m () Source #

insertEntityMany :: forall record (m :: Type -> Type ). ( MonadIO m, PersistRecordBackend record ( RawSqlite b)) => [ Entity record] -> ReaderT ( RawSqlite b) m () Source #

insertKey :: forall record (m :: Type -> Type ). ( MonadIO m, PersistRecordBackend record ( RawSqlite b)) => Key record -> record -> ReaderT ( RawSqlite b) m () Source #

repsert :: forall record (m :: Type -> Type ). ( MonadIO m, PersistRecordBackend record ( RawSqlite b)) => Key record -> record -> ReaderT ( RawSqlite b) m () Source #

repsertMany :: forall record (m :: Type -> Type ). ( MonadIO m, PersistRecordBackend record ( RawSqlite b)) => [( Key record, record)] -> ReaderT ( RawSqlite b) m () Source #

replace :: forall record (m :: Type -> Type ). ( MonadIO m, PersistRecordBackend record ( RawSqlite b)) => Key record -> record -> ReaderT ( RawSqlite b) m () Source #

delete :: forall record (m :: Type -> Type ). ( MonadIO m, PersistRecordBackend record ( RawSqlite b)) => Key record -> ReaderT ( RawSqlite b) m () Source #

update :: forall record (m :: Type -> Type ). ( MonadIO m, PersistRecordBackend record ( RawSqlite b)) => Key record -> [ Update record] -> ReaderT ( RawSqlite b) m () Source #

updateGet :: forall record (m :: Type -> Type ). ( MonadIO m, PersistRecordBackend record ( RawSqlite b)) => Key record -> [ Update record] -> ReaderT ( RawSqlite b) m record Source #

( PersistCore b, PersistCore ( RawSqlite b), PersistField ( BackendKey b)) => PersistField ( BackendKey ( RawSqlite b)) Source #
Instance details

Defined in Database.Persist.Sqlite

type BaseBackend ( RawSqlite b) Source #
Instance details

Defined in Database.Persist.Sqlite

newtype BackendKey ( RawSqlite b) Source #
Instance details

Defined in Database.Persist.Sqlite

persistentBackend :: forall backend backend. Lens ( RawSqlite backend) ( RawSqlite backend) backend backend Source #

withRawSqliteConnInfo :: ( MonadUnliftIO m, MonadLoggerIO m) => SqliteConnectionInfo -> ( RawSqlite SqlBackend -> m a) -> m a Source #

Like withSqliteConnInfo , but exposes the internal Connection . For power users who want to manually interact with SQLite's C API via internals exposed by Database.Sqlite.Internal

Since: 2.10.2

createRawSqlitePoolFromInfo Source #

Arguments

:: ( MonadLoggerIO m, MonadUnliftIO m)
=> SqliteConnectionInfo
-> ( RawSqlite SqlBackend -> m ())

An action that is run whenever a new RawSqlite connection is allocated in the pool. The main use of this function is to register custom functions with the SQLite connection upon creation.

-> Int
-> m ( Pool ( RawSqlite SqlBackend ))

Like createSqlitePoolFromInfo , but like withRawSqliteConnInfo it exposes the internal Connection .

For power users who want to manually interact with SQLite's C API via internals exposed by Database.Sqlite.Internal . The callback can be used to run arbitrary actions on the connection upon allocation from the pool.

Since: 2.10.6

withRawSqlitePoolInfo Source #

Arguments

:: ( MonadUnliftIO m, MonadLoggerIO m)
=> SqliteConnectionInfo
-> ( RawSqlite SqlBackend -> m ())
-> Int

number of connections to open

-> ( Pool ( RawSqlite SqlBackend ) -> m a)
-> m a

Like createSqlitePoolInfo , but based on createRawSqlitePoolFromInfo .

Since: 2.10.6

withRawSqlitePoolInfo_ Source #

Arguments

:: ( MonadUnliftIO m, MonadLoggerIO m)
=> SqliteConnectionInfo
-> Int

number of connections to open

-> ( Pool ( RawSqlite SqlBackend ) -> m a)
-> m a

Like createSqlitePoolInfo , but based on createRawSqlitePoolFromInfo_ .

Since: 2.10.6