beam-postgres-0.3.2.0: Connection layer between beam and postgres

Safe HaskellNone
LanguageHaskell2010

Database.Beam.Postgres.Full

Contents

Description

Module providing (almost) full support for Postgres query and data manipulation statements. These functions shadow the functions in Database.Beam.Query and provide a strict superset of functionality. They map 1-to-1 with the underlying Postgres support.

Synopsis

Additional SELECT features

SELECT Locking clause

data PgWithLocking s a Source #

Combines the result of a query along with a set of locked tables. Used as a return value for the lockingFor_ function.

Instances

ProjectibleWithPredicate c syntax a => ProjectibleWithPredicate c syntax (PgWithLocking s a) Source # 

Methods

project' :: Monad m => Proxy (* -> Constraint) c -> (forall context. c context => Proxy * context -> WithExprContext syntax -> m (WithExprContext syntax)) -> PgWithLocking s a -> m (PgWithLocking s a) #

data PgLockedTables s Source #

An explicit lock against some tables. You can create a value of this type using the locked_ function. You can combine these values monoidally to combine multiple locks for use with the withLocks_ function.

data PgSelectLockingStrength Source #

Specifies the level of lock that will be taken against a row. See the manual section for more information.

Instances

Eq PgSelectLockingStrength Source # 
Show PgSelectLockingStrength Source # 
Generic PgSelectLockingStrength Source # 
type Rep PgSelectLockingStrength Source # 
type Rep PgSelectLockingStrength = D1 * (MetaData "PgSelectLockingStrength" "Database.Beam.Postgres.Syntax" "beam-postgres-0.3.2.0-36iAb593A4W69abKidpZQx" False) ((:+:) * ((:+:) * (C1 * (MetaCons "PgSelectLockingStrengthUpdate" PrefixI False) (U1 *)) (C1 * (MetaCons "PgSelectLockingStrengthNoKeyUpdate" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "PgSelectLockingStrengthShare" PrefixI False) (U1 *)) (C1 * (MetaCons "PgSelectLockingStrengthKeyShare" PrefixI False) (U1 *))))

data PgSelectLockingOptions Source #

Specifies how we should handle lock conflicts.

See the manual section for more information

Constructors

PgSelectLockingOptionsNoWait

NOWAIT. Report an error rather than waiting for the lock

PgSelectLockingOptionsSkipLocked

SKIP LOCKED. Rather than wait for a lock, skip the row instead

Instances

lockingAllTablesFor_ :: (Database Postgres db, Projectible PgExpressionSyntax a) => PgSelectLockingStrength -> Maybe PgSelectLockingOptions -> Q PgSelectSyntax db (QNested s) a -> Q PgSelectSyntax db s a Source #

Like lockingFor_, but does not require an explicit set of locked tables. This produces an empty FOR .. OF clause.

lockingFor_ :: (Database Postgres db, Projectible PgExpressionSyntax a) => PgSelectLockingStrength -> Maybe PgSelectLockingOptions -> Q PgSelectSyntax db (QNested s) (PgWithLocking (QNested s) a) -> Q PgSelectSyntax db s a Source #

Lock some tables during the execution of a query. This is rather complicated, and there are several usage examples in the user guide

The Postgres locking clause is rather complex, and beam currently does not check several pre-conditions. It is assumed you kinda know what you're doing.

Things which postgres doesn't like, but beam will do

  • Using aggregates within a query that has a locking clause
  • Using UNION, INTERSECT, or EXCEPT

See here for more details.

This function accepts a locking strength (UPDATE, SHARE, KEY SHARE, etc), an optional locking option (NOWAIT or SKIP LOCKED), and a query whose rows to lock. The query should return its result wrapped in PgWithLocking, via the withLocks_ or lockAll_ function.

If you want to use the most common behavior (lock all rows in every table mentioned), the lockingAllTablesFor_ function may be what you're after.

locked_ :: Database Postgres db => DatabaseEntity Postgres db (TableEntity tbl) -> Q PgSelectSyntax db s (PgLockedTables s, tbl (QExpr PgExpressionSyntax s)) Source #

Join with a table while locking it explicitly. Provides a PgLockedTables value that can be used with withLocks_ to explicitly lock a table during a SELECT statement

lockAll_ :: a -> PgWithLocking s a Source #

Use with lockingFor_ to lock all tables mentioned in the query

withLocks_ :: a -> PgLockedTables s -> PgWithLocking s a Source #

Return and lock the given tables. Typically used as an infix operator. See the the user guide for usage examples

INSERT and INSERT RETURNING

insert :: DatabaseEntity Postgres db (TableEntity table) -> SqlInsertValues PgInsertValuesSyntax (table (QExpr PgExpressionSyntax s)) -> PgInsertOnConflict table -> SqlInsert PgInsertSyntax Source #

A beam-postgres-specific version of insert, which provides fuller support for the much richer Postgres INSERT syntax. This allows you to specify ON CONFLICT actions. For even more complete support, see insertReturning.

insertReturning :: Projectible PgExpressionSyntax a => DatabaseEntity Postgres be (TableEntity table) -> SqlInsertValues PgInsertValuesSyntax (table (QExpr PgExpressionSyntax s)) -> PgInsertOnConflict table -> Maybe (table (QExpr PgExpressionSyntax PostgresInaccessible) -> a) -> PgInsertReturning (QExprToIdentity a) Source #

The full Postgres INSERT syntax, supporting conflict actions and the RETURNING CLAUSE. See PgInsertOnConflict for how to specify a conflict action or provide onConflictDefault to preserve the behavior without any ON CONFLICT clause. The last argument takes a newly inserted row and returns the expression to be returned as part of the RETURNING clause. For a backend-agnostic version of this functionality see MonadBeamInsertReturning. Use runInsertReturning to get the results.

data PgInsertReturning a Source #

The most general kind of INSERT that postgres can perform

Specifying conflict actions

newtype PgInsertOnConflict (tbl :: (* -> *) -> *) Source #

What to do when an INSERT statement inserts a row into the table tbl that violates a constraint.

newtype PgInsertOnConflictTarget (tbl :: (* -> *) -> *) Source #

Specifies the kind of constraint that must be violated for the action to occur

newtype PgConflictAction (tbl :: (* -> *) -> *) Source #

A description of what to do when a constraint or index is violated.

onConflictDefault :: PgInsertOnConflict tbl Source #

By default, Postgres will throw an error when a conflict is detected. This preserves that functionality.

onConflict :: Beamable tbl => PgInsertOnConflictTarget tbl -> PgConflictAction tbl -> PgInsertOnConflict tbl Source #

Tells postgres what to do on an INSERT conflict. The first argument is the type of conflict to provide an action for. For example, to only provide an action for certain fields, use conflictingFields. Or to only provide an action over certain fields where a particular condition is met, use conflictingFields. If you have a particular constraint violation in mind, use conflictingConstraint. To perform an action on any conflict, use anyConflict.

See the Postgres documentation.

anyConflict :: PgInsertOnConflictTarget tbl Source #

Perform the conflict action when any constraint or index conflict occurs. Syntactically, this is the ON CONFLICT clause, without any conflict target.

conflictingFields :: Projectible PgExpressionSyntax proj => (tbl (QExpr PgExpressionSyntax PostgresInaccessible) -> proj) -> PgInsertOnConflictTarget tbl Source #

Perform the conflict action only when these fields conflict. The first argument gets the current row as a table of expressions. Return the conflict key. For more information, see the beam-postgres manual.

conflictingFieldsWhere :: Projectible PgExpressionSyntax proj => (tbl (QExpr PgExpressionSyntax PostgresInaccessible) -> proj) -> (tbl (QExpr PgExpressionSyntax PostgresInaccessible) -> QExpr PgExpressionSyntax PostgresInaccessible Bool) -> PgInsertOnConflictTarget tbl Source #

Like conflictingFields, but only perform the action if the condition given in the second argument is met. See the postgres manual for more information.

conflictingConstraint :: Text -> PgInsertOnConflictTarget tbl Source #

Perform the action only if the given named constraint is violated

onConflictDoNothing :: PgConflictAction tbl Source #

The Postgres DO NOTHING action

onConflictUpdateSet :: Beamable tbl => (tbl (QField PostgresInaccessible) -> tbl (QExpr PgExpressionSyntax PostgresInaccessible) -> [QAssignment PgFieldNameSyntax PgExpressionSyntax PostgresInaccessible]) -> PgConflictAction tbl Source #

The Postgres DO UPDATE SET action, without the WHERE clause. The argument takes an updatable row (like the one used in update) and the conflicting row. Use current_ on the first argument to get the current value of the row in the database.

onConflictUpdateSetWhere :: Beamable tbl => (tbl (QField PostgresInaccessible) -> tbl (QExpr PgExpressionSyntax PostgresInaccessible) -> [QAssignment PgFieldNameSyntax PgExpressionSyntax PostgresInaccessible]) -> (tbl (QExpr PgExpressionSyntax PostgresInaccessible) -> QExpr PgExpressionSyntax PostgresInaccessible Bool) -> PgConflictAction tbl Source #

The Postgres DO UPDATE SET action, with the WHERE clause. This is like onConflictUpdateSet, but only rows satisfying the given condition are updated. Sometimes this results in more efficient locking. See the Postgres manual for more information.

onConflictUpdateInstead :: (Beamable tbl, Projectible Text proj) => (tbl (QExpr Text PostgresInaccessible) -> proj) -> PgConflictAction tbl Source #

Sometimes you want to update certain columns in the row. Given a projection from a row to the fields you want, Beam can auto-generate an assignment that assigns the corresponding fields of the conflicting row.

onConflictSetAll :: (Beamable tbl, Projectible Text (tbl (QExpr Text PostgresInaccessible))) => PgConflictAction tbl Source #

Sometimes you want to update every value in the row. Beam can auto-generate an assignment that assigns the conflicting row to every field in the database row. This may not always be what you want.

UPDATE RETURNING

data PgUpdateReturning a Source #

The most general kind of UPDATE that postgres can perform

updateReturning :: Projectible PgExpressionSyntax a => DatabaseEntity Postgres be (TableEntity table) -> (forall s. table (QField s) -> [QAssignment PgFieldNameSyntax PgExpressionSyntax s]) -> (forall s. table (QExpr PgExpressionSyntax s) -> QExpr PgExpressionSyntax s Bool) -> (table (QExpr PgExpressionSyntax PostgresInaccessible) -> a) -> PgUpdateReturning (QExprToIdentity a) Source #

Postgres UPDATE ... RETURNING statement support. The last argument takes the newly inserted row and returns the values to be returned. Use runUpdateReturning to get the results.

DELETE RETURNING

newtype PgDeleteReturning a Source #

The most general kind of DELETE that postgres can perform

deleteReturning :: Projectible PgExpressionSyntax a => DatabaseEntity Postgres be (TableEntity table) -> (forall s. table (QExpr PgExpressionSyntax s) -> QExpr PgExpressionSyntax s Bool) -> (table (QExpr PgExpressionSyntax PostgresInaccessible) -> a) -> PgDeleteReturning (QExprToIdentity a) Source #

Postgres DELETE ... RETURNING statement support. The last argument takes the newly inserted row and returns the values to be returned. Use runDeleteReturning to get the results.