esqueleto-2.1.2.3: Type-safe EDSL for SQL queries on persistent backends.

Safe HaskellNone
LanguageHaskell98

Database.Esqueleto.Internal.Language

Contents

Description

This is an internal module, anything exported by this module may change without a major version bump. Please use only Database.Esqueleto if possible.

Synopsis

The pretty face

class (Functor query, Applicative query, Monad query) => Esqueleto query expr backend | query -> expr backend, expr -> query backend where Source

Finally tagless representation of esqueleto's EDSL.

Methods

fromStart :: (PersistEntity a, PersistEntityBackend a ~ backend) => query (expr (PreprocessedFrom (expr (Entity a)))) Source

(Internal) Start a from query with an entity. from does two kinds of magic using fromStart, fromJoin and fromFinish:

  1. The simple but tedious magic of allowing tuples to be used.
  2. The more advanced magic of creating JOINs. The JOIN is processed from right to left. The rightmost entity of the JOIN is created with fromStart. Each JOIN step is then translated into a call to fromJoin. In the end, fromFinish is called to materialize the JOIN.

fromStartMaybe :: (PersistEntity a, PersistEntityBackend a ~ backend) => query (expr (PreprocessedFrom (expr (Maybe (Entity a))))) Source

(Internal) Same as fromStart, but entity may be missing.

fromJoin :: IsJoinKind join => expr (PreprocessedFrom a) -> expr (PreprocessedFrom b) -> query (expr (PreprocessedFrom (join a b))) Source

(Internal) Do a JOIN.

fromFinish :: expr (PreprocessedFrom a) -> query a Source

(Internal) Finish a JOIN.

where_ :: expr (Value Bool) -> query () Source

WHERE clause: restrict the query's result.

on :: expr (Value Bool) -> query () Source

ON clause: restrict the a JOIN's result. The ON clause will be applied to the last JOIN that does not have an ON clause yet. If there are no JOINs without ON clauses (either because you didn't do any JOIN, or because all JOINs already have their own ON clauses), a runtime exception OnClauseWithoutMatchingJoinException is thrown. ON clauses are optional when doing JOINs.

On the simple case of doing just one JOIN, for example

select $
from $ \(foo ``InnerJoin`` bar) -> do
  on (foo ^. FooId ==. bar ^. BarFooId)
  ...

there's no ambiguity and the rules above just mean that you're allowed to call on only once (as in SQL). If you have many joins, then the ons are applied on the reverse order that the JOINs appear. For example:

select $
from $ \(foo ``InnerJoin`` bar ``InnerJoin`` baz) -> do
  on (baz ^. BazId ==. bar ^. BarBazId)
  on (foo ^. FooId ==. bar ^. BarFooId)
  ...

The order is reversed in order to improve composability. For example, consider query1 and query2 below:

let query1 =
      from $ \(foo ``InnerJoin`` bar) -> do
        on (foo ^. FooId ==. bar ^. BarFooId)
    query2 =
      from $ \(mbaz ``LeftOuterJoin`` quux) -> do
        return (mbaz ?. BazName, quux)
    test1 =      (,) <$> query1 <*> query2
    test2 = flip (,) <$> query2 <*> query1

If the order was not reversed, then test2 would be broken: query1's on would refer to query2's LeftOuterJoin.

groupBy :: ToSomeValues expr a => a -> query () 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 SqlExpr (Value Int) to avoid ambiguity):

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)

orderBy :: [expr OrderBy] -> query () Source

ORDER BY clause. See also asc and desc.

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

Ascending order of this field or expression.

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

Descending order of this field or expression.

limit :: Int64 -> query () Source

LIMIT. Limit the number of returned rows.

offset :: Int64 -> query () Source

OFFSET. Usually used with limit.

rand :: expr OrderBy Source

ORDER BY random() clause.

Since: 1.3.10

having :: expr (Value Bool) -> query () Source

HAVING.

Since: 1.2.2

sub_select :: PersistField a => query (expr (Value a)) -> expr (Value a) Source

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

sub_selectDistinct :: PersistField a => query (expr (Value a)) -> expr (Value a) Source

Same as sub_select but using SELECT DISTINCT.

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

Project a field of an entity.

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

Project a field of an entity that may be null.

val :: PersistField typ => typ -> expr (Value typ) Source

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

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

IS NULL comparison.

just :: expr (Value typ) -> expr (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 :: expr (Value (Maybe typ)) Source

NULL value.

joinV :: expr (Value (Maybe (Maybe typ))) -> expr (Value (Maybe typ)) Source

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

countRows :: Num a => expr (Value a) Source

COUNT(*) value.

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

COUNT.

not_ :: expr (Value Bool) -> expr (Value Bool) Source

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

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

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

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

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

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

(&&.) :: expr (Value Bool) -> expr (Value Bool) -> expr (Value Bool) infixr 3 Source

(||.) :: expr (Value Bool) -> expr (Value Bool) -> expr (Value Bool) infixr 2 Source

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

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

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

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

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

round_ :: (PersistField a, Num a, PersistField b, Num b) => expr (Value a) -> expr (Value b) Source

ceiling_ :: (PersistField a, Num a, PersistField b, Num b) => expr (Value a) -> expr (Value b) Source

floor_ :: (PersistField a, Num a, PersistField b, Num b) => expr (Value a) -> expr (Value b) Source

sum_ :: (PersistField a, PersistField b) => expr (Value a) -> expr (Value (Maybe b)) Source

min_ :: PersistField a => expr (Value a) -> expr (Value (Maybe a)) Source

max_ :: PersistField a => expr (Value a) -> expr (Value (Maybe a)) Source

avg_ :: (PersistField a, PersistField b) => expr (Value a) -> expr (Value (Maybe b)) Source

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

COALESCE function. Evaluates the arguments in order and returns the value of the first non-NULL expression, 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 => [expr (Value (Maybe a))] -> expr (Value a) -> expr (Value a) Source

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

Since: 1.4.3

like :: (PersistField s, IsString s) => expr (Value s) -> expr (Value s) -> expr (Value Bool) infixr 2 Source

LIKE operator.

(%) :: (PersistField s, IsString s) => expr (Value s) Source

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

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

concat_ :: (PersistField s, IsString s) => [expr (Value s)] -> expr (Value s) Source

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

(++.) :: (PersistField s, IsString s) => expr (Value s) -> expr (Value s) -> expr (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.

subList_select :: PersistField a => query (expr (Value a)) -> expr (ValueList a) Source

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

subList_selectDistinct :: PersistField a => query (expr (Value a)) -> expr (ValueList a) Source

Same as sublist_select but using SELECT DISTINCT.

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

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

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

IN operator.

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

NOT IN operator.

exists :: query () -> expr (Value Bool) Source

EXISTS operator. For example:

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

notExists :: query () -> expr (Value Bool) Source

NOT EXISTS operator.

set :: PersistEntity val => expr (Entity val) -> [expr (Update val)] -> query () 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 -> expr (Value typ) -> expr (Update val) infixr 3 Source

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

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

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

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

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

Apply a PersistField constructor to expr Value arguments.

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

Apply extra expr Value arguments to a PersistField constructor

case_ :: PersistField a => [(expr (Value Bool), expr (Value a))] -> expr (Value a) -> expr (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

from :: From query expr backend a => (a -> query b) -> query b Source

FROM clause: bring entities into scope.

This function internally uses two type classes in order to provide some flexibility of how you may call it. Internally we refer to these type classes as the two different magics.

The innermost magic allows you to use from with the following types:

  • expr (Entity val), which brings a single entity into scope.
  • expr (Maybe (Entity val)), which brings a single entity that may be NULL into scope. Used for OUTER JOINs.
  • A JOIN of any other two types allowed by the innermost magic, where a JOIN may be an InnerJoin, a CrossJoin, a LeftOuterJoin, a RightOuterJoin, or a FullOuterJoin. The JOINs have right fixity, the same as in SQL.

The outermost magic allows you to use from on any tuples of types supported by innermost magic (and also tuples of tuples, and so on), up to 8-tuples.

Note that using from for the same entity twice does work and corresponds to a self-join. You don't even need to use two different calls to from, you may use a JOIN or a tuple.

The following are valid examples of uses of from (the types of the arguments of the lambda are inside square brackets):

from $ \person -> ...
from $ \(person, blogPost) -> ...
from $ \(p ``LeftOuterJoin`` mb) -> ...
from $ \(p1 ``InnerJoin`` f ``InnerJoin`` p2) -> ...
from $ \((p1 ``InnerJoin`` f) ``InnerJoin`` p2) -> ...

The types of the arguments to the lambdas above are, respectively:

person
  :: ( Esqueleto query expr backend
     , PersistEntity Person
     , PersistEntityBackend Person ~ backend
     ) => expr (Entity Person)
(person, blogPost)
  :: (...) => (expr (Entity Person), expr (Entity BlogPost))
(p ``LeftOuterJoin`` mb)
  :: (...) => InnerJoin (expr (Entity Person)) (expr (Maybe (Entity BlogPost)))
(p1 ``InnerJoin`` f ``InnerJoin`` p2)
  :: (...) => InnerJoin
                (expr (Entity Person))
                (InnerJoin (expr (Entity Follow))
                           (expr (Entity Person)))
((p1 ``InnerJoin`` f) ``InnerJoin`` p2) ::
  :: (...) => InnerJoin
                (InnerJoin (expr (Entity Person))
                           (expr (Entity Follow)))
                (expr (Entity Person))

Note that some backends may not support all kinds of JOINs. For example, when using the SQL backend with SQLite, it will not accept the last example above (which is associated to the left, instead of being to the right) and will not accept RightOuterJoins or FullOuterJoins.

data 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 a 

Instances

Functor Value

Since: 1.4.4

ToSomeValues SqlExpr (SqlExpr (Value a)) 
Eq a => Eq (Value a) 
Ord a => Ord (Value a) 
Show a => Show (Value a) 
PersistField a => SqlSelect (SqlExpr (Value a)) (Value a)

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

Typeable (* -> *) Value 

unValue :: Value a -> a Source

Unwrap a Value.

Since: 1.4.1

data 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

Eq a => Eq (ValueList a) 
Ord a => Ord (ValueList a) 
Show a => Show (ValueList a) 
Typeable (* -> *) ValueList 

data SomeValue expr where Source

A wrapper type for for any expr (Value a) for all a.

Constructors

SomeValue :: Esqueleto query expr backend => expr (Value a) -> SomeValue expr 

class ToSomeValues expr a where Source

A class of things that can be converted into a list of SomeValue. It has instances for tuples and is the reason why groupBy can take tuples, like groupBy (foo ^. FooId, foo ^. FooName, foo ^. FooType).

Methods

toSomeValues :: a -> [SomeValue expr] Source

Instances

ToSomeValues SqlExpr (SqlExpr (Value a)) 
(ToSomeValues expr a, ToSomeValues expr b) => ToSomeValues expr (a, b) 
(ToSomeValues expr a, ToSomeValues expr b, ToSomeValues expr c) => ToSomeValues expr (a, b, c) 
(ToSomeValues expr a, ToSomeValues expr b, ToSomeValues expr c, ToSomeValues expr d) => ToSomeValues expr (a, b, c, d) 
(ToSomeValues expr a, ToSomeValues expr b, ToSomeValues expr c, ToSomeValues expr d, ToSomeValues expr e) => ToSomeValues expr (a, b, c, d, e) 
(ToSomeValues expr a, ToSomeValues expr b, ToSomeValues expr c, ToSomeValues expr d, ToSomeValues expr e, ToSomeValues expr f) => ToSomeValues expr (a, b, c, d, e, f) 
(ToSomeValues expr a, ToSomeValues expr b, ToSomeValues expr c, ToSomeValues expr d, ToSomeValues expr e, ToSomeValues expr f, ToSomeValues expr g) => ToSomeValues expr (a, b, c, d, e, f, g) 
(ToSomeValues expr a, ToSomeValues expr b, ToSomeValues expr c, ToSomeValues expr d, ToSomeValues expr e, ToSomeValues expr f, ToSomeValues expr g, ToSomeValues expr h) => ToSomeValues expr (a, b, c, d, e, f, g, h) 

data InnerJoin a b infixr 2 Source

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

Constructors

a `InnerJoin` b infixr 2 

Instances

IsJoinKind InnerJoin 
(Esqueleto query expr backend, FromPreprocess query expr backend (InnerJoin a b)) => From query expr backend (InnerJoin a b) 

data CrossJoin a b infixr 2 Source

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

Constructors

a `CrossJoin` b infixr 2 

Instances

IsJoinKind CrossJoin 
(Esqueleto query expr backend, FromPreprocess query expr backend (CrossJoin a b)) => From query expr backend (CrossJoin a b) 

data LeftOuterJoin a b infixr 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 infixr 2 

Instances

IsJoinKind LeftOuterJoin 
(Esqueleto query expr backend, FromPreprocess query expr backend (LeftOuterJoin a b)) => From query expr backend (LeftOuterJoin a b) 

data RightOuterJoin a b infixr 2 Source

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

Constructors

a `RightOuterJoin` b infixr 2 

Instances

IsJoinKind RightOuterJoin 
(Esqueleto query expr backend, FromPreprocess query expr backend (RightOuterJoin a b)) => From query expr backend (RightOuterJoin a b) 

data FullOuterJoin a b infixr 2 Source

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

Constructors

a `FullOuterJoin` b infixr 2 

Instances

IsJoinKind FullOuterJoin 
(Esqueleto query expr backend, FromPreprocess query expr backend (FullOuterJoin a b)) => From query expr backend (FullOuterJoin a b) 

data OrderBy Source

Phantom type used by orderBy, asc and desc.

data Update typ Source

Phantom type for a SET operation on an entity of the given type (see set and '(=.)').

data Insertion a Source

Phantom type used by insertSelect.

The guts

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

class IsJoinKind join where Source

(Internal) Functions that operate on types (that should be) of kind JoinKind.

Methods

smartJoin :: a -> b -> join a b Source

(Internal) smartJoin a b is a JOIN of the correct kind.

reifyJoinKind :: join a b -> JoinKind Source

(Internal) Reify a JoinKind from a JOIN. This function is non-strict.

data PreprocessedFrom a Source

(Internal) Phantom type used to process from (see fromStart).

class Esqueleto query expr backend => From query expr backend a Source

(Internal) Class that implements the tuple from magic (see fromStart).

Minimal complete definition

from_

Instances

(Esqueleto query expr backend, FromPreprocess query expr backend (expr (Maybe (Entity val)))) => From query expr backend (expr (Maybe (Entity val))) 
(Esqueleto query expr backend, FromPreprocess query expr backend (expr (Entity val))) => From query expr backend (expr (Entity val)) 
(From query expr backend a, From query expr backend b) => From query expr backend (a, b) 
(Esqueleto query expr backend, FromPreprocess query expr backend (FullOuterJoin a b)) => From query expr backend (FullOuterJoin a b) 
(Esqueleto query expr backend, FromPreprocess query expr backend (RightOuterJoin a b)) => From query expr backend (RightOuterJoin a b) 
(Esqueleto query expr backend, FromPreprocess query expr backend (LeftOuterJoin a b)) => From query expr backend (LeftOuterJoin a b) 
(Esqueleto query expr backend, FromPreprocess query expr backend (CrossJoin a b)) => From query expr backend (CrossJoin a b) 
(Esqueleto query expr backend, FromPreprocess query expr backend (InnerJoin a b)) => From query expr backend (InnerJoin a b) 
(From query expr backend a, From query expr backend b, From query expr backend c) => From query expr backend (a, b, c) 
(From query expr backend a, From query expr backend b, From query expr backend c, From query expr backend d) => From query expr backend (a, b, c, d) 
(From query expr backend a, From query expr backend b, From query expr backend c, From query expr backend d, From query expr backend e) => From query expr backend (a, b, c, d, e) 
(From query expr backend a, From query expr backend b, From query expr backend c, From query expr backend d, From query expr backend e, From query expr backend f) => From query expr backend (a, b, c, d, e, f) 
(From query expr backend a, From query expr backend b, From query expr backend c, From query expr backend d, From query expr backend e, From query expr backend f, From query expr backend g) => From query expr backend (a, b, c, d, e, f, g) 
(From query expr backend a, From query expr backend b, From query expr backend c, From query expr backend d, From query expr backend e, From query expr backend f, From query expr backend g, From query expr backend h) => From query expr backend (a, b, c, d, e, f, g, h) 

class Esqueleto query expr backend => FromPreprocess query expr backend a Source

(Internal) Class that implements the JOIN from magic (see fromStart).

Minimal complete definition

fromPreprocess

Instances

(Esqueleto query expr backend, PersistEntity val, (~) * (PersistEntityBackend val) backend) => FromPreprocess query expr backend (expr (Maybe (Entity val))) 
(Esqueleto query expr backend, PersistEntity val, (~) * (PersistEntityBackend val) backend) => FromPreprocess query expr backend (expr (Entity val)) 
(Esqueleto query expr backend, FromPreprocess query expr backend a, FromPreprocess query expr backend b, IsJoinKind join) => FromPreprocess query expr backend (join a b) 

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