| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
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.
- class (Functor query, Applicative query, Monad query) => Esqueleto query expr backend | query -> expr backend, expr -> query backend where
- from :: From query expr backend a => (a -> query b) -> query b
- data Value a = Value a
- unValue :: Value a -> a
- data ValueList a = ValueList a
- data SomeValue expr where
- class ToSomeValues expr a where
- 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 DistinctOn
- data Update typ
- data Insertion a
- data LockingKind
- class PersistField a => SqlString a
- class ToBaseId ent where
- data JoinKind
- class IsJoinKind join where
- data PreprocessedFrom a
- class Esqueleto query expr backend => From query expr backend a
- class Esqueleto query expr backend => FromPreprocess query expr backend a
- when_ :: expr (Value Bool) -> () -> expr a -> (expr (Value Bool), expr a)
- then_ :: ()
- else_ :: expr a -> expr a
The pretty face
class (Functor query, Applicative query, Monad query) => Esqueleto query expr backend | query -> expr backend, expr -> query backend where #
Finally tagless representation of esqueleto's EDSL.
Minimal complete definition
fromStart, fromStartMaybe, fromJoin, fromFinish, where_, on, groupBy, orderBy, asc, desc, limit, offset, distinct, distinctOn, don, distinctOnOrderBy, rand, having, locking, sub_select, sub_selectDistinct, (^.), (?.), val, isNothing, just, nothing, joinV, countRows, count, countDistinct, not_, (==.), (>=.), (>.), (<=.), (<.), (!=.), (&&.), (||.), (+.), (-.), (/.), (*.), random_, round_, ceiling_, floor_, sum_, min_, max_, avg_, castNum, castNumM, coalesce, coalesceDefault, lower_, like, ilike, (%), concat_, (++.), castString, subList_select, subList_selectDistinct, valList, justList, in_, notIn, exists, notExists, set, (=.), (+=.), (-=.), (*=.), (/=.), (<#), (<&>), case_, toBaseId
Methods
fromStart :: (PersistEntity a, PersistEntityBackend a ~ backend) => query (expr (PreprocessedFrom (expr (Entity a)))) #
(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
JOINs. TheJOINis processed from right to left. The rightmost entity of theJOINis created withfromStart. EachJOINstep is then translated into a call tofromJoin. In the end,fromFinishis called to materialize theJOIN.
fromStartMaybe :: (PersistEntity a, PersistEntityBackend a ~ backend) => query (expr (PreprocessedFrom (expr (Maybe (Entity a))))) #
(Internal) Same as fromStart, but entity may be missing.
fromJoin :: IsJoinKind join => expr (PreprocessedFrom a) -> expr (PreprocessedFrom b) -> query (expr (PreprocessedFrom (join a b))) #
(Internal) Do a JOIN.
fromFinish :: expr (PreprocessedFrom a) -> query a #
(Internal) Finish a JOIN.
where_ :: expr (Value Bool) -> query () #
WHERE clause: restrict the query's result.
on :: expr (Value Bool) -> query () #
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) -> doon(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) -> doon(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 () #
GROUP BY clause. You can enclose multiple columns
in a tuple.
select $from\(foo `InnerJoin` bar) -> doon(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---the second use of
countRows has its type restricted by the :: Int below):
r <- select $from\(foo `InnerJoin` bar) -> doon(foo^.FooBarId==.bar^.BarId)groupBy$ bar^.BarName let countRows' =countRowsorderBy[asccountRows'] return (bar^.BarName, countRows') forM_ r $ \(Valuename,Valuecount) -> do print name print (count :: Int)
orderBy :: [expr OrderBy] -> query () #
ORDER BY clause. See also asc and desc.
Multiple calls to orderBy get concatenated on the final
query, including distinctOnOrderBy.
asc :: PersistField a => expr (Value a) -> expr OrderBy #
Ascending order of this field or expression.
desc :: PersistField a => expr (Value a) -> expr OrderBy #
Descending order of this field or expression.
LIMIT. Limit the number of returned rows.
OFFSET. Usually used with limit.
distinct :: query a -> query a #
DISTINCT. Change the current SELECT into SELECT
DISTINCT. For example:
select $ distinct $
from \foo -> do
...
Note that this also has the same effect:
select $
from \foo -> do
distinct (return ())
...
Since: 2.2.4
distinctOn :: [expr DistinctOn] -> query a -> query a #
DISTINCT ON. Change the current SELECT into
SELECT DISTINCT ON (expressions). 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 expressions. Calls to
distinctOn override any calls to distinct.
Note that PostgreSQL requires the expressions 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 :: expr (Value a) -> expr DistinctOn #
Erase an expression's type so that it's suitable to
be used by distinctOn.
Since: 2.2.4
distinctOnOrderBy :: [expr OrderBy] -> query a -> query a #
A convenience function that calls both distinctOn and
orderBy. In other words,
distinctOnOrderBy [asc foo, desc bar, desc quux] $ do
...
is the same as:
distinctOn[don foo, don bar, don quux] $ doorderBy[asc foo, desc bar, desc quux] ...
Since: 2.2.4
ORDER BY random() clause.
Since: 1.3.10
having :: expr (Value Bool) -> query () #
HAVING.
Since: 1.2.2
locking :: LockingKind -> query () #
Add a locking clause to the query. Please read
LockingKind documentation and your RDBMS manual.
If multiple calls to locking are made on the same query,
the last one is used.
Since: 2.2.7
sub_select :: PersistField a => query (expr (Value a)) -> expr (Value a) #
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) #
Deprecated: Since 2.2.4: use sub_select and distinct.
Same as sub_select but using SELECT DISTINCT.
(^.) :: (PersistEntity val, PersistField typ) => expr (Entity val) -> EntityField val typ -> expr (Value typ) infixl 9 #
Project a field of an entity.
(?.) :: (PersistEntity val, PersistField typ) => expr (Maybe (Entity val)) -> EntityField val typ -> expr (Value (Maybe typ)) #
Project a field of an entity that may be null.
val :: PersistField typ => typ -> expr (Value typ) #
Lift a constant value from Haskell-land to the query.
isNothing :: PersistField typ => expr (Value (Maybe typ)) -> expr (Value Bool) #
IS NULL comparison.
just :: expr (Value typ) -> expr (Value (Maybe typ)) #
Analogous to Just, promotes a value of type typ into
one of type Maybe typ. It should hold that .val . Just
=== just . val
nothing :: expr (Value (Maybe typ)) #
NULL value.
joinV :: expr (Value (Maybe (Maybe typ))) -> expr (Value (Maybe typ)) #
Join nested Maybes in a Value into one. This is useful when
calling aggregate functions on nullable fields.
countRows :: Num a => expr (Value a) #
COUNT(*) value.
count :: Num a => expr (Value typ) -> expr (Value a) #
COUNT.
countDistinct :: Num a => expr (Value typ) -> expr (Value a) #
COUNT(DISTINCT x).
Since: 2.4.1
not_ :: expr (Value Bool) -> expr (Value Bool) #
(==.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool) infix 4 #
(>=.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool) infix 4 #
(>.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool) infix 4 #
(<=.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool) infix 4 #
(<.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool) infix 4 #
(!=.) :: PersistField typ => expr (Value typ) -> expr (Value typ) -> expr (Value Bool) infix 4 #
(&&.) :: expr (Value Bool) -> expr (Value Bool) -> expr (Value Bool) infixr 3 #
(||.) :: expr (Value Bool) -> expr (Value Bool) -> expr (Value Bool) infixr 2 #
(+.) :: PersistField a => expr (Value a) -> expr (Value a) -> expr (Value a) infixl 6 #
(-.) :: PersistField a => expr (Value a) -> expr (Value a) -> expr (Value a) infixl 6 #
(/.) :: PersistField a => expr (Value a) -> expr (Value a) -> expr (Value a) infixl 7 #
(*.) :: PersistField a => expr (Value a) -> expr (Value a) -> expr (Value a) infixl 7 #
random_ :: (PersistField a, Num a) => expr (Value a) #
round_ :: (PersistField a, Num a, PersistField b, Num b) => expr (Value a) -> expr (Value b) #
ceiling_ :: (PersistField a, Num a, PersistField b, Num b) => expr (Value a) -> expr (Value b) #
floor_ :: (PersistField a, Num a, PersistField b, Num b) => expr (Value a) -> expr (Value b) #
sum_ :: (PersistField a, PersistField b) => expr (Value a) -> expr (Value (Maybe b)) #
min_ :: PersistField a => expr (Value a) -> expr (Value (Maybe a)) #
max_ :: PersistField a => expr (Value a) -> expr (Value (Maybe a)) #
avg_ :: (PersistField a, PersistField b) => expr (Value a) -> expr (Value (Maybe b)) #
castNum :: (Num a, Num b) => expr (Value a) -> expr (Value b) #
Allow a number of one type to be used as one of another type via an implicit cast. An explicit cast is not made, this function changes only the types on the Haskell side.
Caveat: Trying to use castNum from Double to Int
will not result in an integer, the original fractional
number will still be used! Use round_, ceiling_ or
floor_ instead.
Safety: This operation is mostly safe due to the Num
constraint between the types and the fact that RDBMSs
usually allow numbers of different types to be used
interchangeably. However, there may still be issues with
the query not being accepted by the RDBMS or persistent
not being able to parse it.
Since: 2.2.9
castNumM :: (Num a, Num b) => expr (Value (Maybe a)) -> expr (Value (Maybe b)) #
Same as castNum, but for nullable values.
Since: 2.2.9
coalesce :: PersistField a => [expr (Value (Maybe a))] -> expr (Value (Maybe a)) #
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) #
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
lower_ :: SqlString s => expr (Value s) -> expr (Value s) #
LOWER function.
like :: SqlString s => expr (Value s) -> expr (Value s) -> expr (Value Bool) infixr 2 #
LIKE operator.
ilike :: SqlString s => expr (Value s) -> expr (Value s) -> expr (Value Bool) infixr 2 #
ILIKE operator (case-insensitive LIKE).
Supported by PostgreSQL only.
Since: 2.2.3
(%) :: SqlString s => expr (Value s) #
The string . May be useful while using %like and
concatenation (concat_ or ++., depending on your
database). Note that you always have to type the parenthesis,
for example:
name `like` (%) ++.val"John" ++. (%)
concat_ :: SqlString s => [expr (Value s)] -> expr (Value s) #
The CONCAT function with a variable number of
parameters. Supported by MySQL and PostgreSQL.
(++.) :: SqlString s => expr (Value s) -> expr (Value s) -> expr (Value s) infixr 5 #
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) => expr (Value s) -> expr (Value r) #
Cast a string type into Text. This function
is very useful if you want to use newtypes, or if you want
to apply functions such as like to strings of different
types.
Safety: This is a slightly unsafe function, especially if
you have defined your own instances of SqlString. Also,
since Maybe is an instance of SqlString, it's possible
to turn a nullable value into a non-nullable one. Avoid
using this function if possible.
subList_select :: PersistField a => query (expr (Value a)) -> expr (ValueList a) #
Execute a subquery SELECT in an expression. Returns a
list of values.
subList_selectDistinct :: PersistField a => query (expr (Value a)) -> expr (ValueList a) #
Deprecated: Since 2.2.4: use subList_select and distinct.
Same as sublist_select but using SELECT DISTINCT.
valList :: PersistField typ => [typ] -> expr (ValueList typ) #
Lift a list of constant value from Haskell-land to the query.
justList :: expr (ValueList typ) -> expr (ValueList (Maybe typ)) #
Same as just but for ValueList. Most of the time you
won't need it, though, because you can use just from
inside subList_select or Just from inside valList.
Since: 2.2.12
in_ :: PersistField typ => expr (Value typ) -> expr (ValueList typ) -> expr (Value Bool) #
IN operator. For example if you want to select all Persons by a list
of IDs:
SELECT * FROM Person WHERE Person.id IN (?)
In esqueleto, we may write the same query above as:
select $from$ \person -> dowhere_$ person^.PersonIdin_valListpersonIds return person
Where personIds is of type [Key Person].
notIn :: PersistField typ => expr (Value typ) -> expr (ValueList typ) -> expr (Value Bool) #
NOT IN operator.
exists :: query () -> expr (Value Bool) #
EXISTS operator. For example:
select $from$ \person -> dowhere_$exists$from$ \post -> dowhere_(post^.BlogPostAuthorId==.person^.PersonId) return person
notExists :: query () -> expr (Value Bool) #
NOT EXISTS operator.
set :: PersistEntity val => expr (Entity val) -> [expr (Update val)] -> query () #
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 #
(+=.) :: (PersistEntity val, PersistField a) => EntityField val a -> expr (Value a) -> expr (Update val) infixr 3 #
(-=.) :: (PersistEntity val, PersistField a) => EntityField val a -> expr (Value a) -> expr (Update val) infixr 3 #
(*=.) :: (PersistEntity val, PersistField a) => EntityField val a -> expr (Value a) -> expr (Update val) infixr 3 #
(/=.) :: (PersistEntity val, PersistField a) => EntityField val a -> expr (Value a) -> expr (Update val) infixr 3 #
(<#) :: (a -> b) -> expr (Value a) -> expr (Insertion b) #
Apply a PersistField constructor to expr Value arguments.
(<&>) :: expr (Insertion (a -> b)) -> expr (Value a) -> expr (Insertion b) #
Apply extra expr Value arguments to a PersistField constructor
case_ :: PersistField a => [(expr (Value Bool), expr (Value a))] -> expr (Value a) -> expr (Value a) #
CASE statement. For example:
select $ return $case_[when_(exists$from$ \p -> dowhere_(p^.PersonName==.val"Mike"))then_(sub_select$from$ \v -> do let sub =from$ \c -> dowhere_(c^.PersonName==.val"Mike") return (c^.PersonFavNum)where_(v^.PersonFavNum >.sub_selectsub) 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_andthen_is mandatory otherwise it will emit an error. - The
else_is also mandatory, unlike the SQL statement in which if theELSEis omitted it will return aNULL. You can reproduce this vianothing.
Since: 2.1.2
toBaseId :: ToBaseId ent => expr (Value (Key ent)) -> expr (Value (Key (BaseEnt ent))) #
Convert an entity's key into another entity's.
This function is to be used when you change an entity's Id to be
that of another entity. For example:
Bar barNum Int Foo Id BarId fooNum Int
For this example, declare:
instance ToBaseId Foo where type BaseEnt Foo = Bar toBaseIdWitness = FooKey
Now you're able to write queries such as:
select$from$ (bar `InnerJoin` foo) -> doon(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
Instances
from :: From query expr backend a => (a -> query b) -> query b #
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 beNULLinto scope. Used forOUTER JOINs.- A
JOINof any other two types allowed by the innermost magic, where aJOINmay be anInnerJoin, aCrossJoin, aLeftOuterJoin, aRightOuterJoin, or aFullOuterJoin. TheJOINshave left fixity.
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
(InnerJoin (expr (Entity Person))
(expr (Entity Follow)))
(expr (Entity Person))
(p1 `InnerJoin` (f `InnerJoin` p2)) ::
:: (...) => InnerJoin
(expr (Entity Person))
(InnerJoin (expr (Entity Follow))
(expr (Entity Person)))
Note that some backends may not support all kinds of JOINs.
A single value (as opposed to a whole entity). You may use
( or ^.)( to get a ?.)Value from an Entity.
Constructors
| Value a |
A list of single values. There's a limited set of functions
able to work with this data type (such as subList_select,
valList, in_ and exists).
Constructors
| ValueList a |
A wrapper type for for any expr (Value a) for all a.
class ToSomeValues expr a where #
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)
Minimal complete definition
Methods
toSomeValues :: a -> [SomeValue expr] #
Instances
Data type that represents an INNER JOIN (see LeftOuterJoin for an example).
Constructors
| a `InnerJoin` b infixl 2 |
Instances
| 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).
Constructors
| a `CrossJoin` b infixl 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 infixl 2 #
Data type that represents a LEFT OUTER JOIN. For example,
select $from$ \(person `LeftOuterJoin` pet) -> ...
is translated into
SELECT ... FROM Person LEFT OUTER JOIN Pet ...
See also: from.
Constructors
| a `LeftOuterJoin` b infixl 2 |
Instances
| IsJoinKind LeftOuterJoin # | |
| (Esqueleto query expr backend, FromPreprocess query expr backend (LeftOuterJoin a b)) => From query expr backend (LeftOuterJoin a b) # | |
data RightOuterJoin a b infixl 2 #
Data type that represents a RIGHT OUTER JOIN (see LeftOuterJoin for an example).
Constructors
| a `RightOuterJoin` b infixl 2 |
Instances
| IsJoinKind RightOuterJoin # | |
| (Esqueleto query expr backend, FromPreprocess query expr backend (RightOuterJoin a b)) => From query expr backend (RightOuterJoin a b) # | |
data FullOuterJoin a b infixl 2 #
Data type that represents a FULL OUTER JOIN (see LeftOuterJoin for an example).
Constructors
| a `FullOuterJoin` b infixl 2 |
Instances
| IsJoinKind FullOuterJoin # | |
| (Esqueleto query expr backend, FromPreprocess query expr backend (FullOuterJoin a b)) => From query expr backend (FullOuterJoin a b) # | |
data OnClauseWithoutMatchingJoinException #
Exception thrown whenever on is used to create an ON
clause but no matching JOIN is found.
Constructors
| OnClauseWithoutMatchingJoinException String |
data DistinctOn #
Phantom type used by distinctOn and don.
Phantom type for a SET operation on an entity of the given
type (see set and '(=.)').
data LockingKind #
Different kinds of locking clauses supported by locking.
Note that each RDBMS has different locking support. The
constructors of this datatype specify only the syntax of the
locking mechanism, not its semantics. For example, even
though both MySQL and PostgreSQL support ForUpdate, there
are no guarantees that they will behave the same.
Since: 2.2.7
Constructors
| ForUpdate |
Since: 2.2.7 |
| ForShare |
Since: 2.2.7 |
| LockInShareMode |
Since: 2.2.7 |
class PersistField a => SqlString a #
Phantom class of data types that are treated as strings by the RDBMS. It has no methods because it's only used to avoid type errors such as trying to concatenate integers.
If you have a custom data type or newtype, feel free to make
it an instance of this class.
Since: 2.4.0
Class that enables one to use toBaseId to convert an entity's
key on a query into another (cf. toBaseId).
Minimal complete definition
Methods
toBaseIdWitness :: Key (BaseEnt ent) -> Key ent #
The guts
(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 #
(Internal) Functions that operate on types (that should be)
of kind JoinKind.
Minimal complete definition
Methods
smartJoin :: a -> b -> join a b #
(Internal) smartJoin a b is a JOIN of the correct kind.
reifyJoinKind :: join a b -> JoinKind #
(Internal) Reify a JoinKind from a JOIN. This
function is non-strict.
data PreprocessedFrom a #
class Esqueleto query expr backend => From query expr backend a #
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 #
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) # | |