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

Database.Persist.SqlBackend.Internal

Synopsis

Documentation

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.

Constructors

SqlBackend 

Fields

  • connPrepare :: Text -> IO Statement

    This function should prepare a Statement in the target database, which should allow for efficient query reuse.

  • connInsertSql :: EntityDef -> [PersistValue] -> InsertSqlResult

    This function generates the SQL and values necessary for performing an insert against the database.

  • connInsertManySql :: Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult)

    SQL for inserting many rows and returning their primary keys, for backends that support this functionality. If Nothing, rows will be inserted one-at-a-time using connInsertSql.

  • connUpsertSql :: Maybe (EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text)

    Some databases support performing UPSERT _and_ RETURN entity in a single call.

    This field when set will be used to generate the UPSERT+RETURN sql given * an entity definition * updates to be run on unique key(s) collision

    When left as Nothing, we find the unique key from entity def before * trying to fetch an entity by said key * perform an update when result found, else issue an insert * return new entity from db

    Since: 2.6

  • connPutManySql :: Maybe (EntityDef -> Int -> Text)

    Some databases support performing bulk UPSERT, specifically "insert or replace many records" in a single call.

    This field when set, given * an entity definition * number of records to be inserted should produce a PUT MANY sql with placeholders for records

    When left as Nothing, we default to using defaultPutMany.

    Since: 2.8.1

  • connStmtMap :: StatementCache

    A reference to the cache of statements. Statements are keyed by the Text queries that generated them.

  • connClose :: IO ()

    Close the underlying connection.

  • connMigrateSql :: [EntityDef] -> (Text -> IO Statement) -> EntityDef -> IO (Either [Text] [(Bool, Text)])

    This function returns the migrations required to include the EntityDef parameter in the [EntityDef] database. This might include creating a new table if the entity is not present, or altering an existing table if it is.

  • connBegin :: (Text -> IO Statement) -> Maybe IsolationLevel -> IO ()

    A function to begin a transaction for the underlying database.

  • connCommit :: (Text -> IO Statement) -> IO ()

    A function to commit a transaction to the underlying database.

  • connRollback :: (Text -> IO Statement) -> IO ()

    A function to roll back a transaction on the underlying database.

  • connEscapeFieldName :: FieldNameDB -> Text

    A function to extract and escape the name of the column corresponding to the provided field.

    Since: 2.12.0.0

  • connEscapeTableName :: EntityDef -> Text

    A function to extract and escape the name of the table corresponding to the provided entity. PostgreSQL uses this to support schemas.

    Since: 2.12.0.0

  • connEscapeRawName :: Text -> Text

    A function to escape raw DB identifiers. MySQL uses backticks, while PostgreSQL uses quotes, and so on.

    Since: 2.12.0.0

  • connNoLimit :: Text
     
  • connRDBMS :: Text

    A tag displaying what database the SqlBackend is for. Can be used to differentiate features in downstream libraries for different database backends.

  • connLimitOffset :: (Int, Int) -> Text -> Text

    Attach a 'LIMIT/OFFSET' clause to a SQL query. Note that LIMIT/OFFSET is problematic for performance, and indexed range queries are the superior way to offer pagination.

  • connLogFunc :: LogFunc

    A log function for the SqlBackend to use.

  • connMaxParams :: Maybe Int

    Some databases (probably only Sqlite) have a limit on how many question-mark parameters may be used in a statement

    Since: 2.6.1

  • connRepsertManySql :: Maybe (EntityDef -> Int -> Text)

    Some databases support performing bulk an atomic+bulk INSERT where constraint conflicting entities can replace existing entities.

    This field when set, given * an entity definition * number of records to be inserted should produce a INSERT sql with placeholders for primary+record fields

    When left as Nothing, we default to using defaultRepsertMany.

    Since: 2.9.0

  • connVault :: Vault

    Carry arbitrary payloads for the connection that may be used to propagate information into hooks.

  • connHooks :: SqlBackendHooks

    Instrumentation hooks that may be used to track the behaviour of a backend.

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.3.2-9cyOmHN2kyqIdNPEsrnIgG" '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