persistent-sql-lifted-0.4.3.1: Monad classes for running queries with Persistent and Esqueleto
Safe HaskellSafe-Inferred
LanguageGHC2021

Database.Persist.Sql.Lifted.Query

Synopsis

Type

data SqlQuery a #

SQL backend for esqueleto using SqlPersistT.

Instances

Instances details
Applicative SqlQuery 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

pure :: a -> SqlQuery a #

(<*>) :: SqlQuery (a -> b) -> SqlQuery a -> SqlQuery b #

liftA2 :: (a -> b -> c) -> SqlQuery a -> SqlQuery b -> SqlQuery c #

(*>) :: SqlQuery a -> SqlQuery b -> SqlQuery b #

(<*) :: SqlQuery a -> SqlQuery b -> SqlQuery a #

Functor SqlQuery 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

fmap :: (a -> b) -> SqlQuery a -> SqlQuery b #

(<$) :: a -> SqlQuery b -> SqlQuery a #

Monad SqlQuery 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

(>>=) :: SqlQuery a -> (a -> SqlQuery b) -> SqlQuery b #

(>>) :: SqlQuery a -> SqlQuery b -> SqlQuery b #

return :: a -> SqlQuery a #

(ToFrom a a', SqlSelect b r, ToAlias b, ToAliasReference b, d ~ (a' :& b)) => DoInnerJoin Lateral a (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) d 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doInnerJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) -> From d #

(ToFrom a a', ToMaybe b, d ~ (a' :& ToMaybeT b), SqlSelect b r, ToAlias b, ToAliasReference b) => DoLeftJoin Lateral a (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) d 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doLeftJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) -> From d #

(ToFrom a a', SqlSelect b r, ToAlias b, ToAliasReference b) => DoCrossJoin Lateral a (a' -> SqlQuery b) (a' :& b) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doCrossJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b) -> From (a' :& b) #

(SqlSelect a r, ToAlias a, ToAliasReference a) => ToFrom (SqlQuery a) a 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: SqlQuery a -> From a #

(SqlSelect a r, ToAlias a, ToAliasReference a) => ToSqlSetOperation (SqlQuery a) a 
Instance details

Defined in Database.Esqueleto.Experimental.From.SqlSetOperation

ValidOnClause (a -> SqlQuery b) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Where

where_ :: SqlExpr (Value Bool) -> SqlQuery () #

WHERE clause: restrict the query's result.

Aggregate

groupBy :: ToSomeValues a => a -> SqlQuery () #

GROUP BY clause. You can enclose multiple columns in a tuple.

select $ from \(foo `InnerJoin` bar) -> do
  on (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) -> do
  on (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 SqlExprs. 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 () #

An alias for groupBy that avoids conflict with the term from Data.List groupBy.

Since: esqueleto-3.5.10.0

having :: SqlExpr (Value Bool) -> SqlQuery () #

HAVING.

Since: esqueleto-1.2.2

Limit & offset

limit :: Int64 -> SqlQuery () #

LIMIT. Limit the number of returned rows.

offset :: Int64 -> SqlQuery () #

OFFSET. Usually used with limit.

Distinct & order by

distinct :: SqlQuery a -> SqlQuery a #

DISTINCT. Change the current SELECT into SELECT DISTINCT. For example:

select $ distinct $
  from \foo -> do
  ...

Note that this also has the same effect:

select $
  from \foo -> do
  distinct (return ())
  ...

Since: esqueleto-2.2.4

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] $ do
  orderBy  [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 UPDATEs. 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

FOR UPDATE syntax. Supported by MySQL, Oracle and PostgreSQL.

Since: esqueleto-2.2.7

ForUpdateSkipLocked

FOR UPDATE SKIP LOCKED syntax. Supported by MySQL, Oracle and PostgreSQL.

Since: esqueleto-2.2.7

ForShare

FOR SHARE syntax. Supported by PostgreSQL.

Since: esqueleto-2.2.7

LockInShareMode

LOCK IN SHARE MODE syntax. Supported by MySQL.

Since: esqueleto-2.2.7

Set operations

union_ :: Union_ a => a #

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