Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Some functionality is useful enough to be provided across backends, but is not standardized. For example, many RDBMS systems provide ways of fetching auto-incrementing or defaulting fields on INSERT or UPDATE.
Beam provides type classes that some backends instantiate that provide this support. This uses direct means on sufficiently advanced backends and is emulated on others.
Synopsis
- class MonadBeam be m => MonadBeamInsertReturning be m | m -> be where
- runInsertReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlInsert be table -> m [table Identity]
- class MonadBeam be m => MonadBeamUpdateReturning be m | m -> be where
- runUpdateReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlUpdate be table -> m [table Identity]
- class MonadBeam be m => MonadBeamDeleteReturning be m | m -> be where
- runDeleteReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlDelete be table -> m [table Identity]
- class BeamSqlBackend be => BeamHasInsertOnConflict be where
- data SqlConflictTarget be (table :: (Type -> Type) -> Type) :: Type
- data SqlConflictAction be (table :: (Type -> Type) -> Type) :: Type
- insertOnConflict :: Beamable table => DatabaseEntity be db (TableEntity table) -> SqlInsertValues be (table (QExpr be s)) -> SqlConflictTarget be table -> SqlConflictAction be table -> SqlInsert be table
- anyConflict :: SqlConflictTarget be table
- conflictingFields :: Projectible be proj => (table (QExpr be QInternal) -> proj) -> SqlConflictTarget be table
- conflictingFieldsWhere :: Projectible be proj => (table (QExpr be QInternal) -> proj) -> (forall s. table (QExpr be s) -> QExpr be s Bool) -> SqlConflictTarget be table
- onConflictDoNothing :: SqlConflictAction be table
- onConflictUpdateSet :: Beamable table => (forall s. table (QField s) -> table (QExpr be s) -> QAssignment be s) -> SqlConflictAction be table
- onConflictUpdateSetWhere :: Beamable table => (forall s. table (QField s) -> table (QExpr be s) -> QAssignment be s) -> (forall s. table (QField s) -> table (QExpr be s) -> QExpr be s Bool) -> SqlConflictAction be table
- newtype SqlSerial a = SqlSerial {
- unSerial :: a
- onConflictUpdateInstead :: forall be table proj. (BeamHasInsertOnConflict be, Beamable table, ProjectibleWithPredicate AnyType () (InaccessibleQAssignment be) proj) => (table (Const (InaccessibleQAssignment be)) -> proj) -> SqlConflictAction be table
- onConflictUpdateAll :: forall be table. (BeamHasInsertOnConflict be, Beamable table) => SqlConflictAction be table
Documentation
class MonadBeam be m => MonadBeamInsertReturning be m | m -> be where Source #
MonadBeam
s that support returning the newly created rows of an INSERT
statement.
Useful for discovering the real value of a defaulted value.
runInsertReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlInsert be table -> m [table Identity] Source #
Instances
class MonadBeam be m => MonadBeamUpdateReturning be m | m -> be where Source #
MonadBeam
s that support returning the updated rows of an UPDATE
statement.
Useful for discovering the new values of the updated rows.
runUpdateReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlUpdate be table -> m [table Identity] Source #
Instances
class MonadBeam be m => MonadBeamDeleteReturning be m | m -> be where Source #
MonadBeam
s that suppert returning rows that will be deleted by the given
DELETE
statement. Useful for deallocating resources based on the value of
deleted rows.
runDeleteReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlDelete be table -> m [table Identity] Source #
Instances
class BeamSqlBackend be => BeamHasInsertOnConflict be where Source #
data SqlConflictTarget be (table :: (Type -> Type) -> Type) :: Type Source #
Specifies the kind of constraint that must be violated for the action to occur
data SqlConflictAction be (table :: (Type -> Type) -> Type) :: Type Source #
What to do when an INSERT
statement inserts a row into the table tbl
that violates a constraint.
insertOnConflict :: Beamable table => DatabaseEntity be db (TableEntity table) -> SqlInsertValues be (table (QExpr be s)) -> SqlConflictTarget be table -> SqlConflictAction be table -> SqlInsert be table Source #
anyConflict :: SqlConflictTarget be table Source #
conflictingFields :: Projectible be proj => (table (QExpr be QInternal) -> proj) -> SqlConflictTarget be table Source #
conflictingFieldsWhere :: Projectible be proj => (table (QExpr be QInternal) -> proj) -> (forall s. table (QExpr be s) -> QExpr be s Bool) -> SqlConflictTarget be table Source #
onConflictDoNothing :: SqlConflictAction be table Source #
onConflictUpdateSet :: Beamable table => (forall s. table (QField s) -> table (QExpr be s) -> QAssignment be s) -> SqlConflictAction be table Source #
onConflictUpdateSetWhere :: Beamable table => (forall s. table (QField s) -> table (QExpr be s) -> QAssignment be s) -> (forall s. table (QField s) -> table (QExpr be s) -> QExpr be s Bool) -> SqlConflictAction be table Source #
Instances
onConflictUpdateInstead :: forall be table proj. (BeamHasInsertOnConflict be, Beamable table, ProjectibleWithPredicate AnyType () (InaccessibleQAssignment be) proj) => (table (Const (InaccessibleQAssignment be)) -> proj) -> SqlConflictAction be table Source #
onConflictUpdateAll :: forall be table. (BeamHasInsertOnConflict be, Beamable table) => SqlConflictAction be table Source #