persistent-2.13.0.3: Type-safe, multi-backend data serialization.
Safe HaskellNone
LanguageHaskell2010

Database.Persist.SqlBackend

Description

This module contains types and information necessary for a SQL database. Database support libraries, like persistent-postgresql, will be responsible for constructing these values.

Synopsis

The type and construction

data SqlBackend Source #

A SqlBackend represents a handle or connection to a database. It contains functions and values that allow databases to have more optimized implementations, as well as references that benefit performance and sharing.

Instead of using the SqlBackend constructor directly, use the mkSqlBackend function.

A SqlBackend is *not* thread-safe. You should not assume that a SqlBackend can be shared among threads and run concurrent queries. This *will* result in problems. Instead, you should create a Pool SqlBackend, known as a ConnectionPool, and pass that around in multi-threaded applications.

To run actions in the persistent library, you should use the runSqlConn function. If you're using a multithreaded application, use the runSqlPool function.

Instances

Instances details
PersistStoreWrite SqlBackend Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

Methods

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

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

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

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

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

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

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

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

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

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

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

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

PersistStoreRead SqlBackend Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

Methods

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

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

PersistCore SqlBackend Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

Associated Types

data BackendKey SqlBackend Source #

IsPersistBackend SqlBackend Source # 
Instance details

Defined in Database.Persist.SqlBackend.Internal

HasPersistBackend SqlBackend Source # 
Instance details

Defined in Database.Persist.SqlBackend.Internal

Associated Types

type BaseBackend SqlBackend Source #

PersistUniqueWrite SqlBackend Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistUnique

Methods

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

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

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

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

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

PersistUniqueRead SqlBackend Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistUnique

Methods

getBy :: forall record (m :: Type -> Type). (MonadIO m, PersistRecordBackend record SqlBackend) => Unique record -> ReaderT SqlBackend m (Maybe (Entity record)) Source #

PersistQueryWrite SqlBackend Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistQuery

Methods

updateWhere :: forall (m :: Type -> Type) record. (MonadIO m, PersistRecordBackend record SqlBackend) => [Filter record] -> [Update record] -> ReaderT SqlBackend m () Source #

deleteWhere :: forall (m :: Type -> Type) record. (MonadIO m, PersistRecordBackend record SqlBackend) => [Filter record] -> ReaderT SqlBackend m () Source #

PersistQueryRead SqlBackend Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistQuery

Methods

selectSourceRes :: forall record (m1 :: Type -> Type) (m2 :: Type -> Type). (PersistRecordBackend record SqlBackend, MonadIO m1, MonadIO m2) => [Filter record] -> [SelectOpt record] -> ReaderT SqlBackend m1 (Acquire (ConduitM () (Entity record) m2 ())) Source #

selectFirst :: forall (m :: Type -> Type) record. (MonadIO m, PersistRecordBackend record SqlBackend) => [Filter record] -> [SelectOpt record] -> ReaderT SqlBackend m (Maybe (Entity record)) Source #

selectKeysRes :: forall (m1 :: Type -> Type) (m2 :: Type -> Type) record. (MonadIO m1, MonadIO m2, PersistRecordBackend record SqlBackend) => [Filter record] -> [SelectOpt record] -> ReaderT SqlBackend m1 (Acquire (ConduitM () (Key record) m2 ())) Source #

count :: forall (m :: Type -> Type) record. (MonadIO m, PersistRecordBackend record SqlBackend) => [Filter record] -> ReaderT SqlBackend m Int Source #

exists :: forall (m :: Type -> Type) record. (MonadIO m, PersistRecordBackend record SqlBackend) => [Filter record] -> ReaderT SqlBackend m Bool Source #

BackendCompatible SqlBackend SqlBackend Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

BackendCompatible SqlBackend SqlWriteBackend Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

BackendCompatible SqlBackend SqlReadBackend Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

Bounded (BackendKey SqlBackend) Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

Enum (BackendKey SqlBackend) Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

Eq (BackendKey SqlBackend) Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

Integral (BackendKey SqlBackend) Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

Num (BackendKey SqlBackend) Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

Ord (BackendKey SqlBackend) Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

Read (BackendKey SqlBackend) Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

Real (BackendKey SqlBackend) Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

Show (BackendKey SqlBackend) Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

Generic (BackendKey SqlBackend) Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

Associated Types

type Rep (BackendKey SqlBackend) :: Type -> Type #

ToJSON (BackendKey SqlBackend) Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

FromJSON (BackendKey SqlBackend) Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

ToHttpApiData (BackendKey SqlBackend) Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

FromHttpApiData (BackendKey SqlBackend) Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

PathPiece (BackendKey SqlBackend) Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

PersistField (BackendKey SqlBackend) Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

PersistFieldSql (BackendKey SqlBackend) Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

newtype BackendKey SqlBackend Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

type BaseBackend SqlBackend Source # 
Instance details

Defined in Database.Persist.SqlBackend.Internal

type Rep (BackendKey SqlBackend) Source # 
Instance details

Defined in Database.Persist.Sql.Orphan.PersistStore

type Rep (BackendKey SqlBackend) = D1 ('MetaData "BackendKey" "Database.Persist.Sql.Orphan.PersistStore" "persistent-2.13.0.3-L98VgAAdaWv9xCVMOjMCNr" 'True) (C1 ('MetaCons "SqlBackendKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSqlBackendKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64)))

mkSqlBackend :: MkSqlBackendArgs -> SqlBackend Source #

A function for creating a value of the SqlBackend type. You should prefer to use this instead of the constructor for SqlBackend, because default values for this will be provided for new fields on the record when new functionality is added.

Since: 2.13.0.0

data MkSqlBackendArgs Source #

This type shares many of the same field names as the SqlBackend type. It's useful for library authors to use this when migrating from using the SqlBackend constructor directly to the mkSqlBackend function.

This type will only contain required fields for constructing a SqlBackend. For fields that aren't present on this record, you'll want to use the various set functions or

Since: 2.13.0.0

Constructors

MkSqlBackendArgs 

Fields

Utilities

The functions exported here are a bit more general than the record accessors. The easiest way to use them is to provide the SqlBackend directly to the function. However, you can also use them in a ReaderT context, and you can even use them with any backend type tht has a BackendCompatible SqlBackend backend instance.

SqlBackend Getters

getEscapedFieldName :: (BackendCompatible SqlBackend backend, MonadReader backend m) => FieldNameDB -> m Text Source #

This function can be used directly with a SqlBackend to escape a FieldNameDB.

let conn :: SqlBackend
getEscapedFieldName (FieldNameDB "asdf") conn

Alternatively, you can use it in a ReaderT SqlBackend context, like SqlPersistT:

query :: SqlPersistM Text
query = do
    field <- getEscapedFieldName (FieldNameDB "asdf")
    pure field

Since: 2.13.0.0

getEscapedRawName :: (BackendCompatible SqlBackend backend, MonadReader backend m) => Text -> m Text Source #

This function can be used directly with a SqlBackend to escape a raw Text.

let conn :: SqlBackend
getEscapedRawName (FieldNameDB "asdf") conn

Alternatively, you can use it in a ReaderT SqlBackend context, like SqlPersistT:

query :: SqlPersistM Text
query = do
    field <- getEscapedRawName (FieldNameDB "asdf")
    pure field

Since: 2.13.0.0

getEscapeRawNameFunction :: (BackendCompatible SqlBackend backend, MonadReader backend m) => m (Text -> Text) Source #

Return the function for escaping a raw name.

Since: 2.13.0.0

getConnLimitOffset Source #

Arguments

:: (BackendCompatible SqlBackend backend, MonadReader backend m) 
=> (Int, Int)

The (LIMIT, OFFSET) to put on the query.

-> Text

The SQL query that the LIMIT/OFFSET clause will be attached to.

-> m Text 

Decorate the given SQL query with the (LIMIT, OFFSET) specified.

Since: 2.13.0.0

getConnUpsertSql :: (BackendCompatible SqlBackend backend, MonadReader backend m) => m (Maybe (EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text)) Source #

Retrieve the function for generating an upsert statement, if the backend supports it.

Since: 2.13.0.0

SqlBackend Setters

setConnMaxParams :: Int -> SqlBackend -> SqlBackend Source #

Set the maximum parameters that may be issued in a given SQL query. This should be used only if the database backend have this limitation.

Since: 2.13.0.0

setConnRepsertManySql :: (EntityDef -> Int -> Text) -> SqlBackend -> SqlBackend Source #

Set the connRepsertManySql field on the SqlBackend. This should only be set by the database backend library. If this is not set, a slow default will be used.

Since: 2.13.0.0

setConnInsertManySql :: (EntityDef -> [[PersistValue]] -> InsertSqlResult) -> SqlBackend -> SqlBackend Source #

Set the connInsertManySql field on the SqlBackend. This should only be used by the database backend library to provide an efficient implementation of a bulk insert function. If this is not set, a slow default will be used.

Since: 2.13.0.0

setConnUpsertSql :: (EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text) -> SqlBackend -> SqlBackend Source #

Set the connUpsertSql field on the SqlBackend. This should only be used by the database backend library to provide an efficient implementation of a bulk insert function. If this is not set, a slow default will be used.

Since: 2.13.0.0

setConnPutManySql :: (EntityDef -> Int -> Text) -> SqlBackend -> SqlBackend Source #

Set the 'connPutManySql field on the SqlBackend. This should only be used by the database backend library to provide an efficient implementation of a bulk insert function. If this is not set, a slow default will be used.

Since: 2.13.0.0