esqueleto-0.2: Bare bones, type-safe EDSL for SQL queries on persistent backends.

Safe HaskellSafe-Infered

Database.Esqueleto.Internal.Language

Synopsis

Documentation

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.

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

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

ORDER BY clause. See also asc and desc.

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

Analog 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 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)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 an entity into scope.

The following types implement from:

  • Expr (Entity val), which brings a single entity into scope.
  • Tuples of any other types supported by from. Calling from multiple times is the same as calling from a single time and using a tuple.

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

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

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

data InnerJoin a b Source

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

Constructors

a InnerJoin b 

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 Source

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

Constructors

a CrossJoin b 

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

Constructors

a LeftOuterJoin b 

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 Source

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

Constructors

a RightOuterJoin b 

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 Source

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

Constructors

a FullOuterJoin b 

Instances

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

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 whereSource

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

Methods

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

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

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 '(=.)').