groundhog-sqlite-0.8: Sqlite3 backend for the groundhog library

Safe HaskellNone
LanguageHaskell98

Database.Groundhog.Sqlite

Synopsis

Documentation

withSqlitePool Source #

Arguments

:: (MonadBaseControl IO m, MonadIO m) 
=> String

connection string

-> Int

number of connections to open

-> (Pool Sqlite -> m a) 
-> m a 

withSqliteConn Source #

Arguments

:: (MonadBaseControl IO m, MonadIO m) 
=> String

connection string

-> (Sqlite -> m a) 
-> m a 

createSqlitePool Source #

Arguments

:: MonadIO m 
=> String

connection string

-> Int

number of connections to open

-> m (Pool Sqlite) 

runDbConn :: (MonadIO m, MonadBaseControl IO m, ConnectionManager conn, ExtractConnection cm conn) => Action conn a -> cm -> m a #

Runs action within connection. It can handle a simple connection, a pool of them, etc.

data Sqlite Source #

Instances

SchemaAnalyzer Sqlite Source # 
SqlDb Sqlite Source # 
DbDescriptor Sqlite Source # 

Associated Types

type AutoKeyType Sqlite :: * #

type QueryRaw Sqlite :: * -> * #

Methods

backendName :: proxy Sqlite -> String #

PersistBackendConn Sqlite Source # 

Methods

insert :: (PersistEntity v, PersistBackend m, (* ~ Conn m) Sqlite) => v -> m (AutoKey v) #

insert_ :: (PersistEntity v, PersistBackend m, (* ~ Conn m) Sqlite) => v -> m () #

insertBy :: (PersistEntity v, IsUniqueKey (Key v (Unique u)), PersistBackend m, (* ~ Conn m) Sqlite) => u (UniqueMarker v) -> v -> m (Either (AutoKey v) (AutoKey v)) #

insertByAll :: (PersistEntity v, PersistBackend m, (* ~ Conn m) Sqlite) => v -> m (Either (AutoKey v) (AutoKey v)) #

replace :: (PersistEntity v, PrimitivePersistField (Key v BackendSpecific), PersistBackend m, (* ~ Conn m) Sqlite) => Key v BackendSpecific -> v -> m () #

replaceBy :: (PersistEntity v, IsUniqueKey (Key v (Unique u)), PersistBackend m, (* ~ Conn m) Sqlite) => u (UniqueMarker v) -> v -> m () #

select :: (PersistEntity v, EntityConstr v c, HasSelectOptions opts Sqlite (RestrictionHolder v c), PersistBackend m, (* ~ Conn m) Sqlite) => opts -> m [v] #

selectStream :: (PersistEntity v, EntityConstr v c, HasSelectOptions opts Sqlite (RestrictionHolder v c), PersistBackend m, (* ~ Conn m) Sqlite) => opts -> m (RowStream v) #

selectAll :: (PersistEntity v, PersistBackend m, (* ~ Conn m) Sqlite) => m [(AutoKey v, v)] #

selectAllStream :: (PersistEntity v, PersistBackend m, (* ~ Conn m) Sqlite) => m (RowStream (AutoKey v, v)) #

get :: (PersistEntity v, PrimitivePersistField (Key v BackendSpecific), PersistBackend m, (* ~ Conn m) Sqlite) => Key v BackendSpecific -> m (Maybe v) #

getBy :: (PersistEntity v, IsUniqueKey (Key v (Unique u)), PersistBackend m, (* ~ Conn m) Sqlite) => Key v (Unique u) -> m (Maybe v) #

update :: (PersistEntity v, EntityConstr v c, PersistBackend m, (* ~ Conn m) Sqlite) => [Update Sqlite (RestrictionHolder v c)] -> Cond Sqlite (RestrictionHolder v c) -> m () #

delete :: (PersistEntity v, EntityConstr v c, PersistBackend m, (* ~ Conn m) Sqlite) => Cond Sqlite (RestrictionHolder v c) -> m () #

deleteBy :: (PersistEntity v, PrimitivePersistField (Key v BackendSpecific), PersistBackend m, (* ~ Conn m) Sqlite) => Key v BackendSpecific -> m () #

deleteAll :: (PersistEntity v, PersistBackend m, (* ~ Conn m) Sqlite) => v -> m () #

count :: (PersistEntity v, EntityConstr v c, PersistBackend m, (* ~ Conn m) Sqlite) => Cond Sqlite (RestrictionHolder v c) -> m Int #

countAll :: (PersistEntity v, PersistBackend m, (* ~ Conn m) Sqlite) => v -> m Int #

project :: (PersistEntity v, EntityConstr v c, Projection' p Sqlite (RestrictionHolder v c) a, HasSelectOptions opts Sqlite (RestrictionHolder v c), PersistBackend m, (* ~ Conn m) Sqlite) => p -> opts -> m [a] #

projectStream :: (PersistEntity v, EntityConstr v c, Projection' p Sqlite (RestrictionHolder v c) a, HasSelectOptions opts Sqlite (RestrictionHolder v c), PersistBackend m, (* ~ Conn m) Sqlite) => p -> opts -> m (RowStream a) #

migrate :: (PersistEntity v, PersistBackend m, (* ~ Conn m) Sqlite) => v -> Migration m #

executeRaw :: (PersistBackend m, (* ~ Conn m) Sqlite) => Bool -> String -> [PersistValue] -> m () #

queryRaw :: (PersistBackend m, (* ~ Conn m) Sqlite) => Bool -> String -> [PersistValue] -> m (RowStream [PersistValue]) #

insertList :: (PersistField a, PersistBackend m, (* ~ Conn m) Sqlite) => [a] -> m Int64 #

getList :: (PersistField a, PersistBackend m, (* ~ Conn m) Sqlite) => Int64 -> m [a] #

ConnectionManager Sqlite Source # 

Methods

withConn :: (MonadBaseControl IO m, MonadIO m) => (Sqlite -> m a) -> Sqlite -> m a #

Savepoint Sqlite Source # 

Methods

withConnSavepoint :: (MonadBaseControl IO m, MonadIO m) => String -> m a -> Sqlite -> m a #

ExtractConnection Sqlite Sqlite Source # 

Methods

extractConn :: (MonadBaseControl IO m, MonadIO m) => (Sqlite -> m a) -> Sqlite -> m a #

ExtractConnection (Pool Sqlite) Sqlite Source # 

Methods

extractConn :: (MonadBaseControl IO m, MonadIO m) => (Sqlite -> m a) -> Pool Sqlite -> m a #

type QueryRaw Sqlite Source # 
type AutoKeyType Sqlite Source #