esqueleto-3.5.10.3: Type-safe EDSL for SQL queries on persistent backends.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Database.Esqueleto.Experimental

Description

This module contains a new way (introduced in 3.3.3.0) of using FROM in Haskell. The old method was a bit finicky and could permit runtime errors, and this new way is both significantly safer and much more powerful.

This syntax will become the default syntax exported from the library in version 3.6.0.0. To use the old syntax, see Database.Esqueleto.Legacy.

Synopsis

Setup

If you're already using Database.Esqueleto, then you can get started using this module just by changing your imports slightly, as well as enabling the TypeApplications extension.

{-# LANGUAGE TypeApplications #-}

...

import Database.Esqueleto.Experimental

Note: Prior to esqueleto-3.3.4.0, the Database.Esqueleto.Experimental module did not reexport Data.Esqueleto.

Introduction

This module is fully backwards-compatible extension to the esqueleto EDSL that expands subquery functionality and enables SQL set operations to be written directly in Haskell. Specifically, this enables:

  • Subqueries in JOIN statements
  • UNION
  • UNION ALL
  • INTERSECT
  • EXCEPT

As a consequence of this, several classes of runtime errors are now caught at compile time. This includes missing on clauses and improper handling of Maybe values in outer joins.

This module can be used in conjunction with the main Database.Esqueleto module, but doing so requires qualified imports to avoid ambiguous definitions of on and from, which are defined in both modules.

Below we will give an overview of how to use this module and the features it enables.

A New Syntax

This module introduces a new syntax that serves to enable the aforementioned features. This new syntax also changes how joins written in the esqueleto EDSL to more closely resemble the underlying SQL.

For our examples, we'll use a schema similar to the one in the Getting Started section of Database.Esqueleto:

share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persist|
  Person
    name String
    age Int Maybe
    deriving Eq Show
  BlogPost
    title String
    authorId PersonId
    deriving Eq Show
  Follow
    follower PersonId
    followed PersonId
    deriving Eq Show
|]

Example 1: Simple select

Let's select all people who are named "John".

Database.Esqueleto:

select $
from $ \people -> do
where_ (people ^. PersonName ==. val "John")
pure people

Database.Esqueleto.Experimental:

select $ do
people <- from $ table @Person
where_ (people ^. PersonName ==. val "John")
pure people

Example 2: Select with join

Let's select all people and their blog posts who are over the age of 18.

Database.Esqueleto:

select $
from $ \(people `LeftOuterJoin` blogPosts) -> do
on (just (people ^. PersonId) ==. blogPosts ?. BlogPostAuthorId)
where_ (people ^. PersonAge >. just (val 18))
pure (people, blogPosts)

Database.Esqueleto.Experimental:

Here we use the :& operator to pattern match against the joined tables.

select $ do
(people :& blogPosts) <-
    from $ table @Person
    `leftJoin` table @BlogPost
    `on` (\(people :& blogPosts) ->
            just (people ^. PersonId) ==. blogPosts ?. BlogPostAuthorId)
where_ (people ^. PersonAge >. just (val 18))
pure (people, blogPosts)

Example 3: Select with multi-table join

Let's select all people who follow a person named "John", including the name of each follower.

Database.Esqueleto:

select $
from $ \(
 people1
 `InnerJoin` followers
 `InnerJoin` people2
) -> do
on (people1 ^. PersonId ==. followers ^. FollowFollowed)
on (followers ^. FollowFollower ==. people2 ^. PersonId)
where_ (people1 ^. PersonName ==. val "John")
pure (followers, people2)

Database.Esqueleto.Experimental:

In this version, with each successive on clause, only the tables we have already joined into are in scope, so we must pattern match accordingly. In this case, in the second innerJoin, we do not use the first Person reference, so we use _ as a placeholder to ignore it. This prevents a possible runtime error where a table is referenced before it appears in the sequence of JOINs.

select $ do
(people1 :& followers :& people2) <-
    from $ table @Person
    `innerJoin` table @Follow
    `on` (\(people1 :& followers) ->
            people1 ^. PersonId ==. followers ^. FollowFollowed)
    `innerJoin` table @Person
    `on` (\(_ :& followers :& people2) ->
            followers ^. FollowFollower ==. people2 ^. PersonId)
where_ (people1 ^. PersonName ==. val "John")
pure (followers, people2)

Example 4: Counting results of a subquery

Let's count the number of people who have posted at least 10 posts

Database.Esqueleto:

select $ pure $ subSelectCount $
from $ \(
  people
  `InnerJoin` blogPosts
) -> do
on (people ^. PersonId ==. blogPosts ^. BlogPostAuthorId)
groupBy (people ^. PersonId)
having ((count $ blogPosts ^. BlogPostId) >. val 10)
pure people

Database.Esqueleto.Experimental:

select $ do
peopleWithPosts <-
  from $ do
    (people :& blogPosts) <-
      from $ table @Person
      `innerJoin` table @BlogPost
      `on` (\(p :& bP) ->
              p ^. PersonId ==. bP ^. BlogPostAuthorId)
    groupBy (people ^. PersonId)
    having ((count $ blogPosts ^. BlogPostId) >. val 10)
    pure people
pure $ count (peopleWithPosts ^. PersonId)

We now have the ability to refactor this

Example 5: Sorting the results of a UNION with limits

Out of all of the posts created by a person and the people they follow, generate a list of the first 25 posts, sorted alphabetically.

Database.Esqueleto:

Since UNION is not supported, this requires using rawSql. (Not shown)

Database.Esqueleto.Experimental:

Since this module supports all set operations (see SqlSetOperation), we can use Union to write this query.

select $ do
(authors, blogPosts) <- from $
  (do
    (author :& blogPost) <-
      from $ table @Person
      `innerJoin` table @BlogPost
      `on` (\(a :& bP) ->
              a ^. PersonId ==. bP ^. BlogPostAuthorId)
    where_ (author ^. PersonId ==. val currentPersonId)
    pure (author, blogPost)
  )
  `union_`
  (do
    (follow :& blogPost :& author) <-
      from $ table @Follow
      `innerJoin` table @BlogPost
      `on` (\(f :& bP) ->
              f ^. FollowFollowed ==. bP ^. BlogPostAuthorId)
      `innerJoin` table @Person
      `on` (\(_ :& bP :& a) ->
              bP ^. BlogPostAuthorId ==. a ^. PersonId)
    where_ (follow ^. FollowFollower ==. val currentPersonId)
    pure (author, blogPost)
  )
orderBy [ asc (blogPosts ^. BlogPostTitle) ]
limit 25
pure (authors, blogPosts)

Example 6: LATERAL JOIN

As of version 3.4.0.0, lateral subquery joins are supported.

select $ do
(salesPerson :& maxSaleAmount :& maxSaleCustomerName) <-
  from $ table @SalesPerson
  `crossJoinLateral` (\salesPerson -> do
        sales <- from $ table @Sale
        where_ $ sales ^. SaleSalesPersonId ==. salesPerson ^. SalesPersonId
        pure $ max_ (sales ^. SaleAmount)
        )
  `crossJoinLateral` (\(salesPerson :& maxSaleAmount) -> do
        sales <- from $ table @Sale
        where_ $ sales ^. SaleSalesPersonId ==. salesPerson ^. SalesPersonId
             &&. sales ^. SaleAmount ==. maxSaleAmount
        pure $ sales ^. SaleCustomerName)
        )
pure (salesPerson ^. SalesPersonName, maxSaleAmount, maxSaleCustomerName)

This is the equivalent to the following SQL (example taken from the MySQL Lateral Derived Table documentation):

SELECT
  salesperson.name,
  max_sale.amount,
  max_sale_customer.customer_name
FROM
  salesperson,
  -- calculate maximum size, cache it in transient derived table max_sale
  LATERAL
  (SELECT MAX(amount) AS amount
    FROM all_sales
    WHERE all_sales.salesperson_id = salesperson.id)
  AS max_sale,
  LATERAL
  (SELECT customer_name
    FROM all_sales
    WHERE all_sales.salesperson_id = salesperson.id
    AND all_sales.amount =
        -- the cached maximum size
        max_sale.amount)
  AS max_sale_customer;

Documentation

Basic Queries

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

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).

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

Bring a PersistEntity into scope from a table

select $ from $ table @People

Since: 3.5.0.0

data Table a Source #

Deprecated: @since 3.5.0.0 - use table instead

Constructors

Table

Deprecated: @since 3.5.0.0 - use table instead

Instances

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

Defined in Database.Esqueleto.Experimental.From

Methods

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

newtype SubQuery a Source #

Deprecated: Since: 3.4.0.0 - It is no longer necessary to tag SqlQuery values with SubQuery

Constructors

SubQuery a

Deprecated: Since: 3.4.0.0 - It is no longer necessary to tag SqlQuery values with SubQuery

Instances

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

Defined in Database.Esqueleto.Experimental.From

Methods

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

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

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: 3.5.0.0

Joins

data a :& b infixl 2 Source #

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') Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

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

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

(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) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

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

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

GetFirstTable t (t :& ts) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

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

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

GetFirstTable t (x :& t) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

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

(ToAlias a, ToAlias b) => ToAlias (a :& b) Source #

Identical to the tuple instance and provided for convenience.

Since: 3.5.3.0

Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

toAlias :: (a :& b) -> SqlQuery (a :& b) Source #

(ToAliasReference a, ToAliasReference b) => ToAliasReference (a :& b) Source #

Identical to the tuple instance and provided for convenience.

Since: 3.5.3.0

Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

toAliasReference :: Ident -> (a :& b) -> SqlQuery (a :& b) Source #

(ToMaybe a, ToMaybe b) => ToMaybe (a :& b) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Associated Types

type ToMaybeT (a :& b) Source #

Methods

toMaybe :: (a :& b) -> ToMaybeT (a :& b) Source #

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

Defined in Database.Esqueleto.Internal.Internal

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

(ToFrom a a', ToFrom b b', ToMaybe a', ToMaybeT a' ~ ma, ToMaybe b', ToMaybeT b' ~ mb, HasOnClause rhs (ma :& mb), ErrorOnLateral b, rhs ~ (b, (ma :& mb) -> SqlExpr (Value Bool))) => ToFrom (FullOuterJoin a rhs) (ma :& mb) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

toFrom :: FullOuterJoin a rhs -> From (ma :& mb) Source #

(ToFrom a a', ToFrom b b', ToMaybe a', ToMaybeT a' ~ ma, HasOnClause rhs (ma :& b'), ErrorOnLateral b, rhs ~ (b, (ma :& b') -> SqlExpr (Value Bool))) => ToFrom (RightOuterJoin a rhs) (ma :& b') Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

toFrom :: RightOuterJoin a rhs -> From (ma :& b') Source #

(SqlSelect a ra, SqlSelect b rb) => SqlSelect (a :& b) (ra :& rb) Source #

You may return joined values from a select query - this is identical to the tuple instance, but is provided for convenience.

Since: 3.5.2.0

Instance details

Defined in Database.Esqueleto.Experimental.From.Join

type ToMaybeT (a :& b) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

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

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

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)

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

INNER JOIN

Used as an infix operator `innerJoin`

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

Since: 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 Source #

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: 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 Source #

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: 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 Source #

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: 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 Source #

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: 3.5.0.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 Source #

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: 3.5.0.0

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

CROSS JOIN

Used as an infix `crossJoin`

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

Since: 3.5.0.0

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

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: 3.5.0.0

Set Operations

Data type that represents SQL set operations. This includes UNION, UNION ALL, EXCEPT, and INTERSECT. These types form a binary tree, with SqlQuery values on the leaves.

Each function corresponding to the aforementioned set operations can be used as an infix in a from to help with readability and lead to code that closely resembles the underlying SQL. For example,

select $ from $
  (do
     a <- from $ table A
     pure $ a ^. ASomeCol
  )
  `union_`
  (do
     b <- from $ table B
     pure $ b ^. BSomeCol
  )

is translated into

SELECT * FROM (
  (SELECT a.some_col FROM a)
  UNION
  (SELECT b.some_col FROM b)
)

union_ :: Union_ a => a Source #

UNION SQL set operation. Can be used as an infix function between SqlQuery values.

data Union a b Source #

Deprecated: Since: 3.4.0.0 - Use the union_ function instead of the Union data constructor

Constructors

a `Union` b

Deprecated: Since: 3.4.0.0 - Use the union_ function instead of the Union data constructor

Instances

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

Defined in Database.Esqueleto.Experimental.From.SqlSetOperation

unionAll_ :: UnionAll_ a => a Source #

UNION ALL SQL set operation. Can be used as an infix function between SqlQuery values.

data UnionAll a b Source #

Deprecated: Since: 3.4.0.0 - Use the unionAll_ function instead of the UnionAll data constructor

Constructors

a `UnionAll` b

Deprecated: Since: 3.4.0.0 - Use the unionAll_ function instead of the UnionAll data constructor

Instances

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

Defined in Database.Esqueleto.Experimental.From.SqlSetOperation

except_ :: (ToSqlSetOperation a a', ToSqlSetOperation b a') => a -> b -> SqlSetOperation a' Source #

EXCEPT SQL set operation. Can be used as an infix function between SqlQuery values.

data Except a b Source #

Deprecated: Since: 3.4.0.0 - Use the except_ function instead of the Except data constructor

Constructors

a `Except` b

Deprecated: Since: 3.4.0.0 - Use the except_ function instead of the Except data constructor

Instances

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

Defined in Database.Esqueleto.Experimental.From.SqlSetOperation

intersect_ :: (ToSqlSetOperation a a', ToSqlSetOperation b a') => a -> b -> SqlSetOperation a' Source #

INTERSECT SQL set operation. Can be used as an infix function between SqlQuery values.

data Intersect a b Source #

Deprecated: Since: 3.4.0.0 - Use the intersect_ function instead of the Intersect data constructor

Constructors

a `Intersect` b

Deprecated: Since: 3.4.0.0 - Use the intersect_ function instead of the Intersect data constructor

Instances

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

Defined in Database.Esqueleto.Experimental.From.SqlSetOperation

pattern SelectQuery :: p -> p Source #

Deprecated: Since: 3.4.0.0 - It is no longer necessary to tag SqlQuery values with SelectQuery

Common Table Expressions

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

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

withRecursive :: (ToAlias a, ToAliasReference a, SqlSelect a r) => SqlQuery a -> UnionKind -> (From a -> SqlQuery a) -> SqlQuery (From a) Source #

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

Internals

newtype From a Source #

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: 3.5.0.0

Constructors

From 

Fields

Instances

Instances details
ToFrom (From a) a Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: From a -> From a Source #

class ToMaybe a where Source #

Associated Types

type ToMaybeT a Source #

Methods

toMaybe :: a -> ToMaybeT a Source #

Instances

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

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Value a)) Source #

ToMaybe (SqlExpr (Entity a)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Entity a)) Source #

ToMaybe (SqlExpr (Maybe a)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Maybe a)) Source #

(ToMaybe a, ToMaybe b) => ToMaybe (a :& b) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Associated Types

type ToMaybeT (a :& b) Source #

Methods

toMaybe :: (a :& b) -> ToMaybeT (a :& b) Source #

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

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (a, b) Source #

Methods

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

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

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (a, b, c) Source #

Methods

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

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

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

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

Methods

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

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

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

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

Methods

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

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

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

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

Methods

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

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

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

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

Methods

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

(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) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

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

Methods

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

class ToAlias a where Source #

Methods

toAlias :: a -> SqlQuery a Source #

Instances

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

Defined in Database.Esqueleto.Experimental.ToAlias

ToAlias (SqlExpr (Entity a)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

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

Defined in Database.Esqueleto.Experimental.ToAlias

(ToAlias a, ToAlias b) => ToAlias (a :& b) Source #

Identical to the tuple instance and provided for convenience.

Since: 3.5.3.0

Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

toAlias :: (a :& b) -> SqlQuery (a :& b) Source #

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

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

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

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

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

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

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

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

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

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

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

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

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

Defined in Database.Esqueleto.Experimental.ToAlias

Methods

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

(ToAlias a, ToAlias b, ToAlias c, ToAlias d, ToAlias e, ToAlias f, ToAlias g) => ToAlias (a, b, c, d, e, f, g) Source # 
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) Source #

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

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

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

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

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

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

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

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

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

type ToAliasT a = a Source #

Deprecated: This type alias doesn't do anything. Please delete it. Will be removed in the next release.

class ToAliasReference a where Source #

Methods

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

Instances

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

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToAliasReference (SqlExpr (Entity a)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

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

Defined in Database.Esqueleto.Experimental.ToAliasReference

(ToAliasReference a, ToAliasReference b) => ToAliasReference (a :& b) Source #

Identical to the tuple instance and provided for convenience.

Since: 3.5.3.0

Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

toAliasReference :: Ident -> (a :& b) -> SqlQuery (a :& b) Source #

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

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

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

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

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

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

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

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

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

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

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

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

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

Defined in Database.Esqueleto.Experimental.ToAliasReference

Methods

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

(ToAliasReference a, ToAliasReference b, ToAliasReference c, ToAliasReference d, ToAliasReference e, ToAliasReference f, ToAliasReference g) => ToAliasReference (a, b, c, d, e, f, g) Source # 
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) Source #

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

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

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

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

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

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

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

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

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

type ToAliasReferenceT a = a Source #

Deprecated: This type alias doesn't do anything. Please delete it. Will be removed in the next release.

class ToSqlSetOperation a r | a -> r where Source #

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

Since: 3.5.0.0

The Normal Stuff

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

WHERE clause: restrict the query's result.

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

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

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

Since: 3.5.10.0

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

ORDER BY clause. See also asc and desc.

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

rand :: SqlExpr OrderBy Source #

Deprecated: Since 2.6.0: rand ordering function is not uniform across all databases! To avoid accidental partiality it will be removed in the next major version.

ORDER BY random() clause.

Since: 1.3.10

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

Ascending order of this field or SqlExpression.

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

Descending order of this field or SqlExpression.

limit :: Int64 -> SqlQuery () Source #

LIMIT. Limit the number of returned rows.

offset :: Int64 -> SqlQuery () Source #

OFFSET. Usually used with limit.

distinct :: SqlQuery a -> SqlQuery a Source #

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: 2.2.4

distinctOn :: [SqlExpr DistinctOn] -> SqlQuery a -> SqlQuery a Source #

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: 2.2.4

don :: SqlExpr (Value a) -> SqlExpr DistinctOn Source #

Erase an SqlExpression's type so that it's suitable to be used by distinctOn.

Since: 2.2.4

distinctOnOrderBy :: [SqlExpr OrderBy] -> SqlQuery a -> SqlQuery a Source #

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: 2.2.4

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

HAVING.

Since: 1.2.2

locking :: LockingKind -> SqlQuery () Source #

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: 2.2.7

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

Deprecated: sub_select sub_select is an unsafe function to use. If used with a SqlQuery that returns 0 results, then it may return NULL despite not mentioning Maybe in the return type. If it returns more than 1 result, then it will throw a SQL error. Instead, consider using one of the following alternatives: - subSelect: attaches a LIMIT 1 and the Maybe return type, totally safe. - subSelectMaybe: Attaches a LIMIT 1, useful for a query that already has a Maybe in the return type. - subSelectCount: Performs a count of the query - this is always safe. - subSelectUnsafe: Performs no checks or guarantees. Safe to use with countRows and friends.

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.

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

Project a field of an entity.

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

Project a field of an entity that may be null.

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

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

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

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}

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

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

Since: 3.5.10.0

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

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

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

NULL value.

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

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

withNonNull :: PersistField typ => SqlExpr (Value (Maybe typ)) -> (SqlExpr (Value typ) -> SqlQuery a) -> SqlQuery a Source #

Project an SqlExpression that may be null, guarding against null cases.

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

COUNT(*) value.

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

COUNT.

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

COUNT(DISTINCT x).

Since: 2.4.1

(==.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) infix 4 Source #

(>=.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) infix 4 Source #

(>.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) infix 4 Source #

(<=.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) infix 4 Source #

(<.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) infix 4 Source #

(!=.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) infix 4 Source #

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

BETWEEN.

@since: 3.1.0

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

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

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

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

random_ :: (PersistField a, Num a) => SqlExpr (Value a) Source #

Deprecated: Since 2.6.0: random_ is not uniform across all databases! Please use a specific one such as random_, random_, or random_

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

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: 2.2.9

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

Same as castNum, but for nullable values.

Since: 2.2.9

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

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: 1.4.3

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

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

Since: 1.4.3

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

LOWER function.

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

UPPER function. @since 3.3.0

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

TRIM function. @since 3.3.0

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

LTRIM function. @since 3.3.0

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

RTRIM function. @since 3.3.0

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

LENGTH function. @since 3.3.0

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

LEFT function. @since 3.3.0

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

RIGHT function. @since 3.3.0

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

LIKE operator.

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

ILIKE operator (case-insensitive LIKE).

Supported by PostgreSQL only.

Since: 2.2.3

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

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" ++. (%)

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

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

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

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

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

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.

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

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

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

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

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

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: 2.2.12

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

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].

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

NOT IN operator.

exists :: SqlQuery () -> SqlExpr (Value Bool) Source #

EXISTS operator. For example:

select $
from $ \person -> do
where_ $ exists $
         from $ \post -> do
         where_ (post ^. BlogPostAuthorId ==. person ^. PersonId)
return person

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

NOT EXISTS operator.

set :: PersistEntity val => SqlExpr (Entity val) -> [SqlExpr (Entity val) -> SqlExpr Update] -> SqlQuery () Source #

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.

(=.) :: (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update infixr 3 Source #

(+=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Entity val) -> SqlExpr Update infixr 3 Source #

(-=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Entity val) -> SqlExpr Update infixr 3 Source #

(*=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Entity val) -> SqlExpr Update infixr 3 Source #

(/=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Entity val) -> SqlExpr Update infixr 3 Source #

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

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: 2.1.2

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

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: 2.4.3

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

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: 3.2.0

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

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: 3.2.0

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

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: 3.2.0

subSelectForeign Source #

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: 3.2.0

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

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: 3.2.0

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

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: 3.2.0

class ToBaseId ent where Source #

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 :: Type Source #

e.g. type BaseEnt MyBase = MyChild

Methods

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

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.

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

Syntax sugar for case_.

Since: 2.1.2

then_ :: () Source #

Syntax sugar for case_.

Since: 2.1.2

else_ :: expr a -> expr a Source #

Syntax sugar for case_.

Since: 2.1.2

newtype Value a Source #

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

Since: 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 Source # 
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)) Source #

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: 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))) Source #

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: 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 Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

(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 Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

Show a => Show (Value a) Source # 
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)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

ToAliasReference (SqlExpr (Value a)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToMaybe (SqlExpr (Value a)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Value a)) Source #

ToSomeValues (SqlExpr (Value a)) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Eq a => Eq (Value a) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Ord a => Ord (Value a) Source # 
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) Source #

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

Instance details

Defined in Database.Esqueleto.Internal.Internal

type ToMaybeT (SqlExpr (Value a)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

newtype ValueList a Source #

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) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Eq a => Eq (ValueList a) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Ord a => Ord (ValueList a) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

data OrderBy Source #

Phantom type used by orderBy, asc and desc.

data DistinctOn Source #

Phantom type used by distinctOn and don.

data LockingKind Source #

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: 2.2.7

Constructors

ForUpdate

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

Since: 2.2.7

ForUpdateSkipLocked

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

Since: 2.2.7

ForShare

FOR SHARE syntax. Supported by PostgreSQL.

Since: 2.2.7

LockInShareMode

LOCK IN SHARE MODE syntax. Supported by MySQL.

Since: 2.2.7

class LockableEntity a where Source #

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

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: 2.4.0

Instances

Instances details
SqlString Html Source #

Since: 2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlString ByteString Source #

Since: 2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlString Text Source #

Since: 2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlString Text Source #

Since: 2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlString a => SqlString (Maybe a) Source #

Since: 2.4.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

a ~ Char => SqlString [a] Source #

Since: 2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

Joins

data InnerJoin a b infixl 2 Source #

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

Constructors

a `InnerJoin` b infixl 2 

Instances

Instances details
IsJoinKind InnerJoin Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

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

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (InnerJoin a b) Source #

(DoInnerJoin lateral lhs rhs r, lateral ~ IsLateral rhs) => ToFrom (InnerJoin lhs rhs) r Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

toFrom :: InnerJoin lhs rhs -> From r Source #

data CrossJoin a b infixl 2 Source #

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

Constructors

a `CrossJoin` b infixl 2 

Instances

Instances details
IsJoinKind CrossJoin Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

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

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (CrossJoin a b) Source #

(DoCrossJoin lateral lhs rhs r, IsLateral rhs ~ lateral) => ToFrom (CrossJoin lhs rhs) r Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

toFrom :: CrossJoin lhs rhs -> From r Source #

data LeftOuterJoin a b infixl 2 Source #

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 Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

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

Defined in Database.Esqueleto.Internal.Internal

(DoLeftJoin lateral lhs rhs r, lateral ~ IsLateral rhs) => ToFrom (LeftOuterJoin lhs rhs) r Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

toFrom :: LeftOuterJoin lhs rhs -> From r Source #

data RightOuterJoin a b infixl 2 Source #

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

Constructors

a `RightOuterJoin` b infixl 2 

Instances

Instances details
IsJoinKind RightOuterJoin Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

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

Defined in Database.Esqueleto.Internal.Internal

(ToFrom a a', ToFrom b b', ToMaybe a', ToMaybeT a' ~ ma, HasOnClause rhs (ma :& b'), ErrorOnLateral b, rhs ~ (b, (ma :& b') -> SqlExpr (Value Bool))) => ToFrom (RightOuterJoin a rhs) (ma :& b') Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

toFrom :: RightOuterJoin a rhs -> From (ma :& b') Source #

data FullOuterJoin a b infixl 2 Source #

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

Constructors

a `FullOuterJoin` b infixl 2 

Instances

Instances details
IsJoinKind FullOuterJoin Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

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

Defined in Database.Esqueleto.Internal.Internal

(ToFrom a a', ToFrom b b', ToMaybe a', ToMaybeT a' ~ ma, ToMaybe b', ToMaybeT b' ~ mb, HasOnClause rhs (ma :& mb), ErrorOnLateral b, rhs ~ (b, (ma :& mb) -> SqlExpr (Value Bool))) => ToFrom (FullOuterJoin a rhs) (ma :& mb) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

toFrom :: FullOuterJoin a rhs -> From (ma :& mb) Source #

data JoinKind Source #

(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 Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Eq JoinKind Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

data OnClauseWithoutMatchingJoinException Source #

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

Instances

Instances details
Exception OnClauseWithoutMatchingJoinException Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Show OnClauseWithoutMatchingJoinException Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Eq OnClauseWithoutMatchingJoinException Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Ord OnClauseWithoutMatchingJoinException Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Join Helpers

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

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: 3.5.9.0

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

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

Since: 3.5.9.0

class GetFirstTable t ts where Source #

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: 3.5.9.0

Methods

getFirstTable :: ts -> t Source #

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

Since: 3.5.9.0

Instances

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

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

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

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

GetFirstTable t (x :& t) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

SQL backend

data SqlQuery a Source #

SQL backend for esqueleto using SqlPersistT.

Instances

Instances details
Applicative SqlQuery Source # 
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 Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Monad SqlQuery Source # 
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 Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

(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 Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

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

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

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

Defined in Database.Esqueleto.Experimental.From

Methods

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

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

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: SqlQuery a -> From a Source #

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

Defined in Database.Esqueleto.Experimental.From.SqlSetOperation

ValidOnClause (a -> SqlQuery b) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

data SqlExpr a Source #

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

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: 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)) Source #

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: 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))) Source #

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: 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 Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

(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 Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

ToAlias (SqlExpr (Value a)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

ToAlias (SqlExpr (Entity a)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.ToAlias

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

Defined in Database.Esqueleto.Experimental.ToAlias

ToAliasReference (SqlExpr (Value a)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToAliasReference (SqlExpr (Entity a)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.ToAliasReference

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

Defined in Database.Esqueleto.Experimental.ToAliasReference

ToMaybe (SqlExpr (Value a)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Value a)) Source #

ToMaybe (SqlExpr (Entity a)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Entity a)) Source #

ToMaybe (SqlExpr (Maybe a)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

Associated Types

type ToMaybeT (SqlExpr (Maybe a)) Source #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Defined in Database.Esqueleto.Internal.Internal

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

Defined in Database.Esqueleto.Internal.Internal

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

Defined in Database.Esqueleto.Internal.Internal

ToSomeValues (SqlExpr (Value a)) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Defined in Database.Esqueleto.Experimental.From

Methods

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

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

INSERT INTO hack.

Instance details

Defined in Database.Esqueleto.Internal.Internal

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

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

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

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

Instance details

Defined in Database.Esqueleto.Internal.Internal

type ToMaybeT (SqlExpr (Value a)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (SqlExpr (Entity a)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

type ToMaybeT (SqlExpr (Maybe a)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.ToMaybe

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

Constraint synonym for persistent entities whose backend is SqlBackend.

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

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).

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

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

selectSource :: (SqlSelect a r, BackendCompatible SqlBackend backend, IsPersistBackend backend, PersistQueryRead backend, PersistStoreRead backend, PersistUniqueRead backend, MonadResource m) => SqlQuery a -> ConduitT () r (ReaderT backend m) () Source #

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

delete :: (MonadIO m, SqlBackendCanWrite backend) => SqlQuery () -> ReaderT backend m () Source #

Execute an esqueleto DELETE query inside persistent's SqlPersistT monad. Note that currently there are no type checks for statements that should not appear on a DELETE query.

Example of usage:

delete $
from $ \appointment ->
where_ (appointment ^. AppointmentDate <. val now)

Unlike select, there is a useful way of using delete that will lead to type ambiguities. If you want to delete all rows (i.e., no where_ clause), you'll have to use a type signature:

delete $
from $ \(appointment :: SqlExpr (Entity Appointment)) ->
return ()

Database.Esqueleto.Experimental:

 delete $ do
   userFeature <- from $ table @UserFeature
   where_ ((userFeature ^. UserFeatureFeature) notIn valList allKnownFeatureFlags)

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

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

update :: (MonadIO m, PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val), SqlBackendCanWrite backend) => (SqlExpr (Entity val) -> SqlQuery ()) -> ReaderT backend m () Source #

Execute an esqueleto UPDATE query inside persistent's SqlPersistT monad. Note that currently there are no type checks for statements that should not appear on a UPDATE query.

Example of usage:

update $ \p -> do
set p [ PersonAge =. just (val thisYear) -. p ^. PersonBorn ]
where_ $ isNothing (p ^. PersonAge)

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

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

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

Insert a PersistField for every selected value.

Since: 2.4.2

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

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

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

Apply a PersistField constructor to SqlExpr Value arguments.

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

Apply extra SqlExpr Value arguments to a PersistField constructor

Rendering Queries

renderQueryToText Source #

Arguments

:: (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: 3.1.1

renderQuerySelect Source #

Arguments

:: (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: 3.1.1

renderQueryUpdate Source #

Arguments

:: (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: 3.1.1

renderQueryDelete Source #

Arguments

:: (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: 3.1.1

renderQueryInsertInto Source #

Arguments

:: (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: 3.1.1

Helpers

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

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: 1.4.2

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

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: 3.1.2

Re-exports

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

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

transactionUndoWithIsolation :: forall (m :: Type -> Type). MonadIO m => IsolationLevel -> ReaderT SqlBackend m () #

Roll back the current transaction and begin a new one with the specified isolation level.

Since: persistent-2.9.0

transactionUndo :: forall (m :: Type -> Type). MonadIO m => ReaderT SqlBackend m () #

Roll back the current transaction and begin a new one. This rolls back to the state of the last call to transactionSave or the enclosing runSqlConn call.

Since: persistent-1.2.0

transactionSaveWithIsolation :: forall (m :: Type -> Type). MonadIO m => IsolationLevel -> ReaderT SqlBackend m () #

Commit the current transaction and begin a new one with the specified isolation level.

Since: persistent-2.9.0

transactionSave :: forall (m :: Type -> Type). MonadIO m => ReaderT SqlBackend m () #

Commit the current transaction and begin a new one. This is used when a transaction commit is required within the context of runSqlConn (which brackets its provided action with a transaction begin/commit pair).

Since: persistent-1.2.0

runSqlCommand :: SqlPersistT IO () -> Migration #

Run an action against the database during a migration. Can be useful for eg creating Postgres extensions:

runSqlCommand $ rawExecute "CREATE EXTENSION IF NOT EXISTS "uuid-ossp";" []

Since: persistent-2.13.0.0

addMigrations :: CautiousMigration -> Migration #

Add a CautiousMigration (aka a [(Bool, Text)]) to the migration plan.

Since: persistent-2.9.2

addMigration #

Arguments

:: Bool

Is the migration unsafe to run? (eg a destructive or non-idempotent update on the schema). If True, the migration is *unsafe*, and will need to be run manually later. If False, the migration is *safe*, and can be run any number of times.

-> Sql

A Text value representing the command to run on the database.

-> Migration 

Add a migration to the migration plan.

Since: persistent-2.9.2

reportErrors :: [Text] -> Migration #

Report multiple errors in a Migration.

Since: persistent-2.9.2

reportError :: Text -> Migration #

Report a single error in a Migration.

Since: persistent-2.9.2

migrate :: [EntityDef] -> EntityDef -> Migration #

Given a list of old entity definitions and a new EntityDef in val, this creates a Migration to update the old list of definitions with the new one.

runMigrationUnsafeQuiet :: forall (m :: Type -> Type). (HasCallStack, MonadIO m) => Migration -> ReaderT SqlBackend m [Text] #

Same as runMigrationUnsafe, but returns a list of the SQL commands executed instead of printing them to stderr.

Since: persistent-2.10.2

runMigrationUnsafe :: forall (m :: Type -> Type). MonadIO m => Migration -> ReaderT SqlBackend m () #

Like runMigration, but this will perform the unsafe database migrations instead of erroring out.

runMigrationSilent :: forall (m :: Type -> Type). MonadUnliftIO m => Migration -> ReaderT SqlBackend m [Text] #

Same as runMigration, but returns a list of the SQL commands executed instead of printing them to stderr.

This function silences the migration by remapping stderr. As a result, it is not thread-safe and can clobber output from other parts of the program. This implementation method was chosen to also silence postgresql migration output on stderr, but is not recommended!

runMigrationQuiet :: forall (m :: Type -> Type). MonadIO m => Migration -> ReaderT SqlBackend m [Text] #

Same as runMigration, but does not report the individual migrations on stderr. Instead it returns a list of the executed SQL commands.

This is a safer/more robust alternative to runMigrationSilent, but may be less silent for some persistent implementations, most notably persistent-postgresql

Since: persistent-2.10.2

runMigration :: forall (m :: Type -> Type). MonadIO m => Migration -> ReaderT SqlBackend m () #

Runs a migration. If the migration fails to parse or if any of the migrations are unsafe, then this throws a PersistUnsafeMigrationException.

getMigration :: forall (m :: Type -> Type). (MonadIO m, HasCallStack) => Migration -> ReaderT SqlBackend m [Sql] #

Return all of the Sql values associated with the given migration. Calls error if there's a parse error on any migration.

showMigration :: forall (m :: Type -> Type). (HasCallStack, MonadIO m) => Migration -> ReaderT SqlBackend m [Text] #

Convert a Migration to a list of Text values corresponding to their Sql statements.

printMigration :: forall (m :: Type -> Type). (HasCallStack, MonadIO m) => Migration -> ReaderT SqlBackend m () #

Prints a migration.

parseMigration' :: forall (m :: Type -> Type). (HasCallStack, MonadIO m) => Migration -> ReaderT SqlBackend m CautiousMigration #

Like parseMigration, but instead of returning the value in an Either value, it calls error on the error values.

parseMigration :: forall (m :: Type -> Type). (HasCallStack, MonadIO m) => Migration -> ReaderT SqlBackend m (Either [Text] CautiousMigration) #

Given a Migration, this parses it and returns either a list of errors associated with the migration or a list of migrations to do.

type Sql = Text #

type CautiousMigration = [(Bool, Sql)] #

A list of SQL operations, marked with a safety flag. If the Bool is True, then the operation is *unsafe* - it might be destructive, or otherwise not idempotent. If the Bool is False, then the operation is *safe*, and can be run repeatedly without issues.

type Migration = WriterT [Text] (WriterT CautiousMigration (ReaderT SqlBackend IO)) () #

A Migration is a four level monad stack consisting of:

newtype PersistUnsafeMigrationException #

An exception indicating that Persistent refused to run some unsafe migrations. Contains a list of pairs where the Bool tracks whether the migration was unsafe (True means unsafe), and the Sql is the sql statement for the migration.

Since: persistent-2.11.1.0

Instances

Instances details
Exception PersistUnsafeMigrationException 
Instance details

Defined in Database.Persist.Sql.Migration

Show PersistUnsafeMigrationException

This Show instance renders an error message suitable for printing to the console. This is a little dodgy, but since GHC uses Show instances when displaying uncaught exceptions, we have little choice.

Instance details

Defined in Database.Persist.Sql.Migration

decorateSQLWithLimitOffset :: Text -> (Int, Int) -> Text -> Text #

Generates sql for limit and offset for postgres, sqlite and mysql.

orderClause #

Arguments

:: PersistEntity val 
=> Maybe FilterTablePrefix

include table name or EXCLUDED

-> SqlBackend 
-> [SelectOpt val] 
-> Text 

Render a [SelectOpt record] made up *only* of Asc and Desc constructors into a Text value suitable for inclusion into a SQL query.

Since: persistent-2.13.2.0

filterClauseWithVals #

Arguments

:: PersistEntity val 
=> Maybe FilterTablePrefix

include table name or EXCLUDED

-> SqlBackend 
-> [Filter val] 
-> (Text, [PersistValue]) 

Render a [Filter record] into a Text value suitable for inclusion into a SQL query, as well as the [PersistValue] to properly fill in the ? place holders.

Since: persistent-2.12.1.0

filterClause #

Arguments

:: PersistEntity val 
=> Maybe FilterTablePrefix

include table name or EXCLUDED

-> SqlBackend 
-> [Filter val] 
-> Text 

Render a [Filter record] into a Text value suitable for inclusion into a SQL query.

Since: persistent-2.12.1.0

data FilterTablePrefix #

Used when determining how to prefix a column name in a WHERE clause.

Since: persistent-2.12.1.0

Constructors

PrefixTableName

Prefix the column with the table name. This is useful if the column name might be ambiguous.

Since: persistent-2.12.1.0

PrefixExcluded

Prefix the column name with the EXCLUDED keyword. This is used with the Postgresql backend when doing ON CONFLICT DO UPDATE clauses - see the documentation on upsertWhere and upsertManyWhere.

Since: persistent-2.12.1.0

fieldDBName :: PersistEntity record => EntityField record typ -> FieldNameDB #

useful for a backend to implement fieldName by adding escaping

getFieldName :: forall record typ (m :: Type -> Type) backend. (PersistEntity record, PersistEntityBackend record ~ SqlBackend, BackendCompatible SqlBackend backend, Monad m) => EntityField record typ -> ReaderT backend m Text #

get the SQL string for the field that an EntityField represents Useful for raw SQL queries

Your backend may provide a more convenient fieldName function which does not operate in a Monad

tableDBName :: PersistEntity record => record -> EntityNameDB #

useful for a backend to implement tableName by adding escaping

getTableName :: forall record (m :: Type -> Type) backend. (PersistEntity record, BackendCompatible SqlBackend backend, Monad m) => record -> ReaderT backend m Text #

get the SQL string for the table that a PeristEntity represents Useful for raw SQL queries

Your backend may provide a more convenient tableName function which does not operate in a Monad

fromSqlKey :: ToBackendKey SqlBackend record => Key record -> Int64 #

toSqlKey :: ToBackendKey SqlBackend record => Int64 -> Key record #

withRawQuery :: forall (m :: Type -> Type) a. MonadIO m => Text -> [PersistValue] -> ConduitM [PersistValue] Void IO a -> ReaderT SqlBackend m a #

close' :: BackendCompatible SqlBackend backend => backend -> IO () #

withSqlConn :: forall backend m a. (MonadUnliftIO m, MonadLoggerIO m, BackendCompatible SqlBackend backend) => (LogFunc -> IO backend) -> (backend -> m a) -> m a #

Create a connection and run sql queries within it. This function automatically closes the connection on it's completion.

Example usage

Expand
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies#-}
{-# LANGUAGE TemplateHaskell#-}
{-# LANGUAGE QuasiQuotes#-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}

import Control.Monad.IO.Class  (liftIO)
import Control.Monad.Logger
import Conduit
import Database.Persist
import Database.Sqlite
import Database.Persist.Sqlite
import Database.Persist.TH

share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase|
Person
  name String
  age Int Maybe
  deriving Show
|]

openConnection :: LogFunc -> IO SqlBackend
openConnection logfn = do
 conn <- open "/home/sibi/test.db"
 wrapConnection conn logfn

main :: IO ()
main = do
  runNoLoggingT $ runResourceT $ withSqlConn openConnection (\backend ->
                                      flip runSqlConn backend $ do
                                        runMigration migrateAll
                                        insert_ $ Person "John doe" $ Just 35
                                        insert_ $ Person "Divya" $ Just 36
                                        (pers :: [Entity Person]) <- selectList [] []
                                        liftIO $ print pers
                                        return ()
                                     )

On executing it, you get this output:

Migrating: CREATE TABLE "person"("id" INTEGER PRIMARY KEY,"name" VARCHAR NOT NULL,"age" INTEGER NULL)
[Entity {entityKey = PersonKey {unPersonKey = SqlBackendKey {unSqlBackendKey = 1}}, entityVal = Person {personName = "John doe", personAge = Just 35}},Entity {entityKey = PersonKey {unPersonKey = SqlBackendKey {unSqlBackendKey = 2}}, entityVal = Person {personName = "Hema", personAge = Just 36}}]

createSqlPoolWithConfig #

Arguments

:: (MonadLoggerIO m, MonadUnliftIO m, BackendCompatible SqlBackend backend) 
=> (LogFunc -> IO backend)

Function to create a new connection

-> ConnectionPoolConfig 
-> m (Pool backend) 

Creates a pool of connections to a SQL database.

Since: persistent-2.11.0.0

createSqlPool :: forall backend m. (MonadLoggerIO m, MonadUnliftIO m, BackendCompatible SqlBackend backend) => (LogFunc -> IO backend) -> Int -> m (Pool backend) #

withSqlPoolWithConfig #

Arguments

:: forall backend m a. (MonadLoggerIO m, MonadUnliftIO m, BackendCompatible SqlBackend backend) 
=> (LogFunc -> IO backend)

Function to create a new connection

-> ConnectionPoolConfig 
-> (Pool backend -> m a) 
-> m a 

Creates a pool of connections to a SQL database which can be used by the Pool backend -> m a function. After the function completes, the connections are destroyed.

Since: persistent-2.11.0.0

withSqlPool #

Arguments

:: forall backend m a. (MonadLoggerIO m, MonadUnliftIO m, BackendCompatible SqlBackend backend) 
=> (LogFunc -> IO backend)

create a new connection

-> Int

connection count

-> (Pool backend -> m a) 
-> m a 

liftSqlPersistMPool :: forall backend m a. (MonadIO m, BackendCompatible SqlBackend backend) => ReaderT backend (NoLoggingT (ResourceT IO)) a -> Pool backend -> m a #

runSqlPersistM :: BackendCompatible SqlBackend backend => ReaderT backend (NoLoggingT (ResourceT IO)) a -> backend -> IO a #

runSqlConnWithIsolation :: forall backend m a. (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> backend -> IsolationLevel -> m a #

Like runSqlConn, but supports specifying an isolation level.

Since: persistent-2.9.0

runSqlConn :: forall backend m a. (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> backend -> m a #

acquireSqlConnWithIsolation :: (MonadReader backend m, BackendCompatible SqlBackend backend) => IsolationLevel -> m (Acquire backend) #

Like acquireSqlConn, but lets you specify an explicit isolation level.

Since: persistent-2.10.5

acquireSqlConn :: (MonadReader backend m, BackendCompatible SqlBackend backend) => m (Acquire backend) #

Starts a new transaction on the connection. When the acquired connection is released the transaction is committed and the connection returned to the pool.

Upon an exception the transaction is rolled back and the connection destroyed.

This is equivalent to runSqlConn but does not incur the MonadUnliftIO constraint, meaning it can be used within, for example, a Conduit pipeline.

Since: persistent-2.10.5

runSqlPoolWithExtensibleHooks :: forall backend m a. (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> Pool backend -> Maybe IsolationLevel -> SqlPoolHooks m backend -> m a #

This function is how runSqlPoolWithHooks is defined.

It's currently the most general function for using a SQL pool.

Since: persistent-2.13.0.0

runSqlPoolWithHooks #

Arguments

:: forall backend m a before after onException. (MonadUnliftIO m, BackendCompatible SqlBackend backend) 
=> ReaderT backend m a 
-> Pool backend 
-> Maybe IsolationLevel 
-> (backend -> m before)

Run this action immediately before the action is performed.

-> (backend -> m after)

Run this action immediately after the action is completed.

-> (backend -> SomeException -> m onException)

This action is performed when an exception is received. The exception is provided as a convenience - it is rethrown once this cleanup function is complete.

-> m a 

This function is how runSqlPool and runSqlPoolNoTransaction are defined. In addition to the action to be performed and the Pool of conections to use, we give you the opportunity to provide three actions - initialize, afterwards, and onException.

Since: persistent-2.12.0.0

runSqlPoolNoTransaction :: forall backend m a. (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> Pool backend -> Maybe IsolationLevel -> m a #

Like runSqlPool, but does not surround the action in a transaction. This action might leave your database in a weird state.

Since: persistent-2.12.0.0

runSqlPoolWithIsolation :: forall backend m a. (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> Pool backend -> IsolationLevel -> m a #

Like runSqlPool, but supports specifying an isolation level.

Since: persistent-2.9.0

runSqlPool :: forall backend m a. (MonadUnliftIO m, BackendCompatible SqlBackend backend) => ReaderT backend m a -> Pool backend -> m a #

Get a connection from the pool, run the given action, and then return the connection to the pool.

This function performs the given action in a transaction. If an exception occurs during the action, then the transaction is rolled back.

Note: This function previously timed out after 2 seconds, but this behavior was buggy and caused more problems than it solved. Since version 2.1.2, it performs no timeout checks.

rawSql #

Arguments

:: forall a (m :: Type -> Type) backend. (RawSql a, MonadIO m, BackendCompatible SqlBackend backend) 
=> Text

SQL statement, possibly with placeholders.

-> [PersistValue]

Values to fill the placeholders.

-> ReaderT backend m [a] 

Execute a raw SQL statement and return its results as a list. If you do not expect a return value, use of rawExecute is recommended.

If you're using Entitys (which is quite likely), then you must use entity selection placeholders (double question mark, ??). These ?? placeholders are then replaced for the names of the columns that we need for your entities. You'll receive an error if you don't use the placeholders. Please see the Entitys documentation for more details.

You may put value placeholders (question marks, ?) in your SQL query. These placeholders are then replaced by the values you pass on the second parameter, already correctly escaped. You may want to use toPersistValue to help you constructing the placeholder values.

Since you're giving a raw SQL statement, you don't get any guarantees regarding safety. If rawSql is not able to parse the results of your query back, then an exception is raised. However, most common problems are mitigated by using the entity selection placeholder ??, and you shouldn't see any error at all if you're not using Single.

Some example of rawSql based on this schema:

share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase|
Person
    name String
    age Int Maybe
    deriving Show
BlogPost
    title String
    authorId PersonId
    deriving Show
|]

Examples based on the above schema:

getPerson :: MonadIO m => ReaderT SqlBackend m [Entity Person]
getPerson = rawSql "select ?? from person where name=?" [PersistText "john"]

getAge :: MonadIO m => ReaderT SqlBackend m [Single Int]
getAge = rawSql "select person.age from person where name=?" [PersistText "john"]

getAgeName :: MonadIO m => ReaderT SqlBackend m [(Single Int, Single Text)]
getAgeName = rawSql "select person.age, person.name from person where name=?" [PersistText "john"]

getPersonBlog :: MonadIO m => ReaderT SqlBackend m [(Entity Person, Entity BlogPost)]
getPersonBlog = rawSql "select ??,?? from person,blog_post where person.id = blog_post.author_id" []

Minimal working program for PostgreSQL backend based on the above concepts:

{-# LANGUAGE EmptyDataDecls             #-}
{-# LANGUAGE FlexibleContexts           #-}
{-# LANGUAGE GADTs                      #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses      #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE QuasiQuotes                #-}
{-# LANGUAGE TemplateHaskell            #-}
{-# LANGUAGE TypeFamilies               #-}

import           Control.Monad.IO.Class  (liftIO)
import           Control.Monad.Logger    (runStderrLoggingT)
import           Database.Persist
import           Control.Monad.Reader
import           Data.Text
import           Database.Persist.Sql
import           Database.Persist.Postgresql
import           Database.Persist.TH

share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase|
Person
    name String
    age Int Maybe
    deriving Show
|]

conn = "host=localhost dbname=new_db user=postgres password=postgres port=5432"

getPerson :: MonadIO m => ReaderT SqlBackend m [Entity Person]
getPerson = rawSql "select ?? from person where name=?" [PersistText "sibi"]

liftSqlPersistMPool y x = liftIO (runSqlPersistMPool y x)

main :: IO ()
main = runStderrLoggingT $ withPostgresqlPool conn 10 $ liftSqlPersistMPool $ do
         runMigration migrateAll
         xs <- getPerson
         liftIO (print xs)

rawExecuteCount #

Arguments

:: forall (m :: Type -> Type) backend. (MonadIO m, BackendCompatible SqlBackend backend) 
=> Text

SQL statement, possibly with placeholders.

-> [PersistValue]

Values to fill the placeholders.

-> ReaderT backend m Int64 

Execute a raw SQL statement and return the number of rows it has modified.

rawExecute #

Arguments

:: forall (m :: Type -> Type) backend. (MonadIO m, BackendCompatible SqlBackend backend) 
=> Text

SQL statement, possibly with placeholders.

-> [PersistValue]

Values to fill the placeholders.

-> ReaderT backend m () 

Execute a raw SQL statement

rawQueryRes :: forall (m1 :: Type -> Type) (m2 :: Type -> Type) env. (MonadIO m1, MonadIO m2, BackendCompatible SqlBackend env) => Text -> [PersistValue] -> ReaderT env m1 (Acquire (ConduitM () [PersistValue] m2 ())) #

rawQuery :: forall (m :: Type -> Type) env. (MonadResource m, MonadReader env m, BackendCompatible SqlBackend env) => Text -> [PersistValue] -> ConduitM () [PersistValue] m () #

unPrefix :: forall (prefix :: Symbol) record. EntityWithPrefix prefix record -> Entity record #

A helper function to tell GHC what the EntityWithPrefix prefix should be. This allows you to use a type application to specify the prefix, instead of specifying the etype on the result.

As an example, here's code that uses this:

myQuery :: SqlPersistM [Entity Person]
myQuery = fmap (unPrefix @"p") $ rawSql query []
  where
    query = "SELECT ?? FROM person AS p"

Since: persistent-2.10.5

class RawSql a where #

Class for data types that may be retrived from a rawSql query.

Methods

rawSqlCols :: (Text -> Text) -> a -> (Int, [Text]) #

Number of columns that this data type needs and the list of substitutions for SELECT placeholders ??.

rawSqlColCountReason :: a -> String #

A string telling the user why the column count is what it is.

rawSqlProcessRow :: [PersistValue] -> Either Text a #

Transform a row of the result into the data type.

Instances

Instances details
(PersistEntity record, PersistEntityBackend record ~ backend, IsPersistBackend backend) => RawSql (Entity record) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> Entity record -> (Int, [Text]) #

rawSqlColCountReason :: Entity record -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (Entity record) #

(PersistEntity a, PersistEntityBackend a ~ backend, IsPersistBackend backend) => RawSql (Key a) 
Instance details

Defined in Database.Persist.Sql.Class

PersistField a => RawSql (Single a) 
Instance details

Defined in Database.Persist.Sql.Class

RawSql a => RawSql (Maybe a)

Since: persistent-1.0.1

Instance details

Defined in Database.Persist.Sql.Class

(PersistEntity record, KnownSymbol prefix, PersistEntityBackend record ~ backend, IsPersistBackend backend) => RawSql (EntityWithPrefix prefix record) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> EntityWithPrefix prefix record -> (Int, [Text]) #

rawSqlColCountReason :: EntityWithPrefix prefix record -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (EntityWithPrefix prefix record) #

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

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b) #

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

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c) #

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

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d) #

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

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e) #

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

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f) #

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

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g) #

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

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h) -> (Int, [Text]) #

rawSqlColCountReason :: (a, b, c, d, e, f, g, h) -> String #

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h) #

(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i) => RawSql (a, b, c, d, e, f, g, h, i)

Since: persistent-2.10.2

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (Text -> Text) -> (a, b, c, d, e, f, g, h, i) -> (Int, [Text]) #

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

rawSqlProcessRow :: [PersistValue] -> Either Text (a, b, c, d, e, f, g, h, i) #

(RawSql a, RawSql b, RawSql c, RawSql d, RawSql e, RawSql f, RawSql g, RawSql h, RawSql i, RawSql j) => RawSql (a, b, c, d, e, f, g, h, i, j)

Since: persistent-2.10.2

Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (