Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Database.Persist.Sql.Lifted.Query
Synopsis
- data SqlQuery a
- where_ :: SqlExpr (Value Bool) -> SqlQuery ()
- groupBy :: ToSomeValues a => a -> SqlQuery ()
- groupBy_ :: ToSomeValues a => a -> SqlQuery ()
- having :: SqlExpr (Value Bool) -> SqlQuery ()
- limit :: Int64 -> SqlQuery ()
- offset :: Int64 -> SqlQuery ()
- distinct :: SqlQuery a -> SqlQuery a
- distinctOn :: [SqlExpr DistinctOn] -> SqlQuery a -> SqlQuery a
- orderBy :: [SqlExpr OrderBy] -> SqlQuery ()
- don :: SqlExpr (Value a) -> SqlExpr DistinctOn
- distinctOnOrderBy :: [SqlExpr OrderBy] -> SqlQuery a -> SqlQuery a
- set :: PersistEntity val => SqlExpr (Entity val) -> [SqlExpr (Entity val) -> SqlExpr Update] -> SqlQuery ()
- withNonNull :: PersistField typ => SqlExpr (Value (Maybe typ)) -> (SqlExpr (Value typ) -> SqlQuery a) -> SqlQuery a
- locking :: LockingKind -> SqlQuery ()
- data LockingKind
- union_ :: Union_ a => a
- unionAll_ :: UnionAll_ a => a
- except_ :: (ToSqlSetOperation a a', ToSqlSetOperation b a') => a -> b -> SqlSetOperation a'
- intersect_ :: (ToSqlSetOperation a a', ToSqlSetOperation b a') => a -> b -> SqlSetOperation a'
- with :: (ToAlias a, ToAliasReference a, SqlSelect a r) => SqlQuery a -> SqlQuery (From a)
- withRecursive :: (ToAlias a, ToAliasReference a, SqlSelect a r) => SqlQuery a -> UnionKind -> (From a -> SqlQuery a) -> SqlQuery (From a)
Type
SQL backend for esqueleto
using SqlPersistT
.
Instances
Where
Aggregate
groupBy :: ToSomeValues a => a -> SqlQuery () #
GROUP BY
clause. You can enclose multiple columns
in a tuple.
select $from
\(foo `InnerJoin
` bar) -> doon
(foo^.
FooBarId==.
bar^.
BarId)groupBy
(bar^.
BarId, bar^.
BarName) return (bar^.
BarId, bar^.
BarName, countRows)
With groupBy you can sort by aggregate functions, like so
(we used let
to restrict the more general countRows
to
SqlSqlExpr (Value Int)
to avoid ambiguity---the second use of
countRows
has its type restricted by the :: Int
below):
r <- select $from
\(foo `InnerJoin
` bar) -> doon
(foo^.
FooBarId==.
bar^.
BarId)groupBy
$ bar^.
BarName let countRows' =countRows
orderBy
[asc
countRows'] return (bar^.
BarName, countRows') forM_ r $ \(Value
name,Value
count) -> do print name print (count :: Int)
Need more columns?
The ToSomeValues
class is defined for SqlExpr
and tuples of SqlExpr
s.
We only have definitions for up to 8 elements in a tuple right now, so it's
possible that you may need to have more than 8 elements.
For example, consider a query with a groupBy
call like this:
groupBy (e0, e1, e2, e3, e4, e5, e6, e7)
This is the biggest you can get with a single tuple. However, you can easily nest the tuples to add more:
groupBy ((e0, e1, e2, e3, e4, e5, e6, e7), e8, e9)
groupBy_ :: ToSomeValues a => a -> SqlQuery () #
Limit & offset
Distinct & order by
distinctOn :: [SqlExpr DistinctOn] -> SqlQuery a -> SqlQuery a #
DISTINCT ON
. Change the current SELECT
into
SELECT DISTINCT ON (SqlExpressions)
. For example:
select $from
\foo ->distinctOn
[don
(foo ^. FooName),don
(foo ^. FooState)] $ do ...
You can also chain different calls to distinctOn
. The
above is equivalent to:
select $from
\foo ->distinctOn
[don
(foo ^. FooName)] $distinctOn
[don
(foo ^. FooState)] $ do ...
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.
Supported by PostgreSQL only.
Since: esqueleto-2.2.4
orderBy :: [SqlExpr OrderBy] -> SqlQuery () #
ORDER BY
clause. See also asc
and desc
.
Multiple calls to orderBy
get concatenated on the final
query, including distinctOnOrderBy
.
don :: SqlExpr (Value a) -> SqlExpr DistinctOn #
Erase an SqlExpression's type so that it's suitable to
be used by distinctOn
.
Since: esqueleto-2.2.4
distinctOnOrderBy :: [SqlExpr OrderBy] -> SqlQuery a -> SqlQuery a #
A convenience function that calls both distinctOn
and
orderBy
. In other words,
distinctOnOrderBy
[asc foo, desc bar, desc quux] $ do
...
is the same as:
distinctOn
[don foo, don bar, don quux] $ doorderBy
[asc foo, desc bar, desc quux] ...
Since: esqueleto-2.2.4
Update
set :: PersistEntity val => SqlExpr (Entity val) -> [SqlExpr (Entity val) -> SqlExpr Update] -> SqlQuery () #
SET
clause used on UPDATE
s. Note that while it's not
a type error to use this function on a SELECT
, it will
most certainly result in a runtime error.
withNonNull
withNonNull :: PersistField typ => SqlExpr (Value (Maybe typ)) -> (SqlExpr (Value typ) -> SqlQuery a) -> SqlQuery a #
Project an SqlExpression that may be null, guarding against null cases.
Locking
locking :: LockingKind -> SqlQuery () #
Add a locking clause to the query. Please read
LockingKind
documentation and your RDBMS manual.
Unsafe since not all locking clauses are implemented for every RDBMS
If multiple calls to locking
are made on the same query,
the last one is used.
Since: esqueleto-2.2.7
data LockingKind #
Different kinds of locking clauses supported by locking
.
Note that each RDBMS has different locking support. The
constructors of this datatype specify only the syntax of the
locking mechanism, not its semantics. For example, even
though both MySQL and PostgreSQL support ForUpdate
, there
are no guarantees that they will behave the same.
Since: esqueleto-2.2.7
Constructors
ForUpdate |
Since: esqueleto-2.2.7 |
ForUpdateSkipLocked |
Since: esqueleto-2.2.7 |
ForShare |
Since: esqueleto-2.2.7 |
LockInShareMode |
Since: esqueleto-2.2.7 |
Set operations
UNION
SQL set operation. Can be used as an infix function between SqlQuery
values.
unionAll_ :: UnionAll_ a => a #
UNION
ALL
SQL set operation. Can be used as an infix function between SqlQuery
values.
except_ :: (ToSqlSetOperation a a', ToSqlSetOperation b a') => a -> b -> SqlSetOperation a' #
EXCEPT
SQL set operation. Can be used as an infix function between SqlQuery
values.
intersect_ :: (ToSqlSetOperation a a', ToSqlSetOperation b a') => a -> b -> SqlSetOperation a' #
INTERSECT
SQL set operation. Can be used as an infix function between SqlQuery
values.
Common table expressions
with :: (ToAlias a, ToAliasReference a, SqlSelect a r) => SqlQuery a -> SqlQuery (From a) #
WITH
clause used to introduce a Common Table Expression (CTE).
CTEs are supported in most modern SQL engines and can be useful
in performance tuning. In Esqueleto, CTEs should be used as a
subquery memoization tactic. When writing plain SQL, CTEs
are sometimes used to organize the SQL code, in Esqueleto, this
is better achieved through function that return SqlQuery
values.
select $ do cte <- with subQuery cteResult <- from cte where_ $ cteResult ... pure cteResult
WARNING: In some SQL engines using a CTE can diminish performance. In these engines the CTE is treated as an optimization fence. You should always verify that using a CTE will in fact improve your performance over a regular subquery.
Notably, in PostgreSQL prior to version 12, CTEs are always fully
calculated, which can potentially significantly pessimize queries. As of
PostgreSQL 12, non-recursive and side-effect-free queries may be inlined and
optimized accordingly if not declared MATERIALIZED
to get the previous
behaviour. See the PostgreSQL CTE documentation,
section Materialization, for more information. To use a MATERIALIZED
query
in Esquelto, see functions withMaterialized
and withRecursiveMaterialized
.
Since: 3.4.0.0
withRecursive :: (ToAlias a, ToAliasReference a, SqlSelect a r) => SqlQuery a -> UnionKind -> (From a -> SqlQuery a) -> SqlQuery (From a) #
WITH
RECURSIVE
allows one to make a recursive subquery, which can
reference itself. Like WITH
, this is supported in most modern SQL engines.
Useful for hierarchical, self-referential data, like a tree of data.
select $ do cte <- withRecursive (do person <- from $ table @Person where_ $ person ^. PersonId ==. val personId pure person ) unionAll_ (\self -> do (p :& f :& p2 :& pSelf) <- from self `innerJoin` $ table @Follow `on` (\(p :& f) -> p ^. PersonId ==. f ^. FollowFollower) `innerJoin` $ table @Person `on` (\(p :& f :& p2) -> f ^. FollowFollowed ==. p2 ^. PersonId) `leftJoin` self `on` (\(_ :& _ :& p2 :& pSelf) -> just (p2 ^. PersonId) ==. pSelf ?. PersonId) where_ $ isNothing (pSelf ?. PersonId) groupBy (p2 ^. PersonId) pure p2 ) from cte
Since: 3.4.0.0