Safe Haskell | Safe-Infered |
---|
This is an internal module, anything exported by this module may change without a major version bump. Please use only Database.Esqueleto if possible.
- class (Functor query, Applicative query, Monad query) => Esqueleto query expr backend | query -> expr backend, expr -> query backend where
- fromStart :: (PersistEntity a, PersistEntityBackend a ~ backend) => query (expr (PreprocessedFrom (expr (Entity a))))
- fromStartMaybe :: (PersistEntity a, PersistEntityBackend a ~ backend) => query (expr (PreprocessedFrom (expr (Maybe (Entity a)))))
- fromJoin :: IsJoinKind join => expr (PreprocessedFrom a) -> expr (PreprocessedFrom b) -> query (expr (PreprocessedFrom (join a b)))
- fromFinish :: expr (PreprocessedFrom a) -> query a
- where_ :: expr (Value Bool) -> query ()
- on :: expr (Value Bool) -> query ()
- orderBy :: [expr OrderBy] -> query ()
- asc :: PersistField a => expr (Value a) -> expr OrderBy
- desc :: PersistField a => expr (Value a) -> expr OrderBy
- sub_select :: PersistField a => query (expr (Value a)) -> expr (Value a)
- sub_selectDistinct :: PersistField a => query (expr (Value a)) -> expr (Value a)
- (^.) :: (PersistEntity val, PersistField typ) => expr (Entity val) -> EntityField val typ -> expr (Value typ)
- (?.) :: (PersistEntity val, PersistField typ) => expr (Maybe (Entity val)) -> EntityField val typ -> expr (Value (Maybe typ))
- val :: PersistField typ => typ -> expr (Value typ)
- isNothing :: PersistField typ => expr (Value (Maybe typ)) -> expr (Value Bool)
- just :: expr (Value typ) -> expr (Value (Maybe typ))
- nothing :: expr (Value (Maybe typ))
- countRows :: Num a => expr (Value a)
- not_ :: expr (Value Bool) -> expr (Value Bool)
- (==.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool)
- (>=.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool)
- (>.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool)
- (<=.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool)
- (<.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool)
- (!=.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool)
- (&&.) :: expr (Value Bool) -> expr (Value Bool) -> expr (Value Bool)
- (||.) :: expr (Value Bool) -> expr (Value Bool) -> expr (Value Bool)
- (+.) :: PersistField a => expr (Value a) -> expr (Value a) -> expr (Value a)
- (-.) :: PersistField a => expr (Value a) -> expr (Value a) -> expr (Value a)
- (/.) :: PersistField a => expr (Value a) -> expr (Value a) -> expr (Value a)
- (*.) :: PersistField a => expr (Value a) -> expr (Value a) -> expr (Value a)
- set :: PersistEntity val => expr (Entity val) -> [expr (Update val)] -> query ()
- (=.) :: (PersistEntity val, PersistField typ) => EntityField val typ -> expr (Value typ) -> expr (Update val)
- (+=.) :: (PersistEntity val, PersistField a) => EntityField val a -> expr (Value a) -> expr (Update val)
- (-=.) :: (PersistEntity val, PersistField a) => EntityField val a -> expr (Value a) -> expr (Update val)
- (*=.) :: (PersistEntity val, PersistField a) => EntityField val a -> expr (Value a) -> expr (Update val)
- (/=.) :: (PersistEntity val, PersistField a) => EntityField val a -> expr (Value a) -> expr (Update val)
- from :: From query expr backend a => (a -> query b) -> query b
- data Value a = Value a
- data InnerJoin a b = a InnerJoin b
- data CrossJoin a b = a CrossJoin b
- data LeftOuterJoin a b = a LeftOuterJoin b
- data RightOuterJoin a b = a RightOuterJoin b
- data FullOuterJoin a b = a FullOuterJoin b
- data OnClauseWithoutMatchingJoinException = OnClauseWithoutMatchingJoinException String
- data OrderBy
- data Update typ
- data JoinKind
- class IsJoinKind join where
- smartJoin :: a -> b -> join a b
- reifyJoinKind :: join a b -> JoinKind
- data PreprocessedFrom a
- class Esqueleto query expr backend => From query expr backend a
- class Esqueleto query expr backend => FromPreprocess query expr backend a
The pretty face
class (Functor query, Applicative query, Monad query) => Esqueleto query expr backend | query -> expr backend, expr -> query backend whereSource
Finally tagless representation of esqueleto
's EDSL.
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
:
- The simple but tedious magic of allowing tuples to be used.
- The more advanced magic of creating
JOIN
s. TheJOIN
is processed from right to left. The rightmost entity of theJOIN
is created withfromStart
. EachJOIN
step is then translated into a call tofromJoin
. In the end,fromFinish
is called to materialize theJOIN
.
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 aSource
(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 JOIN
s without
ON
clauses (either because you didn't do any JOIN
, or
because all JOIN
s already have their own ON
clauses), a
runtime exception OnClauseWithoutMatchingJoinException
is
thrown. ON
clauses are optional when doing JOIN
s.
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 on
s are applied on the reverse
order that the JOIN
s 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
.
orderBy :: [expr OrderBy] -> query ()Source
asc :: PersistField a => expr (Value a) -> expr OrderBySource
Ascending order of this field or expression.
desc :: PersistField a => expr (Value a) -> expr OrderBySource
Descending order of this field or expression.
sub_select :: PersistField a => query (expr (Value a)) -> expr (Value a)Source
Execute a subquery SELECT
in an expression.
sub_selectDistinct :: PersistField a => query (expr (Value a)) -> expr (Value a)Source
Execute a subquery SELECT DISTINCT
in an expression.
(^.) :: (PersistEntity val, PersistField typ) => expr (Entity val) -> EntityField val typ -> expr (Value typ)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.
countRows :: Num a => expr (Value a)Source
COUNT(*)
value.
not_ :: expr (Value Bool) -> expr (Value Bool)Source
(==.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool)Source
(>=.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool)Source
(>.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool)Source
(<=.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool)Source
(<.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool)Source
(!=.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool)Source
(&&.) :: expr (Value Bool) -> expr (Value Bool) -> expr (Value Bool)Source
(||.) :: expr (Value Bool) -> expr (Value Bool) -> expr (Value Bool)Source
(+.) :: PersistField a => expr (Value a) -> expr (Value a) -> expr (Value a)Source
(-.) :: PersistField a => expr (Value a) -> expr (Value a) -> expr (Value a)Source
(/.) :: PersistField a => expr (Value a) -> expr (Value a) -> expr (Value a)Source
(*.) :: PersistField a => expr (Value a) -> expr (Value a) -> expr (Value a)Source
set :: PersistEntity val => expr (Entity val) -> [expr (Update val)] -> query ()Source
SET
clause used on UPDATE
s. Note that while it's not
a type error to use this function on a SELECT
, it will
most certainly result in a runtime error.
(=.) :: (PersistEntity val, PersistField typ) => EntityField val typ -> expr (Value typ) -> expr (Update val)Source
(+=.) :: (PersistEntity val, PersistField a) => EntityField val a -> expr (Value a) -> expr (Update val)Source
(-=.) :: (PersistEntity val, PersistField a) => EntityField val a -> expr (Value a) -> expr (Update val)Source
(*=.) :: (PersistEntity val, PersistField a) => EntityField val a -> expr (Value a) -> expr (Update val)Source
(/=.) :: (PersistEntity val, PersistField a) => EntityField val a -> expr (Value a) -> expr (Update val)Source
from :: From query expr backend a => (a -> query b) -> query bSource
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 beNULL
into scope. Used forOUTER JOIN
s. - A
JOIN
of any other two types allowed by the innermost magic, where aJOIN
may be anInnerJoin
, aCrossJoin
, aLeftOuterJoin
, aRightOuterJoin
, or aFullOuterJoin
. TheJOINs
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 JOIN
s.
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
RightOuterJoin
s or FullOuterJoin
s.
A single value (as opposed to a whole entity). You may use
(
or ^.
)(
to get a ?.
)Value
from an Entity
.
Value a |
Data type that represents an INNER JOIN
(see LeftOuterJoin
for an example).
a InnerJoin b |
IsJoinKind InnerJoin | |
(Esqueleto query expr backend, FromPreprocess query expr backend (InnerJoin a b)) => From query expr backend (InnerJoin a b) |
Data type that represents a CROSS JOIN
(see LeftOuterJoin
for an example).
a CrossJoin b |
IsJoinKind CrossJoin | |
(Esqueleto query expr backend, FromPreprocess query expr backend (CrossJoin a b)) => From query expr backend (CrossJoin a b) |
data LeftOuterJoin a b 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
.
a LeftOuterJoin b |
IsJoinKind LeftOuterJoin | |
(Esqueleto query expr backend, FromPreprocess query expr backend (LeftOuterJoin a b)) => From query expr backend (LeftOuterJoin a b) |
data RightOuterJoin a b Source
Data type that represents a RIGHT OUTER JOIN
(see LeftOuterJoin
for an example).
a RightOuterJoin b |
IsJoinKind RightOuterJoin | |
(Esqueleto query expr backend, FromPreprocess query expr backend (RightOuterJoin a b)) => From query expr backend (RightOuterJoin a b) |
data FullOuterJoin a b Source
Data type that represents a FULL OUTER JOIN
(see LeftOuterJoin
for an example).
a FullOuterJoin b |
IsJoinKind FullOuterJoin | |
(Esqueleto query expr backend, FromPreprocess query expr backend (FullOuterJoin a b)) => From query expr backend (FullOuterJoin a b) |
data OnClauseWithoutMatchingJoinException Source
Exception thrown whenever on
is used to create an ON
clause but no matching JOIN
is found.
Phantom type for a SET
operation on an entity of the given
type (see set
and '(=.)').
The guts
(Internal) A kind of JOIN
.
InnerJoinKind | INNER JOIN |
CrossJoinKind | CROSS JOIN |
LeftOuterJoinKind | LEFT OUTER JOIN |
RightOuterJoinKind | RIGHT OUTER JOIN |
FullOuterJoinKind | FULL OUTER JOIN |
class IsJoinKind join whereSource
(Internal) Functions that operate on types (that should be)
of kind JoinKind
.
smartJoin :: a -> b -> join a bSource
(Internal) smartJoin a b
is a JOIN
of the correct kind.
reifyJoinKind :: join a b -> JoinKindSource
(Internal) Reify a JoinKind
from a JOIN
. This
function is non-strict.
data PreprocessedFrom a Source
class Esqueleto query expr backend => From query expr backend a Source
(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
(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) |