beam-core-0.9.0.0: Type-safe, feature-complete SQL query and manipulation interface for Haskell

Safe HaskellNone
LanguageHaskell2010

Database.Beam.Backend.SQL.BeamExtensions

Description

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

Documentation

class MonadBeam be m => MonadBeamInsertReturning be m | m -> be where Source #

MonadBeams that support returning the newly created rows of an INSERT statement. Useful for discovering the real value of a defaulted value.

Methods

runInsertReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlInsert be table -> m [table Identity] Source #

Instances
(MonadBeamInsertReturning be m, Monoid r) => MonadBeamInsertReturning be (WriterT r m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runInsertReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlInsert be table -> WriterT r m [table Identity] Source #

(MonadBeamInsertReturning be m, Monoid r) => MonadBeamInsertReturning be (WriterT r m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runInsertReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlInsert be table -> WriterT r m [table Identity] Source #

MonadBeamInsertReturning be m => MonadBeamInsertReturning be (StateT r m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runInsertReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlInsert be table -> StateT r m [table Identity] Source #

MonadBeamInsertReturning be m => MonadBeamInsertReturning be (StateT r m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runInsertReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlInsert be table -> StateT r m [table Identity] Source #

MonadBeamInsertReturning be m => MonadBeamInsertReturning be (ExceptT e m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runInsertReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlInsert be table -> ExceptT e m [table Identity] Source #

MonadBeamInsertReturning be m => MonadBeamInsertReturning be (ReaderT r m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runInsertReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlInsert be table -> ReaderT r m [table Identity] Source #

MonadBeamInsertReturning be m => MonadBeamInsertReturning be (ContT r m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runInsertReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlInsert be table -> ContT r m [table Identity] Source #

(MonadBeamInsertReturning be m, Monoid w) => MonadBeamInsertReturning be (RWST r w s m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runInsertReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlInsert be table -> RWST r w s m [table Identity] Source #

(MonadBeamInsertReturning be m, Monoid w) => MonadBeamInsertReturning be (RWST r w s m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runInsertReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlInsert be table -> RWST r w s m [table Identity] Source #

class MonadBeam be m => MonadBeamUpdateReturning be m | m -> be where Source #

MonadBeams that support returning the updated rows of an UPDATE statement. Useful for discovering the new values of the updated rows.

Methods

runUpdateReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlUpdate be table -> m [table Identity] Source #

Instances
(MonadBeamUpdateReturning be m, Monoid r) => MonadBeamUpdateReturning be (WriterT r m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runUpdateReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlUpdate be table -> WriterT r m [table Identity] Source #

(MonadBeamUpdateReturning be m, Monoid r) => MonadBeamUpdateReturning be (WriterT r m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runUpdateReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlUpdate be table -> WriterT r m [table Identity] Source #

MonadBeamUpdateReturning be m => MonadBeamUpdateReturning be (StateT r m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runUpdateReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlUpdate be table -> StateT r m [table Identity] Source #

MonadBeamUpdateReturning be m => MonadBeamUpdateReturning be (StateT r m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runUpdateReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlUpdate be table -> StateT r m [table Identity] Source #

MonadBeamUpdateReturning be m => MonadBeamUpdateReturning be (ExceptT e m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runUpdateReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlUpdate be table -> ExceptT e m [table Identity] Source #

MonadBeamUpdateReturning be m => MonadBeamUpdateReturning be (ReaderT r m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runUpdateReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlUpdate be table -> ReaderT r m [table Identity] Source #

MonadBeamUpdateReturning be m => MonadBeamUpdateReturning be (ContT r m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runUpdateReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlUpdate be table -> ContT r m [table Identity] Source #

(MonadBeamUpdateReturning be m, Monoid w) => MonadBeamUpdateReturning be (RWST r w s m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runUpdateReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlUpdate be table -> RWST r w s m [table Identity] Source #

(MonadBeamUpdateReturning be m, Monoid w) => MonadBeamUpdateReturning be (RWST r w s m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runUpdateReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlUpdate be table -> RWST r w s m [table Identity] Source #

class MonadBeam be m => MonadBeamDeleteReturning be m | m -> be where Source #

MonadBeams that suppert returning rows that will be deleted by the given DELETE statement. Useful for deallocating resources based on the value of deleted rows.

Methods

runDeleteReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlDelete be table -> m [table Identity] Source #

Instances
(MonadBeamDeleteReturning be m, Monoid r) => MonadBeamDeleteReturning be (WriterT r m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runDeleteReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlDelete be table -> WriterT r m [table Identity] Source #

(MonadBeamDeleteReturning be m, Monoid r) => MonadBeamDeleteReturning be (WriterT r m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runDeleteReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlDelete be table -> WriterT r m [table Identity] Source #

MonadBeamDeleteReturning be m => MonadBeamDeleteReturning be (StateT r m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runDeleteReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlDelete be table -> StateT r m [table Identity] Source #

MonadBeamDeleteReturning be m => MonadBeamDeleteReturning be (StateT r m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runDeleteReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlDelete be table -> StateT r m [table Identity] Source #

MonadBeamDeleteReturning be m => MonadBeamDeleteReturning be (ExceptT e m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runDeleteReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlDelete be table -> ExceptT e m [table Identity] Source #

MonadBeamDeleteReturning be m => MonadBeamDeleteReturning be (ReaderT r m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runDeleteReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlDelete be table -> ReaderT r m [table Identity] Source #

MonadBeamDeleteReturning be m => MonadBeamDeleteReturning be (ContT r m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runDeleteReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlDelete be table -> ContT r m [table Identity] Source #

(MonadBeamDeleteReturning be m, Monoid w) => MonadBeamDeleteReturning be (RWST r w s m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runDeleteReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlDelete be table -> RWST r w s m [table Identity] Source #

(MonadBeamDeleteReturning be m, Monoid w) => MonadBeamDeleteReturning be (RWST r w s m) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.BeamExtensions

Methods

runDeleteReturningList :: (Beamable table, Projectible be (table (QExpr be ())), FromBackendRow be (table Identity)) => SqlDelete be table -> RWST r w s m [table Identity] Source #

class BeamSqlBackend be => BeamHasInsertOnConflict be where Source #

Associated Types

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.

Methods

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 #

newtype SqlSerial a Source #

Constructors

SqlSerial 

Fields

Instances
FromBackendRow be x => FromBackendRow be (SqlSerial x) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Row

HasSqlValueSyntax syntax x => HasSqlValueSyntax syntax (SqlSerial x) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.SQL92

Methods

sqlValueSyntax :: SqlSerial x -> syntax Source #

HasSqlQuantifiedEqualityCheck syntax a => HasSqlQuantifiedEqualityCheck syntax (SqlSerial a) Source # 
Instance details

Defined in Database.Beam.Query.Ord

HasSqlEqualityCheck be a => HasSqlEqualityCheck be (SqlSerial a) Source # 
Instance details

Defined in Database.Beam.Query.Ord

Enum a => Enum (SqlSerial a) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Types

Eq a => Eq (SqlSerial a) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Types

Methods

(==) :: SqlSerial a -> SqlSerial a -> Bool #

(/=) :: SqlSerial a -> SqlSerial a -> Bool #

Integral a => Integral (SqlSerial a) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Types

Num a => Num (SqlSerial a) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Types

Ord a => Ord (SqlSerial a) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Types

Read a => Read (SqlSerial a) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Types

Real a => Real (SqlSerial a) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Types

Show a => Show (SqlSerial a) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Types

ToJSON a => ToJSON (SqlSerial a) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Types

FromJSON a => FromJSON (SqlSerial a) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Types

onConflictUpdateInstead :: forall be table proj. (BeamHasInsertOnConflict be, Beamable table, ProjectibleWithPredicate AnyType () (InaccessibleQAssignment be) proj) => (table (Const (InaccessibleQAssignment be)) -> proj) -> SqlConflictAction be table Source #