esqueleto-compat-0.0.2.0: Compatibility operators for Persistent and Esqueleto
Safe HaskellSafe-Inferred
LanguageHaskell2010

Database.Esqueleto.Compat

Description

This package aims to provide compatibility operators for esqueleto and persistent such that you can import Database.Esqueleto.Compat without name conflicts.

This module re-exports Database.Persist.Sql and Database.Esqueleto.Experimental together and hides the conflicting terms in each module. Then we expose compatibility operators (like ==.) that can work in either context, and names with suffixes to avoid conflicts for other things (like updateE instead of update).

Synopsis

The compatibility operators

Re-exports from Database.Esqueleto.Experimental

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

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.

Since: 3.4.0.0

getTableMaybe :: GetFirstTable (SqlExpr (Maybe (Entity t))) ts => ts -> SqlExpr (Maybe (Entity t)) #

A variant of getTable that operates on possibly-null entities.

Since: esqueleto-3.5.9.0

getTable :: GetFirstTable (SqlExpr (Entity t)) ts => ts -> SqlExpr (Entity t) #

Get the first table of a given type from a chain of tables joined with (:&).

This can make it easier to write queries with a large number of join clauses:

select $ do
(people :& followers :& blogPosts) <-
    from $ table @Person
    `innerJoin` table @Follow
    `on` (\(person :& follow) ->
            person ^. PersonId ==. follow ^. FollowFollowed)
    `innerJoin` table @BlogPost
    `on` (\((getTable @Follow -> follow) :& blogPost) ->
            blogPost ^. BlogPostAuthorId ==. follow ^. FollowFollower)
where_ (people1 ^. PersonName ==. val "John")
pure (followers, people2)

This example is a bit trivial, but once you've joined five or six tables it becomes enormously helpful. The above example uses a ViewPattern to call the function and assign the variable directly, but you can also imagine it being written like this:

    `on` (\(prev :& blogPost) ->
            let
                follow = getTable @Follow prev
             in
                blogPost ^. BlogPostAuthorId ==. follow ^. FollowFollower)

This function will pluck out the first table that matches the applied type, so if you join on the same table multiple times, it will always select the first one provided.

The (:&) operator associates so that the left hand side can be a wildcard for an arbitrary amount of nesting, and the "most recent" or "newest" table in a join sequence is always available on the rightmost - so (prev :& bar) is a pattern that matches bar table (the most recent table added) and prev tables (all prior tables in the join match).

By calling getTable on the prev, you can select exactly the table you want, allowing you to omit a large number of spurious pattern matches. Consider a query that does several LEFT JOIN on a first table:

SELECT *
FROM person
LEFT JOIN car
  ON person.id = car.person_id
LEFT JOIN bike
  ON person.id = bike.person_id
LEFT JOIN food
  ON person.id = food.person_id
LEFT JOIN address
  ON person.id = address.person_id

The final on clause in esqueleto would look like this:

    `on` do
        \(person :& _car :& _bike :& _food :& address) ->
            person.id ==. address.personId

First, we can change it to a prev :& newest match. We can do this because of the operator associativity. This is kind of like how a list : operator associates, but in the other direction: a : (b : c) = a : b : c.

    `on` do
        \(prev :& address) ->
            let (person :& _car :& _bike :& _food) = prev
             in person.id ==. address.personId

Then, we can use getTable to select the Person table directly, instead of pattern matching manually.

    `on` do
        \(prev :& address) ->
            let person = getTable @Person prev
             in person.id ==. address.personId

Finally, we can use a ViewPattern language extension to "inline" the access.

    `on` do
        \((getTable @Person -> person) :& address) ->
           person.id ==. address.personId

With this form, you do not need to be concerned about the number and wildcard status of tables that do not matter to the specific ON clause.

Since: esqueleto-3.5.9.0

fullOuterJoin :: (ToFrom a a', ToFrom b b', ToMaybe a', ToMaybe b', HasOnClause rhs (ToMaybeT a' :& ToMaybeT b'), rhs ~ (b, (ToMaybeT a' :& ToMaybeT b') -> SqlExpr (Value Bool))) => a -> rhs -> From (ToMaybeT a' :& ToMaybeT b') infixl 2 #

FULL OUTER JOIN

Join where both sides of the join may not exist. Because of this the result needs to be handled as a Maybe

Used as an infix operator `fullOuterJoin`

select $
from $ table @Person
`fullOuterJoin` table @BlogPost
`on` (\(p :& bp) ->
        p ?. PersonId ==. bp ?. BlogPostAuthorId)

Since: esqueleto-3.5.0.0

rightJoin :: (ToFrom a a', ToFrom b b', ToMaybe a', HasOnClause rhs (ToMaybeT a' :& b'), rhs ~ (b, (ToMaybeT a' :& b') -> SqlExpr (Value Bool))) => a -> rhs -> From (ToMaybeT a' :& b') infixl 2 #

RIGHT OUTER JOIN

Join where the left side may not exist. If the on clause fails then the left side will be NULL'ed Because of this the left side needs to be handled as a Maybe

Used as an infix operator `rightJoin`

select $
from $ table @Person
`rightJoin` table @BlogPost
`on` (\(p :& bp) ->
        p ?. PersonId ==. bp ^. BlogPostAuthorId)

Since: esqueleto-3.5.0.0

leftJoinLateral :: (ToFrom a a', SqlSelect b r, HasOnClause rhs (a' :& ToMaybeT b), ToAlias b, ToAliasReference b, ToMaybe b, rhs ~ (a' -> SqlQuery b, (a' :& ToMaybeT b) -> SqlExpr (Value Bool))) => a -> rhs -> From (a' :& ToMaybeT b) infixl 2 #

LEFT OUTER JOIN LATERAL

Lateral join where the right side may not exist. In the case that the query returns nothing or the on clause fails the right side of the join will be NULL'ed Because of this the right side needs to be handled as a Maybe

Used as an infix operator `leftJoinLateral`

See example 6 for how to use LATERAL

Since: esqueleto-3.5.0.0

leftJoin :: (ToFrom a a', ToFrom b b', ToMaybe b', HasOnClause rhs (a' :& ToMaybeT b'), rhs ~ (b, (a' :& ToMaybeT b') -> SqlExpr (Value Bool))) => a -> rhs -> From (a' :& ToMaybeT b') infixl 2 #

LEFT OUTER JOIN

Join where the right side may not exist. If the on clause fails then the right side will be NULL'ed Because of this the right side needs to be handled as a Maybe

Used as an infix operator `leftJoin`

select $
from $ table @Person
`leftJoin` table @BlogPost
`on` (\(p :& bp) ->
        just (p ^. PersonId) ==. bp ?. BlogPostAuthorId)

Since: esqueleto-3.5.0.0

crossJoinLateral :: (ToFrom a a', SqlSelect b r, ToAlias b, ToAliasReference b) => a -> (a' -> SqlQuery b) -> From (a' :& b) infixl 2 #

CROSS JOIN LATERAL

A Lateral subquery join allows the joined query to reference entities from the left hand side of the join.

Used as an infix operator `crossJoinLateral`

See example 6

Since: esqueleto-3.5.0.0

crossJoin :: (ToFrom a a', ToFrom b b') => a -> b -> From (a' :& b') infixl 2 #

CROSS JOIN

Used as an infix `crossJoin`

select $ do
from $ table @Person
`crossJoin` table @BlogPost

Since: esqueleto-3.5.0.0

innerJoinLateral :: (ToFrom a a', HasOnClause rhs (a' :& b), SqlSelect b r, ToAlias b, ToAliasReference b, rhs ~ (a' -> SqlQuery b, (a' :& b) -> SqlExpr (Value Bool))) => a -> rhs -> From (a' :& b) infixl 2 #

INNER JOIN LATERAL

A Lateral subquery join allows the joined query to reference entities from the left hand side of the join. Discards rows that don't match the on clause

Used as an infix operator `innerJoinLateral`

See example 6

Since: esqueleto-3.5.0.0

innerJoin :: (ToFrom a a', ToFrom b b', HasOnClause rhs (a' :& b'), rhs ~ (b, (a' :& b') -> SqlExpr (Value Bool))) => a -> rhs -> From (a' :& b') infixl 2 #

INNER JOIN

Used as an infix operator `innerJoin`

select $
from $ table @Person
`innerJoin` table @BlogPost
`on` (\(p :& bp) ->
        p ^. PersonId ==. bp ^. BlogPostAuthorId)

Since: esqueleto-3.5.0.0

on :: ValidOnClause a => a -> (b -> SqlExpr (Value Bool)) -> (a, b -> SqlExpr (Value Bool)) infix 9 #

An ON clause that describes how two tables are related. This should be used as an infix operator after a JOIN. For example,

select $
from $ table @Person
`innerJoin` table @BlogPost
`on` (\(p :& bP) ->
        p ^. PersonId ==. bP ^. BlogPostAuthorId)

class GetFirstTable t ts where #

Typeclass for selecting tables using type application syntax.

If you have a long chain of tables joined with (:&), like a :& b :& c :& d, then getTable @c (a :& b :& c :& d) will give you the c table back.

Note that this typeclass will only select the first table of the given type; it may be less useful if there's multiple tables of the same type.

Since: esqueleto-3.5.9.0

Methods

getFirstTable :: ts -> t #

Get the first table of type t from the tables ts.

Since: esqueleto-3.5.9.0

Instances

Instances details
GetFirstTable t (t :& ts) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

getFirstTable :: (t :& ts) -> t #

GetFirstTable t ts => GetFirstTable t (ts :& x) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

getFirstTable :: (ts :& x) -> t #

GetFirstTable t (x :& t) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

getFirstTable :: (x :& t) -> t #

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.

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.

pattern SelectQuery :: p -> p #

class ToSqlSetOperation a r | a -> r where #

Type class to support direct use of SqlQuery in a set operation tree

Since: esqueleto-3.5.0.0

data Union a b #

Constructors

a `Union` b 

Instances

Instances details
ToSqlSetOperation a a' => ToSqlSetOperation (Union a a) a' 
Instance details

Defined in Database.Esqueleto.Experimental.From.SqlSetOperation

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.

data UnionAll a b #

Constructors

a `UnionAll` b 

Instances

Instances details
ToSqlSetOperation a a' => ToSqlSetOperation (UnionAll a a) a' 
Instance details

Defined in Database.Esqueleto.Experimental.From.SqlSetOperation

data Except a b #

Constructors

a `Except` b 

Instances

Instances details
ToSqlSetOperation a a' => ToSqlSetOperation (Except a a) a' 
Instance details

Defined in Database.Esqueleto.Experimental.From.SqlSetOperation

data Intersect a b #

Constructors

a `Intersect` b 

Instances

Instances details
ToSqlSetOperation a a' => ToSqlSetOperation (Intersect a a) a' 
Instance details

Defined in Database.Esqueleto.Experimental.From.SqlSetOperation

selectQuery :: (SqlSelect a r, ToAlias a, ToAliasReference a) => SqlQuery a -> From a #

Select from a subquery, often used in conjuction with joins but can be used without any joins. Because SqlQuery has a ToFrom instance you probably dont need to use this function directly.

select $
     p <- from $
             selectQuery do
             p <- from $ table @Person
             limit 5
             orderBy [ asc p ^. PersonAge ]
     ...

Since: esqueleto-3.5.0.0

table :: PersistEntity ent => From (SqlExpr (Entity ent)) #

Bring a PersistEntity into scope from a table

select $ from $ table @People

Since: esqueleto-3.5.0.0

from :: ToFrom a a' => a -> SqlQuery a' #

FROM clause, used to bring entities into scope.

Internally, this function uses the From datatype. Unlike the old from, this does not take a function as a parameter, but rather a value that represents a JOIN tree constructed out of instances of From. This implementation eliminates certain types of runtime errors by preventing the construction of invalid SQL (e.g. illegal nested-from).

newtype From a #

Data type defining the From language. This should not constructed directly in application code.

A From is a SqlQuery which returns a reference to the result of calling from and a function that produces a portion of a FROM clause. This gets passed to the FromRaw FromClause constructor directly when converting from a From to a SqlQuery using from

Since: esqueleto-3.5.0.0

Constructors

From 

Fields

Instances

Instances details
ToFrom (From a) a 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: From a -> From a #

data Table a #

Constructors

Table 

Instances

Instances details
PersistEntity ent => ToFrom (Table ent) (SqlExpr (Entity ent)) 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: Table ent -> From (SqlExpr (Entity ent)) #

newtype SubQuery a #

Constructors

SubQuery a 

Instances

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

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: SubQuery (SqlQuery a) -> From a #

type ToAliasT a = a #

class ToAlias a where #

Methods

toAlias :: a -> SqlQuery a #

Instances

Instances details
ToAlias (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: SqlExpr (Value a) -> SqlQuery (SqlExpr (Value a)) #

ToAlias (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: SqlExpr (Entity a) -> SqlQuery (SqlExpr (Entity a)) #

ToAlias (SqlExpr (Maybe (Entity a))) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: SqlExpr (Maybe (Entity a)) -> SqlQuery (SqlExpr (Maybe (Entity a))) #

(ToAlias a, ToAlias b) => ToAlias (a, b) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

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

(ToAlias a, ToAlias b, ToAlias c) => ToAlias (a, b, c) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: (a, b, c) -> SqlQuery (a, b, c) #

(ToAlias a, ToAlias b, ToAlias c, ToAlias d) => ToAlias (a, b, c, d) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: (a, b, c, d) -> SqlQuery (a, b, c, d) #

(ToAlias a, ToAlias b, ToAlias c, ToAlias d, ToAlias e) => ToAlias (a, b, c, d, e) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: (a, b, c, d, e) -> SqlQuery (a, b, c, d, e) #

(ToAlias a, ToAlias b, ToAlias c, ToAlias d, ToAlias e, ToAlias f) => ToAlias (a, b, c, d, e, f) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: (a, b, c, d, e, f) -> SqlQuery (a, b, c, d, e, f) #

(ToAlias a, ToAlias b, ToAlias c, ToAlias d, ToAlias e, ToAlias f, ToAlias g) => ToAlias (a, b, c, d, e, f, g) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: (a, b, c, d, e, f, g) -> SqlQuery (a, b, c, d, e, f, g) #

(ToAlias a, ToAlias b, ToAlias c, ToAlias d, ToAlias e, ToAlias f, ToAlias g, ToAlias h) => ToAlias (a, b, c, d, e, f, g, h) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: (a, b, c, d, e, f, g, h) -> SqlQuery (a, b, c, d, e, f, g, h) #

(ToAlias a, ToAlias b, ToAlias c, ToAlias d, ToAlias e, ToAlias f, ToAlias g, ToAlias h, ToAlias i) => ToAlias (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: (a, b, c, d, e, f, g, h, i) -> SqlQuery (a, b, c, d, e, f, g, h, i) #

(ToAlias a, ToAlias b, ToAlias c, ToAlias d, ToAlias e, ToAlias f, ToAlias g, ToAlias h, ToAlias i, ToAlias j) => ToAlias (a, b, c, d, e, f, g, h, i, j) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: (a, b, c, d, e, f, g, h, i, j) -> SqlQuery (a, b, c, d, e, f, g, h, i, j) #

(ToAlias a, ToAlias b, ToAlias c, ToAlias d, ToAlias e, ToAlias f, ToAlias g, ToAlias h, ToAlias i, ToAlias j, ToAlias k) => ToAlias (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: (a, b, c, d, e, f, g, h, i, j, k) -> SqlQuery (a, b, c, d, e, f, g, h, i, j, k) #

(ToAlias a, ToAlias b, ToAlias c, ToAlias d, ToAlias e, ToAlias f, ToAlias g, ToAlias h, ToAlias i, ToAlias j, ToAlias k, ToAlias l) => ToAlias (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: (a, b, c, d, e, f, g, h, i, j, k, l) -> SqlQuery (a, b, c, d, e, f, g, h, i, j, k, l) #

(ToAlias a, ToAlias b, ToAlias c, ToAlias d, ToAlias e, ToAlias f, ToAlias g, ToAlias h, ToAlias i, ToAlias j, ToAlias k, ToAlias l, ToAlias m) => ToAlias (a, b, c, d, e, f, g, h, i, j, k, l, m) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> SqlQuery (a, b, c, d, e, f, g, h, i, j, k, l, m) #

(ToAlias a, ToAlias b, ToAlias c, ToAlias d, ToAlias e, ToAlias f, ToAlias g, ToAlias h, ToAlias i, ToAlias j, ToAlias k, ToAlias l, ToAlias m, ToAlias n) => ToAlias (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> SqlQuery (a, b, c, d, e, f, g, h, i, j, k, l, m, n) #

(ToAlias a, ToAlias b, ToAlias c, ToAlias d, ToAlias e, ToAlias f, ToAlias g, ToAlias h, ToAlias i, ToAlias j, ToAlias k, ToAlias l, ToAlias m, ToAlias n, ToAlias o) => ToAlias (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> SqlQuery (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) #

(ToAlias a, ToAlias b, ToAlias c, ToAlias d, ToAlias e, ToAlias f, ToAlias g, ToAlias h, ToAlias i, ToAlias j, ToAlias k, ToAlias l, ToAlias m, ToAlias n, ToAlias o, ToAlias p) => ToAlias (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> SqlQuery (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) #

type ToAliasReferenceT a = a #

class ToAliasReference a where #

Methods

toAliasReference :: Ident -> a -> SqlQuery a #

Instances

Instances details
ToAliasReference (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToAliasReference (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToAliasReference (SqlExpr (Maybe (Entity a))) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

(ToAliasReference a, ToAliasReference b) => ToAliasReference (a, b) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

toAliasReference :: Ident -> (a, b) -> SqlQuery (a, b) #

(ToAliasReference a, ToAliasReference b, ToAliasReference c) => ToAliasReference (a, b, c) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

toAliasReference :: Ident -> (a, b, c) -> SqlQuery (a, b, c) #

(ToAliasReference a, ToAliasReference b, ToAliasReference c, ToAliasReference d) => ToAliasReference (a, b, c, d) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

toAliasReference :: Ident -> (a, b, c, d) -> SqlQuery (a, b, c, d) #

(ToAliasReference a, ToAliasReference b, ToAliasReference c, ToAliasReference d, ToAliasReference e) => ToAliasReference (a, b, c, d, e) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

toAliasReference :: Ident -> (a, b, c, d, e) -> SqlQuery (a, b, c, d, e) #

(ToAliasReference a, ToAliasReference b, ToAliasReference c, ToAliasReference d, ToAliasReference e, ToAliasReference f) => ToAliasReference (a, b, c, d, e, f) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

toAliasReference :: Ident -> (a, b, c, d, e, f) -> SqlQuery (a, b, c, d, e, f) #

(ToAliasReference a, ToAliasReference b, ToAliasReference c, ToAliasReference d, ToAliasReference e, ToAliasReference f, ToAliasReference g) => ToAliasReference (a, b, c, d, e, f, g) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

toAliasReference :: Ident -> (a, b, c, d, e, f, g) -> SqlQuery (a, b, c, d, e, f, g) #

(ToAliasReference a, ToAliasReference b, ToAliasReference c, ToAliasReference d, ToAliasReference e, ToAliasReference f, ToAliasReference g, ToAliasReference h) => ToAliasReference (a, b, c, d, e, f, g, h) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

toAliasReference :: Ident -> (a, b, c, d, e, f, g, h) -> SqlQuery (a, b, c, d, e, f, g, h) #

(ToAliasReference a, ToAliasReference b, ToAliasReference c, ToAliasReference d, ToAliasReference e, ToAliasReference f, ToAliasReference g, ToAliasReference h, ToAliasReference i) => ToAliasReference (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

toAliasReference :: Ident -> (a, b, c, d, e, f, g, h, i) -> SqlQuery (a, b, c, d, e, f, g, h, i) #

(ToAliasReference a, ToAliasReference b, ToAliasReference c, ToAliasReference d, ToAliasReference e, ToAliasReference f, ToAliasReference g, ToAliasReference h, ToAliasReference i, ToAliasReference j) => ToAliasReference (a, b, c, d, e, f, g, h, i, j) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

toAliasReference :: Ident -> (a, b, c, d, e, f, g, h, i, j) -> SqlQuery (a, b, c, d, e, f, g, h, i, j) #

(ToAliasReference a, ToAliasReference b, ToAliasReference c, ToAliasReference d, ToAliasReference e, ToAliasReference f, ToAliasReference g, ToAliasReference h, ToAliasReference i, ToAliasReference j, ToAliasReference k) => ToAliasReference (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

toAliasReference :: Ident -> (a, b, c, d, e, f, g, h, i, j, k) -> SqlQuery (a, b, c, d, e, f, g, h, i, j, k) #

(ToAliasReference a, ToAliasReference b, ToAliasReference c, ToAliasReference d, ToAliasReference e, ToAliasReference f, ToAliasReference g, ToAliasReference h, ToAliasReference i, ToAliasReference j, ToAliasReference k, ToAliasReference l) => ToAliasReference (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

toAliasReference :: Ident -> (a, b, c, d, e, f, g, h, i, j, k, l) -> SqlQuery (a, b, c, d, e, f, g, h, i, j, k, l) #

(ToAliasReference a, ToAliasReference b, ToAliasReference c, ToAliasReference d, ToAliasReference e, ToAliasReference f, ToAliasReference g, ToAliasReference h, ToAliasReference i, ToAliasReference j, ToAliasReference k, ToAliasReference l, ToAliasReference m) => ToAliasReference (a, b, c, d, e, f, g, h, i, j, k, l, m) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

toAliasReference :: Ident -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> SqlQuery (a, b, c, d, e, f, g, h, i, j, k, l, m) #

(ToAliasReference a, ToAliasReference b, ToAliasReference c, ToAliasReference d, ToAliasReference e, ToAliasReference f, ToAliasReference g, ToAliasReference h, ToAliasReference i, ToAliasReference j, ToAliasReference k, ToAliasReference l, ToAliasReference m, ToAliasReference n) => ToAliasReference (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

toAliasReference :: Ident -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> SqlQuery (a, b, c, d, e, f, g, h, i, j, k, l, m, n) #

(ToAliasReference a, ToAliasReference b, ToAliasReference c, ToAliasReference d, ToAliasReference e, ToAliasReference f, ToAliasReference g, ToAliasReference h, ToAliasReference i, ToAliasReference j, ToAliasReference k, ToAliasReference l, ToAliasReference m, ToAliasReference n, ToAliasReference o) => ToAliasReference (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

toAliasReference :: Ident -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> SqlQuery (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) #

(ToAliasReference a, ToAliasReference b, ToAliasReference c, ToAliasReference d, ToAliasReference e, ToAliasReference f, ToAliasReference g, ToAliasReference h, ToAliasReference i, ToAliasReference j, ToAliasReference k, ToAliasReference l, ToAliasReference m, ToAliasReference n, ToAliasReference o, ToAliasReference p) => ToAliasReference (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

toAliasReference :: Ident -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> SqlQuery (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) #

type family ToMaybeT a #

Instances

Instances details
type ToMaybeT (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (SqlExpr (Maybe a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (a :& b) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

type ToMaybeT (a :& b) = ToMaybeT a :& ToMaybeT b
type ToMaybeT (a, b) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (a, b) = (ToMaybeT a, ToMaybeT b)
type ToMaybeT (a, b, c) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (a, b, c) = (ToMaybeT a, ToMaybeT b, ToMaybeT c)
type ToMaybeT (a, b, c, d) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (a, b, c, d) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d)
type ToMaybeT (a, b, c, d, e) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (a, b, c, d, e) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e)
type ToMaybeT (a, b, c, d, e, f) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (a, b, c, d, e, f) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e, ToMaybeT f)
type ToMaybeT (a, b, c, d, e, f, g) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (a, b, c, d, e, f, g) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e, ToMaybeT f, ToMaybeT g)
type ToMaybeT (a, b, c, d, e, f, g, h) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (a, b, c, d, e, f, g, h) = (ToMaybeT a, ToMaybeT b, ToMaybeT c, ToMaybeT d, ToMaybeT e, ToMaybeT f, ToMaybeT g, ToMaybeT h)

class ToMaybe a where #

Associated Types

type ToMaybeT a #

Methods

toMaybe :: a -> ToMaybeT a #

Instances

Instances details
ToMaybe (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Value a)) #

Methods

toMaybe :: SqlExpr (Value a) -> ToMaybeT (SqlExpr (Value a)) #

ToMaybe (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Entity a)) #

Methods

toMaybe :: SqlExpr (Entity a) -> ToMaybeT (SqlExpr (Entity a)) #

ToMaybe (SqlExpr (Maybe a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Maybe a)) #

Methods

toMaybe :: SqlExpr (Maybe a) -> ToMaybeT (SqlExpr (Maybe a)) #

(ToMaybe a, ToMaybe b) => ToMaybe (a, b) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (a, b) #

Methods

toMaybe :: (a, b) -> ToMaybeT (a, b) #

(ToMaybe a, ToMaybe b, ToMaybe c) => ToMaybe (a, b, c) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (a, b, c) #

Methods

toMaybe :: (a, b, c) -> ToMaybeT (a, b, c) #

(ToMaybe a, ToMaybe b, ToMaybe c, ToMaybe d) => ToMaybe (a, b, c, d) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (a, b, c, d) #

Methods

toMaybe :: (a, b, c, d) -> ToMaybeT (a, b, c, d) #

(ToMaybe a, ToMaybe b, ToMaybe c, ToMaybe d, ToMaybe e) => ToMaybe (a, b, c, d, e) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (a, b, c, d, e) #

Methods

toMaybe :: (a, b, c, d, e) -> ToMaybeT (a, b, c, d, e) #

(ToMaybe a, ToMaybe b, ToMaybe c, ToMaybe d, ToMaybe e, ToMaybe f) => ToMaybe (a, b, c, d, e, f) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (a, b, c, d, e, f) #

Methods

toMaybe :: (a, b, c, d, e, f) -> ToMaybeT (a, b, c, d, e, f) #

(ToMaybe a, ToMaybe b, ToMaybe c, ToMaybe d, ToMaybe e, ToMaybe f, ToMaybe g) => ToMaybe (a, b, c, d, e, f, g) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (a, b, c, d, e, f, g) #

Methods

toMaybe :: (a, b, c, d, e, f, g) -> ToMaybeT (a, b, c, d, e, f, g) #

(ToMaybe a, ToMaybe b, ToMaybe c, ToMaybe d, ToMaybe e, ToMaybe f, ToMaybe g, ToMaybe h) => ToMaybe (a, b, c, d, e, f, g, h) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (a, b, c, d, e, f, g, h) #

Methods

toMaybe :: (a, b, c, d, e, f, g, h) -> ToMaybeT (a, b, c, d, e, f, g, h) #

associateJoin :: forall e1 e0. Ord (Key e0) => [(Entity e0, e1)] -> Map (Key e0) (e0, [e1]) #

Avoid N+1 queries and join entities into a map structure.

This function is useful to call on the result of a single JOIN. For example, suppose you have this query:

getFoosAndNestedBarsFromParent
    :: ParentId
    -> SqlPersistT IO [(Entity Foo, Maybe (Entity Bar))]
getFoosAndNestedBarsFromParent parentId =
    select $ do
        (foo :& bar) <- from $
            table Foo
            `LeftOuterJoin`
            table Bar
                `on` do
                    \(foo :& bar) ->
                        foo ^. FooId ==. bar ?. BarFooId
        where_ $
            foo ^. FooParentId ==. val parentId
        pure (foo, bar)

This is a natural result type for SQL - a list of tuples. However, it's not what we usually want in Haskell - each Foo in the list will be represented multiple times, once for each Bar.

We can write fmap associateJoin and it will translate it into a Map that is keyed on the Key of the left Entity, and the value is a tuple of the entity's value as well as the list of each coresponding entity.

getFoosAndNestedBarsFromParentHaskellese
    :: ParentId
    -> SqlPersistT (Map (Key Foo) (Foo, [Maybe (Entity Bar)]))
getFoosAndNestedBarsFromParentHaskellese parentId =
    fmap associateJoin $ getFoosdAndNestedBarsFromParent parentId

What if you have multiple joins?

Let's use associateJoin with a *two* join query.

userPostComments
    :: SqlQuery (SqlExpr (Entity User, Entity Post, Entity Comment))
userPostsComment = do
    (u :& p :& c) <- from $
        table User
        `InnerJoin`
        table Post
            on do
                \(u :& p) ->
                    u ^. UserId ==. p ^. PostUserId
        `InnerJoin`
        table @Comment
            `on` do
                \(_ :& p :& c) ->
                    p ^. PostId ==. c ^. CommentPostId
    pure (u, p, c)

This query returns a User, with all of the users Posts, and then all of the Comments on that post.

First, we *nest* the tuple.

nest :: (a, b, c) -> (a, (b, c))
nest (a, b, c) = (a, (b, c))

This makes the return of the query conform to the input expected from associateJoin.

nestedUserPostComments
    :: SqlPersistT IO [(Entity User, (Entity Post, Entity Comment))]
nestedUserPostComments =
    fmap nest $ select userPostsComments

Now, we can call associateJoin on it.

associateUsers
    :: [(Entity User, (Entity Post, Entity Comment))]
    -> Map UserId (User, [(Entity Post, Entity Comment)])
associateUsers =
    associateJoin

Next, we'll use the Functor instances for Map and tuple to call associateJoin on the [(Entity Post, Entity Comment)].

associatePostsAndComments
    :: Map UserId (User, [(Entity Post, Entity Comment)])
    -> Map UserId (User, Map PostId (Post, [Entity Comment]))
associatePostsAndComments =
    fmap (fmap associateJoin)

For more reading on this topic, see this Foxhound Systems blog post.

Since: esqueleto-3.1.2

deleteKey :: forall backend val (m :: Type -> Type). (PersistStore backend, BaseBackend backend ~ PersistEntityBackend val, MonadIO m, PersistEntity val) => Key val -> ReaderT backend m () #

Synonym for delete that does not clash with esqueleto's delete.

valJ :: PersistField (Key entity) => Value (Key entity) -> SqlExpr (Value (Key entity)) #

valJ is like val but for something that is already a Value. The use case it was written for was, given a Value lift the Key for that Value into the query expression in a type safe way. However, the implementation is more generic than that so we call it valJ.

Its important to note that the input entity and the output entity are constrained to be the same by the type signature on the function (https://github.com/prowdsponsor/esqueleto/pull/69).

Since: esqueleto-1.4.2

insertSelectCount :: forall (m :: Type -> Type) a backend. (MonadIO m, PersistEntity a, SqlBackendCanWrite backend) => SqlQuery (SqlExpr (Insertion a)) -> ReaderT backend m Int64 #

Insert a PersistField for every selected value, return the count afterward

insertSelect :: forall (m :: Type -> Type) a backend. (MonadIO m, PersistEntity a, SqlBackendCanWrite backend) => SqlQuery (SqlExpr (Insertion a)) -> ReaderT backend m () #

Insert a PersistField for every selected value.

Since: esqueleto-2.4.2

renderQueryInsertInto #

Arguments

:: forall a r backend (m :: Type -> Type). (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) 
=> SqlQuery a

The SQL query you want to render.

-> ReaderT backend m (Text, [PersistValue]) 

Renders a SqlQuery into a Text value along with the list of PersistValues that would be supplied to the database for ? placeholders.

Since: esqueleto-3.1.1

renderQueryUpdate #

Arguments

:: forall a r backend (m :: Type -> Type). (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) 
=> SqlQuery a

The SQL query you want to render.

-> ReaderT backend m (Text, [PersistValue]) 

Renders a SqlQuery into a Text value along with the list of PersistValues that would be supplied to the database for ? placeholders.

Since: esqueleto-3.1.1

renderQueryDelete #

Arguments

:: forall a r backend (m :: Type -> Type). (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) 
=> SqlQuery a

The SQL query you want to render.

-> ReaderT backend m (Text, [PersistValue]) 

Renders a SqlQuery into a Text value along with the list of PersistValues that would be supplied to the database for ? placeholders.

Since: esqueleto-3.1.1

renderQuerySelect #

Arguments

:: forall a r backend (m :: Type -> Type). (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) 
=> SqlQuery a

The SQL query you want to render.

-> ReaderT backend m (Text, [PersistValue]) 

Renders a SqlQuery into a Text value along with the list of PersistValues that would be supplied to the database for ? placeholders.

Since: esqueleto-3.1.1

renderQueryToText #

Arguments

:: forall a r backend (m :: Type -> Type). (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) 
=> Mode

Whether to render as an SELECT, DELETE, etc.

-> SqlQuery a

The SQL query you want to render.

-> ReaderT backend m (Text, [PersistValue]) 

Renders a SqlQuery into a Text value along with the list of PersistValues that would be supplied to the database for ? placeholders.

You must ensure that the Mode you pass to this function corresponds with the actual SqlQuery. If you pass a query that uses incompatible features (like an INSERT statement with a SELECT mode) then you'll get a weird result.

Since: esqueleto-3.1.1

updateCount :: forall (m :: Type -> Type) val backend. (MonadIO m, PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val), SqlBackendCanWrite backend) => (SqlExpr (Entity val) -> SqlQuery ()) -> ReaderT backend m Int64 #

Same as update, but returns the number of rows affected.

deleteCount :: forall (m :: Type -> Type) backend. (MonadIO m, SqlBackendCanWrite backend) => SqlQuery () -> ReaderT backend m Int64 #

Same as delete, but returns the number of rows affected.

selectOne :: forall a r (m :: Type -> Type) backend. (SqlSelect a r, MonadIO m, SqlBackendCanRead backend) => SqlQuery a -> ReaderT backend m (Maybe r) #

Execute an esqueleto SELECT query inside persistent's SqlPersistT monad and return the first entry wrapped in a Maybe. @since 3.5.1.0

Example usage

Expand
firstPerson :: MonadIO m => SqlPersistT m (Maybe (Entity Person))
firstPerson =
 selectOne $ do
     person <- from $ table @Person
     return person

The above query is equivalent to a select combined with limit but you would still have to transform the results from a list:

firstPerson :: MonadIO m => SqlPersistT m [Entity Person]
firstPerson =
 select $ do
     person <- from $ table @Person
     limit 1
     return person

select :: forall a r (m :: Type -> Type) backend. (SqlSelect a r, MonadIO m, SqlBackendCanRead backend) => SqlQuery a -> ReaderT backend m [r] #

Execute an esqueleto SELECT query inside persistent's SqlPersistT monad and return a list of rows.

We've seen that from has some magic about which kinds of things you may bring into scope. This select function also has some magic for which kinds of things you may bring back to Haskell-land by using SqlQuery's return:

  • You may return a SqlExpr (Entity v) for an entity v (i.e., like the * in SQL), which is then returned to Haskell-land as just Entity v.
  • You may return a SqlExpr (Maybe (Entity v)) for an entity v that may be NULL, which is then returned to Haskell-land as Maybe (Entity v). Used for OUTER JOINs.
  • You may return a SqlExpr (Value t) for a value t (i.e., a single column), where t is any instance of PersistField, which is then returned to Haskell-land as Value t. You may use Value to return projections of an Entity (see (^.) and (?.)) or to return any other value calculated on the query (e.g., countRows or subSelect).

The SqlSelect a r class has functional dependencies that allow type information to flow both from a to r and vice-versa. This means that you'll almost never have to give any type signatures for esqueleto queries. For example, the query select $ from $ \p -> return p alone is ambiguous, but in the context of

do ps <- select $
         from $ \p ->
         return p
   liftIO $ mapM_ (putStrLn . personName . entityVal) ps

we are able to infer from that single personName . entityVal function composition that the p inside the query is of type SqlExpr (Entity Person).

else_ :: expr a -> expr a #

Syntax sugar for case_.

Since: esqueleto-2.1.2

then_ :: () #

Syntax sugar for case_.

Since: esqueleto-2.1.2

when_ :: expr (Value Bool) -> () -> expr a -> (expr (Value Bool), expr a) #

Syntax sugar for case_.

Since: esqueleto-2.1.2

toBaseId :: ToBaseId ent => SqlExpr (Value (Key ent)) -> SqlExpr (Value (Key (BaseEnt ent))) #

Convert an entity's key into another entity's.

This function is to be used when you change an entity's Id to be that of another entity. For example:

Bar
  barNum Int
Foo
  bar BarId
  fooNum Int
  Primary bar

In this example, Bar is said to be the BaseEnt(ity), and Foo the child. To model this in Esqueleto, declare:

instance ToBaseId Foo where
  type BaseEnt Foo = Bar
  toBaseIdWitness barId = FooKey barId

Now you're able to write queries such as:

select $
from $ (bar `InnerJoin` foo) -> do
on (toBaseId (foo ^. FooId) ==. bar ^. BarId)
return (bar, foo)

Note: this function may be unsafe to use in conditions not like the one of the example above.

Since: esqueleto-2.4.3

case_ :: PersistField a => [(SqlExpr (Value Bool), SqlExpr (Value a))] -> SqlExpr (Value a) -> SqlExpr (Value a) #

CASE statement. For example:

select $
return $
case_
   [ when_
       (exists $
       from $ \p -> do
       where_ (p ^. PersonName ==. val "Mike"))
     then_
       (sub_select $
       from $ \v -> do
       let sub =
               from $ \c -> do
               where_ (c ^. PersonName ==. val "Mike")
               return (c ^. PersonFavNum)
       where_ (v ^. PersonFavNum >. sub_select sub)
       return $ count (v ^. PersonName) +. val (1 :: Int)) ]
   (else_ $ val (-1))

This query is a bit complicated, but basically it checks if a person named "Mike" exists, and if that person does, run the subquery to find out how many people have a ranking (by Fav Num) higher than "Mike".

NOTE: There are a few things to be aware about this statement.

  • This only implements the full CASE statement, it does not implement the "simple" CASE statement.
  • At least one when_ and then_ is mandatory otherwise it will emit an error.
  • The else_ is also mandatory, unlike the SQL statement in which if the ELSE is omitted it will return a NULL. You can reproduce this via nothing.

Since: esqueleto-2.1.2

(<&>) :: SqlExpr (Insertion (a -> b)) -> SqlExpr (Value a) -> SqlExpr (Insertion b) #

Apply extra SqlExpr Value arguments to a PersistField constructor

(<#) :: (a -> b) -> SqlExpr (Value a) -> SqlExpr (Insertion b) #

Apply a PersistField constructor to SqlExpr Value arguments.

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.

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

NOT EXISTS operator.

notIn :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool) #

NOT IN operator.

in_ :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool) #

IN operator. For example if you want to select all Persons by a list of IDs:

SELECT *
FROM Person
WHERE Person.id IN (?)

In esqueleto, we may write the same query above as:

select $
from $ \person -> do
where_ $ person ^. PersonId `in_` valList personIds
return person

Where personIds is of type [Key Person].

justList :: SqlExpr (ValueList typ) -> SqlExpr (ValueList (Maybe typ)) #

Same as just but for ValueList. Most of the time you won't need it, though, because you can use just from inside subList_select or Just from inside valList.

Since: esqueleto-2.2.12

valList :: PersistField typ => [typ] -> SqlExpr (ValueList typ) #

Lift a list of constant value from Haskell-land to the query.

subList_select :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (ValueList a) #

Execute a subquery SELECT in an SqlExpression. Returns a list of values.

castString :: (SqlString s, SqlString r) => SqlExpr (Value s) -> SqlExpr (Value r) #

Cast a string type into Text. This function is very useful if you want to use newtypes, or if you want to apply functions such as like to strings of different types.

Safety: This is a slightly unsafe function, especially if you have defined your own instances of SqlString. Also, since Maybe is an instance of SqlString, it's possible to turn a nullable value into a non-nullable one. Avoid using this function if possible.

(++.) :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) -> SqlExpr (Value s) infixr 5 #

The || string concatenation operator (named after Haskell's ++ in order to avoid naming clash with ||.). Supported by SQLite and PostgreSQL.

concat_ :: SqlString s => [SqlExpr (Value s)] -> SqlExpr (Value s) #

The CONCAT function with a variable number of parameters. Supported by MySQL and PostgreSQL.

(%) :: SqlString s => SqlExpr (Value s) #

The string %. May be useful while using like and concatenation (concat_ or ++., depending on your database). Note that you always have to type the parenthesis, for example:

name `like` (%) ++. val "John" ++. (%)

ilike :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) -> SqlExpr (Value Bool) infixr 2 #

ILIKE operator (case-insensitive LIKE).

Supported by PostgreSQL only.

Since: esqueleto-2.2.3

like :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) -> SqlExpr (Value Bool) infixr 2 #

LIKE operator.

right_ :: (SqlString s, Num a) => (SqlExpr (Value s), SqlExpr (Value a)) -> SqlExpr (Value s) #

RIGHT function. @since 3.3.0

left_ :: (SqlString s, Num a) => (SqlExpr (Value s), SqlExpr (Value a)) -> SqlExpr (Value s) #

LEFT function. @since 3.3.0

length_ :: (SqlString s, Num a) => SqlExpr (Value s) -> SqlExpr (Value a) #

LENGTH function. @since 3.3.0

ltrim_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) #

LTRIM function. @since 3.3.0

rtrim_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) #

RTRIM function. @since 3.3.0

trim_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) #

TRIM function. @since 3.3.0

upper_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) #

UPPER function. @since 3.3.0

lower_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) #

LOWER function.

coalesceDefault :: PersistField a => [SqlExpr (Value (Maybe a))] -> SqlExpr (Value a) -> SqlExpr (Value a) #

Like coalesce, but takes a non-nullable SqlExpression placed at the end of the SqlExpression list, which guarantees a non-NULL result.

Since: esqueleto-1.4.3

coalesce :: PersistField a => [SqlExpr (Value (Maybe a))] -> SqlExpr (Value (Maybe a)) #

COALESCE function. Evaluates the arguments in order and returns the value of the first non-NULL SqlExpression, or NULL (Nothing) otherwise. Some RDBMSs (such as SQLite) require at least two arguments; please refer to the appropriate documentation.

Since: esqueleto-1.4.3

castNumM :: (Num a, Num b) => SqlExpr (Value (Maybe a)) -> SqlExpr (Value (Maybe b)) #

Same as castNum, but for nullable values.

Since: esqueleto-2.2.9

castNum :: (Num a, Num b) => SqlExpr (Value a) -> SqlExpr (Value b) #

Allow a number of one type to be used as one of another type via an implicit cast. An explicit cast is not made, this function changes only the types on the Haskell side.

Caveat: Trying to use castNum from Double to Int will not result in an integer, the original fractional number will still be used! Use round_, ceiling_ or floor_ instead.

Safety: This operation is mostly safe due to the Num constraint between the types and the fact that RDBMSs usually allow numbers of different types to be used interchangeably. However, there may still be issues with the query not being accepted by the RDBMS or persistent not being able to parse it.

Since: esqueleto-2.2.9

between :: PersistField a => SqlExpr (Value a) -> (SqlExpr (Value a), SqlExpr (Value a)) -> SqlExpr (Value Bool) #

BETWEEN.

@since: 3.1.0

(*.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a) infixl 7 #

(/.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a) infixl 7 #

(-.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a) infixl 6 #

(+.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a) infixl 6 #

countDistinct :: Num a => SqlExpr (Value typ) -> SqlExpr (Value a) #

COUNT(DISTINCT x).

Since: esqueleto-2.4.1

countRows :: Num a => SqlExpr (Value a) #

COUNT(*) value.

joinV :: SqlExpr (Value (Maybe (Maybe typ))) -> SqlExpr (Value (Maybe typ)) #

Join nested Maybes in a Value into one. This is useful when calling aggregate functions on nullable fields.

nothing :: SqlExpr (Value (Maybe typ)) #

NULL value.

just :: SqlExpr (Value typ) -> SqlExpr (Value (Maybe typ)) #

Analogous to Just, promotes a value of type typ into one of type Maybe typ. It should hold that val . Just === just . val.

isNothing_ :: PersistField typ => SqlExpr (Value (Maybe typ)) -> SqlExpr (Value Bool) #

An alias for isNothing that avoids clashing with the function from Data.Maybe isNothing.

Since: esqueleto-3.5.10.0

isNothing :: PersistField typ => SqlExpr (Value (Maybe typ)) -> SqlExpr (Value Bool) #

IS NULL comparison.

For IS NOT NULL, you can negate this with not_, as in not_ (isNothing (person ^. PersonAge))

Warning: Persistent and Esqueleto have different behavior for != Nothing:

HaskellSQL
Persistent!=. NothingIS NOT NULL
Esqueleto!=. Nothing!= NULL

In SQL, = NULL and != NULL return NULL instead of true or false. For this reason, you very likely do not want to use !=. Nothing in Esqueleto. You may find these hlint rules helpful to enforce this:

- error: {lhs: v Database.Esqueleto.==. Database.Esqueleto.nothing, rhs: Database.Esqueleto.isNothing v, name: Use Esqueleto's isNothing}
- error: {lhs: v Database.Esqueleto.==. Database.Esqueleto.val Nothing, rhs: Database.Esqueleto.isNothing v, name: Use Esqueleto's isNothing}
- error: {lhs: v Database.Esqueleto.!=. Database.Esqueleto.nothing, rhs: not_ (Database.Esqueleto.isNothing v), name: Use Esqueleto's not isNothing}
- error: {lhs: v Database.Esqueleto.!=. Database.Esqueleto.val Nothing, rhs: not_ (Database.Esqueleto.isNothing v), name: Use Esqueleto's not isNothing}

val :: PersistField typ => typ -> SqlExpr (Value typ) #

Lift a constant value from Haskell-land to the query.

(?.) :: (PersistEntity val, PersistField typ) => SqlExpr (Maybe (Entity val)) -> EntityField val typ -> SqlExpr (Value (Maybe typ)) #

Project a field of an entity that may be null.

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.

(^.) :: forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) infixl 9 #

Project a field of an entity.

subSelectUnsafe :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (Value a) #

Execute a subquery SELECT in a SqlExpr. This function is unsafe, because it can throw runtime exceptions in two cases:

  1. If the query passed has 0 result rows, then it will return a NULL value. The persistent parsing operations will fail on an unexpected NULL.
  2. If the query passed returns more than one row, then the SQL engine will fail with an error like "More than one row returned by a subquery used as an expression".

This function is safe if you guarantee that exactly one row will be returned, or if the result already has a Maybe type for some reason.

For variants with the safety encoded already, see subSelect and subSelectMaybe. For the most common safe use of this, see subSelectCount.

Since: esqueleto-3.2.0

subSelectForeign #

Arguments

:: (BackendCompatible SqlBackend (PersistEntityBackend val1), PersistEntity val1, PersistEntity val2, PersistField a) 
=> SqlExpr (Entity val2)

An expression representing the table you have access to now.

-> EntityField val2 (Key val1)

The foreign key field on the table.

-> (SqlExpr (Entity val1) -> SqlExpr (Value a))

A function to extract a value from the foreign reference table.

-> SqlExpr (Value a) 

Performs a sub-select using the given foreign key on the entity. This is useful to extract values that are known to be present by the database schema.

As an example, consider the following persistent definition:

User
  profile ProfileId

Profile
  name    Text

The following query will return the name of the user.

getUserWithName =
    select $
    from $ user ->
    pure (user, subSelectForeign user UserProfile (^. ProfileName)

Since: esqueleto-3.2.0

subSelectList :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (ValueList a) #

Execute a subquery SELECT in a SqlExpr that returns a list. This is an alias for subList_select and is provided for symmetry with the other safe subselect functions.

Since: esqueleto-3.2.0

subSelectCount :: (Num a, PersistField a) => SqlQuery ignored -> SqlExpr (Value a) #

Performs a COUNT of the given query in a subSelect manner. This is always guaranteed to return a result value, and is completely safe.

Since: esqueleto-3.2.0

subSelectMaybe :: PersistField a => SqlQuery (SqlExpr (Value (Maybe a))) -> SqlExpr (Value (Maybe a)) #

Execute a subquery SELECT in a SqlExpr. This function is a shorthand for the common joinV . subSelect idiom, where you are calling subSelect on an expression that would be Maybe already.

As an example, you would use this function when calling sum_ or max_, which have Maybe in the result type (for a 0 row query).

Since: esqueleto-3.2.0

subSelect :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (Value (Maybe a)) #

Execute a subquery SELECT in a SqlExpr. The query passed to this function will only return a single result - it has a LIMIT 1 passed in to the query to make it safe, and the return type is Maybe to indicate that the subquery might result in 0 rows.

If you find yourself writing joinV . subSelect, then consider using subSelectMaybe.

If you're performing a countRows, then you can use subSelectCount which is safe.

If you know that the subquery will always return exactly one row (eg a foreign key constraint guarantees that you'll get exactly one row), then consider subSelectUnsafe, along with a comment explaining why it is safe.

Since: esqueleto-3.2.0

sub_select :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (Value a) #

Execute a subquery SELECT in an SqlExpression. Returns a simple value so should be used only when the SELECT query is guaranteed to return just one row.

Deprecated in 3.2.0.

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

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

HAVING.

Since: esqueleto-1.2.2

rand :: SqlExpr OrderBy #

ORDER BY random() clause.

Since: esqueleto-1.3.10

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

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

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

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

offset :: Int64 -> SqlQuery () #

OFFSET. Usually used with limit.

limit :: Int64 -> SqlQuery () #

LIMIT. Limit the number of returned rows.

desc :: PersistField a => SqlExpr (Value a) -> SqlExpr OrderBy #

Descending order of this field or SqlExpression.

asc :: PersistField a => SqlExpr (Value a) -> SqlExpr OrderBy #

Ascending order of this field or SqlExpression.

orderBy :: [SqlExpr OrderBy] -> SqlQuery () #

ORDER BY clause. See also asc and desc.

Multiple calls to orderBy get concatenated on the final query, including distinctOnOrderBy.

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

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)

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

WHERE clause: restrict the query's result.

newtype Value a #

A single value (as opposed to a whole entity). You may use (^.) or (?.) to get a Value from an Entity.

Constructors

Value 

Fields

Instances

Instances details
Applicative Value 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

pure :: a -> Value a #

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

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

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

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

Functor Value

Since: esqueleto-1.4.4

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Monad Value 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

return :: a -> Value a #

(PersistEntity rec, PersistField typ, SymbolToField sym rec typ) => HasField (sym :: Symbol) (SqlExpr (Entity rec)) (SqlExpr (Value typ))

This instance allows you to use record.field notation with GHC 9.2's OverloadedRecordDot extension.

Example:

-- persistent model:
BlogPost
    authorId     PersonId
    title        Text

-- query:
select $ do
    bp <- from $ table @BlogPost
    pure $ bp.title

This is exactly equivalent to the following:

blogPost :: SqlExpr (Entity BlogPost)

blogPost ^. BlogPostTitle
blogPost ^. #title
blogPost.title

There's another instance defined on SqlExpr (Entity (Maybe rec)), which allows you to project from a LEFT JOINed entity.

Since: esqueleto-3.5.4.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

getField :: SqlExpr (Entity rec) -> SqlExpr (Value typ) #

(PersistEntity rec, PersistField typ, SymbolToField sym rec typ) => HasField (sym :: Symbol) (SqlExpr (Maybe (Entity rec))) (SqlExpr (Value (Maybe typ)))

This instance allows you to use record.field notation with GC 9.2's OverloadedRecordDot extension.

Example:

-- persistent model:
Person
    name         Text

BlogPost
    title        Text
    authorId     PersonId

-- query:

select $ do
    (p :& bp) <- from $
        table Person
        leftJoin table BlogPost
        on do
            \(p :& bp) ->
                just p.id ==. bp.authorId
    pure (p.name, bp.title)

The following forms are all equivalent:

blogPost :: SqlExpr (Maybe (Entity BlogPost))

blogPost ?. BlogPostTitle
blogPost ?. #title
blogPost.title

Since: esqueleto-3.5.4.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

getField :: SqlExpr (Maybe (Entity rec)) -> SqlExpr (Value (Maybe typ)) #

(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 #

(PersistEntity rec, PersistField typ, field ~ EntityField rec typ) => SqlAssignment field (SqlExpr (Value typ)) (SqlExpr (Entity rec) -> SqlExpr Update) Source # 
Instance details

Defined in Database.Esqueleto.Compat.Operators

Methods

(=.) :: field -> SqlExpr (Value typ) -> SqlExpr (Entity rec) -> SqlExpr Update Source #

(-=.) :: field -> SqlExpr (Value typ) -> SqlExpr (Entity rec) -> SqlExpr Update Source #

(+=.) :: field -> SqlExpr (Value typ) -> SqlExpr (Entity rec) -> SqlExpr Update Source #

(*=.) :: field -> SqlExpr (Value typ) -> SqlExpr (Entity rec) -> SqlExpr Update Source #

Show a => Show (Value a) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

showsPrec :: Int -> Value a -> ShowS #

show :: Value a -> String #

showList :: [Value a] -> ShowS #

ToAlias (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: SqlExpr (Value a) -> SqlQuery (SqlExpr (Value a)) #

ToAliasReference (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToMaybe (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Value a)) #

Methods

toMaybe :: SqlExpr (Value a) -> ToMaybeT (SqlExpr (Value a)) #

ToSomeValues (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

toSomeValues :: SqlExpr (Value a) -> [SomeValue] #

a ~ Bool => SqlBoolean (SqlExpr (Value a)) Source #

SqlExpr can be compared as SqlBoolean values, provided that they contain a Value Bool.

The implementation uses the (a ~ Bool) equality constraint so that polymorphic definitions don't get too confused.

Instance details

Defined in Database.Esqueleto.Compat.Operators

a ~ Bool => SqlBooleanNot (SqlExpr (Value a)) Source # 
Instance details

Defined in Database.Esqueleto.Compat.Operators

Methods

not_ :: SqlExpr (Value a) -> SqlExpr (Value a) Source #

Eq a => Eq (Value a) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Ord a => Ord (Value a) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

compare :: Value a -> Value a -> Ordering #

(<) :: Value a -> Value a -> Bool #

(<=) :: Value a -> Value a -> Bool #

(>) :: Value a -> Value a -> Bool #

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

max :: Value a -> Value a -> Value a #

min :: Value a -> Value a -> Value a #

PersistField a => SqlSelect (SqlExpr (Value a)) (Value a)

You may return any single value (i.e. a single column) from a select query.

Instance details

Defined in Database.Esqueleto.Internal.Internal

(PersistField a, a ~ b, lhs ~ SqlExpr (Value a), c ~ Bool) => SqlComparison (SqlExpr (Value a)) (SqlExpr (Value b)) (SqlExpr (Value c)) Source # 
Instance details

Defined in Database.Esqueleto.Compat.Operators

type ToMaybeT (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

newtype ValueList a #

A list of single values. There's a limited set of functions able to work with this data type (such as subList_select, valList, in_ and exists).

Constructors

ValueList a 

Instances

Instances details
Show a => Show (ValueList a) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Eq a => Eq (ValueList a) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Ord a => Ord (ValueList a) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

data InnerJoin a b infixl 2 #

Data type that represents an INNER JOIN (see LeftOuterJoin for an example).

Constructors

a `InnerJoin` b infixl 2 

Instances

Instances details
IsJoinKind InnerJoin 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

smartJoin :: a -> b -> InnerJoin a b #

reifyJoinKind :: InnerJoin a b -> JoinKind #

FromPreprocess (InnerJoin a b) => From (InnerJoin a b) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (InnerJoin a b) #

data CrossJoin a b infixl 2 #

Data type that represents a CROSS JOIN (see LeftOuterJoin for an example).

Constructors

a `CrossJoin` b infixl 2 

Instances

Instances details
IsJoinKind CrossJoin 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

smartJoin :: a -> b -> CrossJoin a b #

reifyJoinKind :: CrossJoin a b -> JoinKind #

FromPreprocess (CrossJoin a b) => From (CrossJoin a b) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (CrossJoin a b) #

data LeftOuterJoin a b infixl 2 #

Data type that represents a LEFT OUTER JOIN. For example,

select $
from $ \(person `LeftOuterJoin` pet) ->
  ...

is translated into

SELECT ...
FROM Person LEFT OUTER JOIN Pet
...

See also: from.

Constructors

a `LeftOuterJoin` b infixl 2 

Instances

Instances details
IsJoinKind LeftOuterJoin 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

smartJoin :: a -> b -> LeftOuterJoin a b #

reifyJoinKind :: LeftOuterJoin a b -> JoinKind #

FromPreprocess (LeftOuterJoin a b) => From (LeftOuterJoin a b) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (LeftOuterJoin a b) #

data RightOuterJoin a b infixl 2 #

Data type that represents a RIGHT OUTER JOIN (see LeftOuterJoin for an example).

Constructors

a `RightOuterJoin` b infixl 2 

Instances

Instances details
IsJoinKind RightOuterJoin 
Instance details

Defined in Database.Esqueleto.Internal.Internal

FromPreprocess (RightOuterJoin a b) => From (RightOuterJoin a b) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (RightOuterJoin a b) #

data FullOuterJoin a b infixl 2 #

Data type that represents a FULL OUTER JOIN (see LeftOuterJoin for an example).

Constructors

a `FullOuterJoin` b infixl 2 

Instances

Instances details
IsJoinKind FullOuterJoin 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

smartJoin :: a -> b -> FullOuterJoin a b #

reifyJoinKind :: FullOuterJoin a b -> JoinKind #

FromPreprocess (FullOuterJoin a b) => From (FullOuterJoin a b) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (FullOuterJoin a b) #

data JoinKind #

(Internal) A kind of JOIN.

Constructors

InnerJoinKind
INNER JOIN
CrossJoinKind
CROSS JOIN
LeftOuterJoinKind
LEFT OUTER JOIN
RightOuterJoinKind
RIGHT OUTER JOIN
FullOuterJoinKind
FULL OUTER JOIN

Instances

Instances details
Show JoinKind 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Eq JoinKind 
Instance details

Defined in Database.Esqueleto.Internal.Internal

data OnClauseWithoutMatchingJoinException #

Exception thrown whenever on is used to create an ON clause but no matching JOIN is found.

Instances

Instances details
Exception OnClauseWithoutMatchingJoinException 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Show OnClauseWithoutMatchingJoinException 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Eq OnClauseWithoutMatchingJoinException 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Ord OnClauseWithoutMatchingJoinException 
Instance details

Defined in Database.Esqueleto.Internal.Internal

data OrderBy #

Phantom type used by orderBy, asc and desc.

data DistinctOn #

Phantom type used by distinctOn and don.

data a :& b infixl 2 #

A left-precedence pair. Pronounced "and". Used to represent expressions that have been joined together.

The precedence behavior can be demonstrated by:

a :& b :& c == ((a :& b) :& c)

See the examples at the beginning of this module to see how this operator is used in JOIN operations.

Constructors

a :& b infixl 2 

Instances

Instances details
(ToFrom a a', ToFrom b b') => DoCrossJoin NotLateral a b (a' :& b') 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

(ToFrom a a', ToFrom b b', HasOnClause rhs (a' :& b'), rhs ~ (b, (a' :& b') -> SqlExpr (Value Bool))) => DoInnerJoin NotLateral a rhs (a' :& b') 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doInnerJoin :: Proxy NotLateral -> a -> rhs -> From (a' :& b') #

(ToFrom a a', ToFrom b b', ToMaybe b', ToMaybeT b' ~ mb, HasOnClause rhs (a' :& mb), rhs ~ (b, (a' :& mb) -> SqlExpr (Value Bool))) => DoLeftJoin NotLateral a rhs (a' :& mb) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doLeftJoin :: Proxy NotLateral -> a -> rhs -> From (a' :& mb) #

(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) #

GetFirstTable t (t :& ts) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

getFirstTable :: (t :& ts) -> t #

GetFirstTable t ts => GetFirstTable t (ts :& x) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

getFirstTable :: (ts :& x) -> t #

GetFirstTable t (x :& t) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

getFirstTable :: (x :& t) -> t #

(Show a, Show b) => Show (a :& b) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

showsPrec :: Int -> (a :& b) -> ShowS #

show :: (a :& b) -> String #

showList :: [a :& b] -> ShowS #

(LockableEntity a, LockableEntity b) => LockableEntity (a :& b) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

(Eq a, Eq b) => Eq (a :& b) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

(==) :: (a :& b) -> (a :& b) -> Bool #

(/=) :: (a :& b) -> (a :& b) -> Bool #

type ToMaybeT (a :& b) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

type ToMaybeT (a :& b) = ToMaybeT a :& ToMaybeT b

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

class LockableEntity a where #

Lockable entity

Example use:

select $ do
    (p :& bp) <- from $
        table Person
        innerJoin table BlogPost
            on do
                (p :& bp) -> p ^. PersonId ==. b ^. BlogPostAuthorId
    forUpdateOf (p :& b) skipLocked
    return p

class PersistField a => SqlString a #

Phantom class of data types that are treated as strings by the RDBMS. It has no methods because it's only used to avoid type errors such as trying to concatenate integers.

If you have a custom data type or newtype, feel free to make it an instance of this class.

Since: esqueleto-2.4.0

Instances

Instances details
SqlString Html

Since: esqueleto-2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlString ByteString

Since: esqueleto-2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlString Text

Since: esqueleto-2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlString Text

Since: esqueleto-2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlString a => SqlString (Maybe a)

Since: esqueleto-2.4.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

a ~ Char => SqlString [a]

Since: esqueleto-2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

type family BaseEnt ent #

e.g. type BaseEnt MyBase = MyChild

class ToBaseId ent where #

Class that enables one to use toBaseId to convert an entity's key on a query into another (cf. toBaseId).

Associated Types

type BaseEnt ent #

e.g. type BaseEnt MyBase = MyChild

Methods

toBaseIdWitness :: Key (BaseEnt ent) -> Key ent #

Convert from the key of the BaseEnt(ity) to the key of the child entity. This function is not actually called, but that it typechecks proves this operation is safe.

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 (SubQuery (SqlQuery a)) a 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: SubQuery (SqlQuery a) -> From a #

(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

type SqlEntity ent = (PersistEntity ent, PersistEntityBackend ent ~ SqlBackend) #

Constraint synonym for persistent entities whose backend is SqlBackend.

data SqlExpr a #

An expression on the SQL backend.

Raw expression: Contains a SqlExprMeta and a function for building the expr. It recieves a parameter telling it whether it is in a parenthesized context, and takes information about the SQL connection (mainly for escaping names) and returns both an string (Builder) and a list of values to be interpolated by the SQL backend.

Instances

Instances details
(TypeError SqlExprFunctorMessage :: Constraint) => Functor SqlExpr

Folks often want the ability to promote a Haskell function into the SqlExpr expression language - and naturally reach for fmap. Unfortunately, this is impossible. We cannot send *functions* to the database, which is what we would need to do in order for this to make sense. Let's consider the type of fmap for SqlExpr:

fmap :: (a -> b) -> SqlExpr a -> SqlExpr b

This type signature is making a pretty strong claim: "Give me a Haskell function from a -> b. I will then transform a SQL expression representing a Haskell value of type a and turn it into a SQL expression representing a Haskell value of type b."

Let's suppose we *could* do this - fmap (+1) would have to somehow inspect the function expression means "add one", and then translate that to the appropriate SQL.

This is why esqueleto defines a bunch of operators: x +. (val 1) can be used instead of fmap (+1) x.

If you do have a SQL function, then you can provide a safe type and introduce it with unsafeSqlFunction or unsafeSqlBinOp.

Since: esqueleto-3.5.8.2

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

(PersistEntity rec, PersistField typ, SymbolToField sym rec typ) => HasField (sym :: Symbol) (SqlExpr (Entity rec)) (SqlExpr (Value typ))

This instance allows you to use record.field notation with GHC 9.2's OverloadedRecordDot extension.

Example:

-- persistent model:
BlogPost
    authorId     PersonId
    title        Text

-- query:
select $ do
    bp <- from $ table @BlogPost
    pure $ bp.title

This is exactly equivalent to the following:

blogPost :: SqlExpr (Entity BlogPost)

blogPost ^. BlogPostTitle
blogPost ^. #title
blogPost.title

There's another instance defined on SqlExpr (Entity (Maybe rec)), which allows you to project from a LEFT JOINed entity.

Since: esqueleto-3.5.4.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

getField :: SqlExpr (Entity rec) -> SqlExpr (Value typ) #

(PersistEntity rec, PersistField typ, SymbolToField sym rec typ) => HasField (sym :: Symbol) (SqlExpr (Maybe (Entity rec))) (SqlExpr (Value (Maybe typ)))

This instance allows you to use record.field notation with GC 9.2's OverloadedRecordDot extension.

Example:

-- persistent model:
Person
    name         Text

BlogPost
    title        Text
    authorId     PersonId

-- query:

select $ do
    (p :& bp) <- from $
        table Person
        leftJoin table BlogPost
        on do
            \(p :& bp) ->
                just p.id ==. bp.authorId
    pure (p.name, bp.title)

The following forms are all equivalent:

blogPost :: SqlExpr (Maybe (Entity BlogPost))

blogPost ?. BlogPostTitle
blogPost ?. #title
blogPost.title

Since: esqueleto-3.5.4.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

getField :: SqlExpr (Maybe (Entity rec)) -> SqlExpr (Value (Maybe typ)) #

(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 #

(PersistEntity rec, PersistField typ, field ~ EntityField rec typ) => SqlAssignment field (SqlExpr (Value typ)) (SqlExpr (Entity rec) -> SqlExpr Update) Source # 
Instance details

Defined in Database.Esqueleto.Compat.Operators

Methods

(=.) :: field -> SqlExpr (Value typ) -> SqlExpr (Entity rec) -> SqlExpr Update Source #

(-=.) :: field -> SqlExpr (Value typ) -> SqlExpr (Entity rec) -> SqlExpr Update Source #

(+=.) :: field -> SqlExpr (Value typ) -> SqlExpr (Entity rec) -> SqlExpr Update Source #

(*=.) :: field -> SqlExpr (Value typ) -> SqlExpr (Entity rec) -> SqlExpr Update Source #

ToAlias (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: SqlExpr (Value a) -> SqlQuery (SqlExpr (Value a)) #

ToAlias (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: SqlExpr (Entity a) -> SqlQuery (SqlExpr (Entity a)) #

ToAlias (SqlExpr (Maybe (Entity a))) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

toAlias :: SqlExpr (Maybe (Entity a)) -> SqlQuery (SqlExpr (Maybe (Entity a))) #

ToAliasReference (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToAliasReference (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToAliasReference (SqlExpr (Maybe (Entity a))) 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToMaybe (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Value a)) #

Methods

toMaybe :: SqlExpr (Value a) -> ToMaybeT (SqlExpr (Value a)) #

ToMaybe (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Entity a)) #

Methods

toMaybe :: SqlExpr (Entity a) -> ToMaybeT (SqlExpr (Entity a)) #

ToMaybe (SqlExpr (Maybe a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Maybe a)) #

Methods

toMaybe :: SqlExpr (Maybe a) -> ToMaybeT (SqlExpr (Maybe a)) #

FromPreprocess (SqlExpr (Entity val)) => From (SqlExpr (Entity val)) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (SqlExpr (Entity val)) #

FromPreprocess (SqlExpr (Maybe (Entity val))) => From (SqlExpr (Maybe (Entity val))) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (SqlExpr (Maybe (Entity val))) #

(PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => FromPreprocess (SqlExpr (Entity val)) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

(PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => FromPreprocess (SqlExpr (Maybe (Entity val))) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

PersistEntity val => LockableEntity (SqlExpr (Entity val)) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

ToSomeValues (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

toSomeValues :: SqlExpr (Value a) -> [SomeValue] #

a ~ Value b => UnsafeSqlFunctionArgument (SqlExpr a) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

toArgList :: SqlExpr a -> [SqlExpr (Value ())] #

a ~ Bool => SqlBoolean (SqlExpr (Value a)) Source #

SqlExpr can be compared as SqlBoolean values, provided that they contain a Value Bool.

The implementation uses the (a ~ Bool) equality constraint so that polymorphic definitions don't get too confused.

Instance details

Defined in Database.Esqueleto.Compat.Operators

a ~ Bool => SqlBooleanNot (SqlExpr (Value a)) Source # 
Instance details

Defined in Database.Esqueleto.Compat.Operators

Methods

not_ :: SqlExpr (Value a) -> SqlExpr (Value a) Source #

PersistEntity ent => ToFrom (Table ent) (SqlExpr (Entity ent)) 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: Table ent -> From (SqlExpr (Entity ent)) #

PersistEntity e => SqlSelect (SqlExpr (Insertion e)) (Insertion e)

INSERT INTO hack.

Instance details

Defined in Database.Esqueleto.Internal.Internal

PersistField a => SqlSelect (SqlExpr (Value a)) (Value a)

You may return any single value (i.e. a single column) from a select query.

Instance details

Defined in Database.Esqueleto.Internal.Internal

PersistEntity a => SqlSelect (SqlExpr (Entity a)) (Entity a)

You may return an Entity from a select query.

Instance details

Defined in Database.Esqueleto.Internal.Internal

PersistEntity a => SqlSelect (SqlExpr (Maybe (Entity a))) (Maybe (Entity a))

You may return a possibly-NULL Entity from a select query.

Instance details

Defined in Database.Esqueleto.Internal.Internal

(PersistField a, a ~ b, lhs ~ SqlExpr (Value a), c ~ Bool) => SqlComparison (SqlExpr (Value a)) (SqlExpr (Value b)) (SqlExpr (Value c)) Source # 
Instance details

Defined in Database.Esqueleto.Compat.Operators

type ToMaybeT (SqlExpr (Value a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (SqlExpr (Entity a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (SqlExpr (Maybe a)) 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

class PersistConfig c where #

Represents a value containing all the configuration options for a specific backend. This abstraction makes it easier to write code that can easily swap backends.

Minimal complete definition

loadConfig, createPoolConfig, runPool

Associated Types

type PersistConfigBackend c :: (Type -> Type) -> Type -> Type #

type PersistConfigPool c #

Methods

loadConfig :: Value -> Parser c #

Load the config settings from a Value, most likely taken from a YAML config file.

applyEnv :: c -> IO c #

Modify the config settings based on environment variables.

createPoolConfig :: c -> IO (PersistConfigPool c) #

Create a new connection pool based on the given config settings.

runPool :: MonadUnliftIO m => c -> PersistConfigBackend c m a -> PersistConfigPool c -> m a #

Run a database action by taking a connection from the pool.

Instances

Instances details
(PersistConfig c1, PersistConfig c2, PersistConfigPool c1 ~ PersistConfigPool c2, PersistConfigBackend c1 ~ PersistConfigBackend c2) => PersistConfig (Either c1 c2) 
Instance details

Defined in Database.Persist.Class.PersistConfig

Associated Types

type PersistConfigBackend (Either c1 c2) :: (Type -> Type) -> Type -> Type #

type PersistConfigPool (Either c1 c2) #

Methods

loadConfig :: Value -> Parser (Either c1 c2) #

applyEnv :: Either c1 c2 -> IO (Either c1 c2) #

createPoolConfig :: Either c1 c2 -> IO (PersistConfigPool (Either c1 c2)) #

runPool :: MonadUnliftIO m => Either c1 c2 -> PersistConfigBackend (Either c1 c2) m a -> PersistConfigPool (Either c1 c2) -> m a #

type family PersistConfigBackend c :: (Type -> Type) -> Type -> Type #

Instances

Instances details
type PersistConfigBackend (Either c1 c2) 
Instance details

Defined in Database.Persist.Class.PersistConfig

type family PersistConfigPool c #

Instances

Instances details
type PersistConfigPool (Either c1 c2) 
Instance details

Defined in Database.Persist.Class.PersistConfig

newtype ConstraintNameHS #

An ConstraintNameHS represents the Haskell-side name that persistent will use for a constraint.

Since: persistent-2.12.0.0

Constructors

ConstraintNameHS 

newtype ConstraintNameDB #

A ConstraintNameDB represents the datastore-side name that persistent will use for a constraint.

Since: persistent-2.12.0.0

Constructors

ConstraintNameDB 

Instances

Instances details
Read ConstraintNameDB 
Instance details

Defined in Database.Persist.Names

Show ConstraintNameDB 
Instance details

Defined in Database.Persist.Names

Eq ConstraintNameDB 
Instance details

Defined in Database.Persist.Names

Ord ConstraintNameDB 
Instance details

Defined in Database.Persist.Names

DatabaseName ConstraintNameDB

Since: persistent-2.12.0.0

Instance details

Defined in Database.Persist.Names

Methods

escapeWith :: (Text -> str) -> ConstraintNameDB -> str #

Lift ConstraintNameDB 
Instance details

Defined in Database.Persist.Names

Methods

lift :: Quote m => ConstraintNameDB -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => ConstraintNameDB -> Code m ConstraintNameDB #

newtype EntityNameDB #

An EntityNameDB represents the datastore-side name that persistent will use for an entity.

Since: persistent-2.12.0.0

Constructors

EntityNameDB 

Fields