| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Database.Esqueleto.PostgreSQL
Contents
Description
This module contain PostgreSQL-specific functions.
Since: 2.2.8
Synopsis
- data AggMode
- arrayAggDistinct :: (PersistField a, PersistField [a]) => SqlExpr (Value a) -> SqlExpr (Value (Maybe [a]))
- arrayAgg :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value (Maybe [a]))
- arrayAggWith :: AggMode -> SqlExpr (Value a) -> [OrderByClause] -> SqlExpr (Value (Maybe [a]))
- arrayRemove :: SqlExpr (Value [a]) -> SqlExpr (Value a) -> SqlExpr (Value [a])
- arrayRemoveNull :: SqlExpr (Value [Maybe a]) -> SqlExpr (Value [a])
- stringAgg :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) -> SqlExpr (Value (Maybe s))
- stringAggWith :: SqlString s => AggMode -> SqlExpr (Value s) -> SqlExpr (Value s) -> [OrderByClause] -> SqlExpr (Value (Maybe s))
- maybeArray :: (PersistField a, PersistField [a]) => SqlExpr (Value (Maybe [a])) -> SqlExpr (Value [a])
- chr :: SqlString s => SqlExpr (Value Int) -> SqlExpr (Value s)
- now_ :: SqlExpr (Value UTCTime)
- random_ :: (PersistField a, Num a) => SqlExpr (Value a)
- upsert :: (MonadIO m, PersistEntity record, OnlyOneUniqueKey record, PersistRecordBackend record SqlBackend, IsPersistBackend (PersistEntityBackend record)) => record -> NonEmpty (SqlExpr (Entity record) -> SqlExpr Update) -> ReaderT SqlBackend m (Entity record)
- upsertMaybe :: (MonadIO m, PersistEntity record, OnlyOneUniqueKey record, PersistRecordBackend record SqlBackend, IsPersistBackend (PersistEntityBackend record)) => record -> [SqlExpr (Entity record) -> SqlExpr Update] -> ReaderT SqlBackend m (Maybe (Entity record))
- upsertBy :: (MonadIO m, PersistEntity record, IsPersistBackend (PersistEntityBackend record), HasCallStack) => Unique record -> record -> NonEmpty (SqlExpr (Entity record) -> SqlExpr Update) -> ReaderT SqlBackend m (Entity record)
- upsertMaybeBy :: (MonadIO m, PersistEntity record, IsPersistBackend (PersistEntityBackend record)) => Unique record -> record -> [SqlExpr (Entity record) -> SqlExpr Update] -> ReaderT SqlBackend m (Maybe (Entity record))
- insertSelectWithConflict :: forall a m val backend. (FinalResult a, KnowResult a ~ Unique val, MonadIO m, PersistEntity val, SqlBackendCanWrite backend) => a -> SqlQuery (SqlExpr (Insertion val)) -> (SqlExpr (Entity val) -> SqlExpr (Entity val) -> [SqlExpr (Entity val) -> SqlExpr Update]) -> ReaderT backend m ()
- insertSelectWithConflictCount :: forall a val m backend. (FinalResult a, KnowResult a ~ Unique val, MonadIO m, PersistEntity val, SqlBackendCanWrite backend) => a -> SqlQuery (SqlExpr (Insertion val)) -> (SqlExpr (Entity val) -> SqlExpr (Entity val) -> [SqlExpr (Entity val) -> SqlExpr Update]) -> ReaderT backend m Int64
- noWait :: OnLockedBehavior
- wait :: OnLockedBehavior
- skipLocked :: OnLockedBehavior
- forUpdateOf :: LockableEntity a => a -> OnLockedBehavior -> SqlQuery ()
- forNoKeyUpdateOf :: LockableEntity a => a -> OnLockedBehavior -> SqlQuery ()
- forShare :: LockingKind
- forShareOf :: LockableEntity a => a -> OnLockedBehavior -> SqlQuery ()
- forKeyShareOf :: LockableEntity a => a -> OnLockedBehavior -> SqlQuery ()
- filterWhere :: SqlExpr (Value a) -> SqlExpr (Value Bool) -> SqlExpr (Value a)
- values :: (ToSomeValues a, ToAliasReference a, ToAlias a) => NonEmpty a -> From a
- ilike :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) -> SqlExpr (Value Bool)
- distinctOn :: [SqlExpr DistinctOn] -> SqlQuery ()
- distinctOnOrderBy :: [SqlExpr OrderBy] -> SqlQuery ()
- withMaterialized :: (ToAlias a, ToAliasReference a, SqlSelect a r) => SqlQuery a -> SqlQuery (From a)
- withNotMaterialized :: (ToAlias a, ToAliasReference a, SqlSelect a r) => SqlQuery a -> SqlQuery (From a)
- ascNullsFirst :: PersistField a => SqlExpr (Value a) -> SqlExpr OrderBy
- ascNullsLast :: PersistField a => SqlExpr (Value a) -> SqlExpr OrderBy
- descNullsFirst :: PersistField a => SqlExpr (Value a) -> SqlExpr OrderBy
- descNullsLast :: PersistField a => SqlExpr (Value a) -> SqlExpr OrderBy
- unsafeSqlAggregateFunction :: UnsafeSqlFunctionArgument a => Builder -> AggMode -> a -> [OrderByClause] -> SqlExpr (Value b)
Documentation
Aggregate mode
Constructors
| AggModeAll | ALL | 
| AggModeDistinct | DISTINCT | 
arrayAggDistinct :: (PersistField a, PersistField [a]) => SqlExpr (Value a) -> SqlExpr (Value (Maybe [a])) Source #
(array_agg) Concatenate distinct input values, including NULLs, into
 an array.
Since: 2.5.3
arrayAggWith :: AggMode -> SqlExpr (Value a) -> [OrderByClause] -> SqlExpr (Value (Maybe [a])) Source #
arrayRemove :: SqlExpr (Value [a]) -> SqlExpr (Value a) -> SqlExpr (Value [a]) Source #
(array_remove) Remove all elements equal to the given value from the
 array.
Since: 2.5.3
arrayRemoveNull :: SqlExpr (Value [Maybe a]) -> SqlExpr (Value [a]) Source #
Remove NULL values from an array
Arguments
| :: SqlString s | |
| => SqlExpr (Value s) | Input values. | 
| -> SqlExpr (Value s) | Delimiter. | 
| -> SqlExpr (Value (Maybe s)) | Concatenation. | 
(string_agg) Concatenate input values separated by a
 delimiter.
Since: 2.2.8
Arguments
| :: SqlString s | |
| => AggMode | Aggregate mode (ALL or DISTINCT) | 
| -> SqlExpr (Value s) | Input values. | 
| -> SqlExpr (Value s) | Delimiter. | 
| -> [OrderByClause] | ORDER BY clauses | 
| -> SqlExpr (Value (Maybe s)) | Concatenation. | 
(string_agg) Concatenate input values separated by a
 delimiter.
maybeArray :: (PersistField a, PersistField [a]) => SqlExpr (Value (Maybe [a])) -> SqlExpr (Value [a]) Source #
Coalesce an array with an empty default value
chr :: SqlString s => SqlExpr (Value Int) -> SqlExpr (Value s) Source #
(chr) Translate the given integer to a character. (Note the result will
 depend on the character set of your database.)
Since: 2.2.11
random_ :: (PersistField a, Num a) => SqlExpr (Value a) Source #
(random()) Split out into database specific modules
 because MySQL uses `rand()`.
Since: 2.6.0
Arguments
| :: (MonadIO m, PersistEntity record, OnlyOneUniqueKey record, PersistRecordBackend record SqlBackend, IsPersistBackend (PersistEntityBackend record)) | |
| => record | new record to insert | 
| -> NonEmpty (SqlExpr (Entity record) -> SqlExpr Update) | updates to perform if the record already exists | 
| -> ReaderT SqlBackend m (Entity record) | the record in the database after the operation | 
Perform an upsert operation on the given record.
If the record exists in the database already, then the updates will be performed on that record. If the record does not exist, then the provided record will be inserted.
If you wish to provide an empty list of updates (ie "if the record
 exists, do nothing"), then you will need to call upsertMaybe. Postgres
 will not return anything if there are no modifications or inserts made.
Arguments
| :: (MonadIO m, PersistEntity record, OnlyOneUniqueKey record, PersistRecordBackend record SqlBackend, IsPersistBackend (PersistEntityBackend record)) | |
| => record | new record to insert | 
| -> [SqlExpr (Entity record) -> SqlExpr Update] | updates to perform if the record already exists | 
| -> ReaderT SqlBackend m (Maybe (Entity record)) | the record in the database after the operation | 
Like upsert, but permits an empty list of updates to be performed.
If no updates are provided and the record already was present in the
 database, then this will return Nothing. If you want to fetch the
 record out of the database, you can write:
 mresult <- upsertMaybe record []
 case mresult of
     Nothing ->
         getBy (onlyUniqueP record)
     Just res ->
         pure (Just res)
Since: 3.6.0.0
Arguments
| :: (MonadIO m, PersistEntity record, IsPersistBackend (PersistEntityBackend record), HasCallStack) | |
| => Unique record | uniqueness constraint to find by | 
| -> record | new record to insert | 
| -> NonEmpty (SqlExpr (Entity record) -> SqlExpr Update) | updates to perform if the record already exists | 
| -> ReaderT SqlBackend m (Entity record) | the record in the database after the operation | 
Arguments
| :: (MonadIO m, PersistEntity record, IsPersistBackend (PersistEntityBackend record)) | |
| => Unique record | uniqueness constraint to find by | 
| -> record | new record to insert | 
| -> [SqlExpr (Entity record) -> SqlExpr Update] | updates to perform if the record already exists | 
| -> ReaderT SqlBackend m (Maybe (Entity record)) | the record in the database after the operation | 
insertSelectWithConflict Source #
Arguments
| :: forall a m val backend. (FinalResult a, KnowResult a ~ Unique val, MonadIO m, PersistEntity val, SqlBackendCanWrite backend) | |
| => a | Unique constructor or a unique, this is used just to get the name of the postgres constraint, the value(s) is(are) never used, so if you have a unique "MyUnique 0", "MyUnique undefined" would work as well. | 
| -> SqlQuery (SqlExpr (Insertion val)) | Insert query. | 
| -> (SqlExpr (Entity val) -> SqlExpr (Entity val) -> [SqlExpr (Entity val) -> SqlExpr Update]) | A list of updates to be applied in case of the constraint being violated. The expression takes the current and excluded value to produce the updates. | 
| -> ReaderT backend m () | 
Inserts into a table the results of a query similar to insertSelect but allows
 to update values that violate a constraint during insertions.
Example of usage:
mkPersistsqlSettings[persistLowerCase| Bar num Int deriving Eq Show Foo num Int UniqueFoo num deriving Eq Show |] action = doinsertSelectWithConflictUniqueFoo -- (UniqueFoo undefined) or (UniqueFoo anyNumber) would also work (do b <- from $ table @Bar return $ Foo <# (b ^. BarNum) ) (\current excluded -> [FooNum =. (current ^. FooNum) +. (excluded ^. FooNum)] )
Inserts to table Foo all Bar.num values and in case of conflict SomeFooUnique,
 the conflicting value is updated to the current plus the excluded.
Since: 3.1.3
insertSelectWithConflictCount :: forall a val m backend. (FinalResult a, KnowResult a ~ Unique val, MonadIO m, PersistEntity val, SqlBackendCanWrite backend) => a -> SqlQuery (SqlExpr (Insertion val)) -> (SqlExpr (Entity val) -> SqlExpr (Entity val) -> [SqlExpr (Entity val) -> SqlExpr Update]) -> ReaderT backend m Int64 Source #
Same as insertSelectWithConflict but returns the number of rows affected.
Since: 3.1.3
noWait :: OnLockedBehavior Source #
NOWAIT syntax for postgres locking
 error will be thrown if locked rows are attempted to be selected
Since: 3.5.9.0
wait :: OnLockedBehavior Source #
default behaviour of postgres locks. will attempt to wait for locks to expire
Since: 3.5.9.0
skipLocked :: OnLockedBehavior Source #
`SKIP LOCKED` syntax for postgres locking locked rows will be skipped
Since: 3.5.9.0
forUpdateOf :: LockableEntity a => a -> OnLockedBehavior -> SqlQuery () Source #
`FOR UPDATE OF` syntax for postgres locking allows locking of specific tables with an update lock in a view or join
Since: 3.5.9.0
forNoKeyUpdateOf :: LockableEntity a => a -> OnLockedBehavior -> SqlQuery () Source #
`FOR NO KEY UPDATE OF` syntax for postgres locking allows locking of specific tables with a no key update lock in a view or join
Since: 3.5.13.0
forShareOf :: LockableEntity a => a -> OnLockedBehavior -> SqlQuery () Source #
`FOR SHARE OF` syntax for postgres locking allows locking of specific tables with a share lock in a view or join
Since: 3.5.9.0
forKeyShareOf :: LockableEntity a => a -> OnLockedBehavior -> SqlQuery () Source #
`FOR KEY SHARE OF` syntax for postgres locking allows locking of specific tables with a key share lock in a view or join
Since: 3.5.13.0
Arguments
| :: SqlExpr (Value a) | Aggregate function | 
| -> SqlExpr (Value Bool) | Filter clause | 
| -> SqlExpr (Value a) | 
Allow aggregate functions to take a filter clause.
Example of usage:
share [mkPersist sqlSettings] [persistLowerCase|
  User
    name Text
    deriving Eq Show
  Task
    userId UserId
    completed Bool
    deriving Eq Show
|]
select $ from $ (users InnerJoin tasks) -> do
  on $ users ^. UserId ==. tasks ^. TaskUserId
  groupBy $ users ^. UserId
  return
   ( users ^. UserId
   , count (tasks ^. TaskId) filterWhere (tasks ^. TaskCompleted ==. val True)
   , count (tasks ^. TaskId) filterWhere (tasks ^. TaskCompleted ==. val False)
   )
Since: 3.3.3.3
values :: (ToSomeValues a, ToAliasReference a, ToAlias a) => NonEmpty a -> From a Source #
Allows to use `VALUES (..)` in-memory set of values
 in RHS of from expressions. Useful for JOIN's on
 known values which also can be additionally preprocessed
 somehow on db side with usage of inner PostgreSQL capabilities.
Example of usage:
share [mkPersist sqlSettings] [persistLowerCase|
  User
    name Text
    age Int
    deriving Eq Show
select $ do
 bound :& user <- from $
     values (   (val (10 :: Int), val ("ten" :: Text))
           :| [ (val 20, val "twenty")
              , (val 30, val "thirty") ]
           )
     InnerJoin table User
     on (((bound, _boundName) :& user) -> user^.UserAge >=. bound)
 groupBy bound
 pure (bound, count @Int $ user^.UserName)
Since: 3.5.2.3
ilike :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) -> SqlExpr (Value Bool) Source #
ILIKE operator (case-insensitive LIKE).
Since: 2.2.3
distinctOn :: [SqlExpr DistinctOn] -> SqlQuery () Source #
DISTINCT ON.  Change the current SELECT into
 SELECT DISTINCT ON (SqlExpressions).  For example:
select $ do foo <-from$ table @FoodistinctOn[don(foo ^. FooName),don(foo ^. FooState)] pure foo
You can also chain different calls to distinctOn.  The
 above is equivalent to:
select $ do foo <-from$ table @FoodistinctOn[don(foo ^. FooName)]distinctOn[don(foo ^. FooState)] pure foo
Each call to distinctOn adds more SqlExpressions.  Calls to
 distinctOn override any calls to distinct.
Note that PostgreSQL requires the SqlExpressions on DISTINCT
 ON to be the first ones to appear on a ORDER BY.  This is
 not managed automatically by esqueleto, keeping its spirit
 of trying to be close to raw SQL.
Since: 3.6.0
distinctOnOrderBy :: [SqlExpr OrderBy] -> SqlQuery () Source #
A convenience function that calls both distinctOn and
 orderBy.  In other words,
distinctOnOrderBy [asc foo, desc bar, desc quux]
is the same as:
distinctOn[don foo, don bar, don quux]orderBy[asc foo, desc bar, desc quux] ...
Since: 3.6.0.0
withMaterialized :: (ToAlias a, ToAliasReference a, SqlSelect a r) => SqlQuery a -> SqlQuery (From a) Source #
WITH MATERIALIZED clause is used to introduce a
 Common Table Expression (CTE)
 with the MATERIALIZED keyword. The MATERIALIZED keyword is only supported in PostgreSQL >= version 12.
 In Esqueleto, CTEs should be used as a subquery memoization tactic. PostgreSQL treats a materialized CTE as an optimization fence.
 A materialized CTE is always fully calculated, and is not "inlined" with other table joins.
 Without the MATERIALIZED keyword, PostgreSQL >= 12 may "inline" the CTE as though it was any other join.
 You should always verify that using a materialized CTE will in fact improve your performance
 over a regular subquery.
select $ do cte <- withMaterialized subQuery cteResult <- from cte where_ $ cteResult ... pure cteResult
For more information on materialized CTEs, see the PostgreSQL manual documentation on Common Table Expression Materialization.
Since: 3.5.14.0
withNotMaterialized :: (ToAlias a, ToAliasReference a, SqlSelect a r) => SqlQuery a -> SqlQuery (From a) Source #
WITH NOT MATERIALIZED clause is used to introduce a
 Common Table Expression (CTE)
 with the NOT MATERIALIZED keywords. These are only supported in PostgreSQL >=
 version 12. In Esqueleto, CTEs should be used as a subquery memoization
 tactic. PostgreSQL treats a materialized CTE as an optimization fence. A
 MATERIALIZED CTE is always fully calculated, and is not "inlined" with other
 table joins. Sometimes, this is undesirable, so postgres provides the NOT
 MATERIALIZED modifier to prevent this behavior, thus enabling it to possibly
 decide to treat the CTE as any other join.
Given the above, it is unlikely that this function will be useful, as a normal join should be used instead, but is provided for completeness.
select $ do cte <- withNotMaterialized subQuery cteResult <- from cte where_ $ cteResult ... pure cteResult
For more information on materialized CTEs, see the PostgreSQL manual documentation on Common Table Expression Materialization.
Since: 3.5.14.0
ascNullsFirst :: PersistField a => SqlExpr (Value a) -> SqlExpr OrderBy Source #
Ascending order of this field or SqlExpression with nulls coming first.
Since: 3.5.14.0
ascNullsLast :: PersistField a => SqlExpr (Value a) -> SqlExpr OrderBy Source #
Ascending order of this field or SqlExpression with nulls coming last. Note that this is the same as normal ascending ordering in Postgres, but it has been included for completeness.
Since: 3.5.14.0
descNullsFirst :: PersistField a => SqlExpr (Value a) -> SqlExpr OrderBy Source #
Descending order of this field or SqlExpression with nulls coming first. Note that this is the same as normal ascending ordering in Postgres, but it has been included for completeness.
Since: 3.5.14.0
descNullsLast :: PersistField a => SqlExpr (Value a) -> SqlExpr OrderBy Source #
Descending order of this field or SqlExpression with nulls coming last.
Since: 3.5.14.0
Internal
unsafeSqlAggregateFunction :: UnsafeSqlFunctionArgument a => Builder -> AggMode -> a -> [OrderByClause] -> SqlExpr (Value b) Source #
(Internal) Create a custom aggregate functions with aggregate mode
Do not use this function directly, instead define a new function and give
 it a type (see unsafeSqlBinOp)