Safe Haskell | None |
---|---|
Language | Haskell98 |
Database.Esqueleto
Contents
Description
The esqueleto
EDSL (embedded domain specific language).
This module replaces Database.Persist
, so instead of
importing that module you should just import this one:
-- For a module using just esqueleto. import Database.Esqueleto
If you need to use persistent
's default support for queries
as well, either import it qualified:
-- For a module that mostly uses esqueleto. import Database.Esqueleto import qualified Database.Persist as P
or import esqueleto
itself qualified:
-- For a module that uses esqueleto just on some queries. import Database.Persist import qualified Database.Esqueleto as E
Other than identifier name clashes, esqueleto
does not
conflict with persistent
in any way.
- class (Functor query, Applicative query, Monad query) => Esqueleto query expr backend | query -> expr backend, expr -> query backend where
- class ToBaseId ent where
- when_ :: expr (Value Bool) -> () -> expr a -> (expr (Value Bool), expr a)
- then_ :: ()
- else_ :: expr a -> expr a
- 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 OrderBy
- data DistinctOn
- data LockingKind
- class PersistField a => SqlString 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 SqlQuery a
- data SqlExpr a
- type SqlEntity ent = (PersistEntity ent, PersistEntityBackend ent ~ SqlBackend)
- select :: (SqlSelect a r, MonadIO m) => SqlQuery a -> SqlReadT m [r]
- selectDistinct :: (SqlSelect a r, MonadIO m) => SqlQuery a -> SqlPersistT m [r]
- selectSource :: (SqlSelect a r, MonadResource m) => SqlQuery a -> Source (SqlPersistT m) r
- selectDistinctSource :: (SqlSelect a r, MonadResource m) => SqlQuery a -> Source (SqlPersistT m) r
- delete :: MonadIO m => SqlQuery () -> SqlWriteT m ()
- deleteCount :: MonadIO m => SqlQuery () -> SqlWriteT m Int64
- update :: (MonadIO m, SqlEntity val) => (SqlExpr (Entity val) -> SqlQuery ()) -> SqlWriteT m ()
- updateCount :: (MonadIO m, SqlEntity val) => (SqlExpr (Entity val) -> SqlQuery ()) -> SqlWriteT m Int64
- insertSelect :: (MonadIO m, PersistEntity a) => SqlQuery (SqlExpr (Insertion a)) -> SqlWriteT m ()
- insertSelectCount :: (MonadIO m, PersistEntity a) => SqlQuery (SqlExpr (Insertion a)) -> SqlWriteT m Int64
- insertSelectDistinct :: (MonadIO m, PersistEntity a) => SqlQuery (SqlExpr (Insertion a)) -> SqlWriteT m ()
- (<#) :: Esqueleto query expr backend => (a -> b) -> expr (Value a) -> expr (Insertion b)
- (<&>) :: Esqueleto query expr backend => expr (Insertion (a -> b)) -> expr (Value a) -> expr (Insertion b)
- valkey :: (Esqueleto query expr backend, ToBackendKey SqlBackend entity, PersistField (Key entity)) => Int64 -> expr (Value (Key entity))
- valJ :: (Esqueleto query expr backend, PersistField (Key entity)) => Value (Key entity) -> expr (Value (Key entity))
- deleteKey :: (PersistStore backend, BaseBackend backend ~ PersistEntityBackend val, MonadIO m, PersistEntity val) => Key val -> ReaderT backend m ()
- module Database.Persist.Sql
Setup
If you're already using persistent
, then you're ready to use
esqueleto
, no further setup is needed. If you're just
starting a new project and would like to use esqueleto
, take
a look at persistent
's book first
(http://www.yesodweb.com/book/persistent) to learn how to
define your schema.
Introduction
The main goals of esqueleto
are to:
- Be easily translatable to SQL. When you take a look at a
esqueleto
query, you should be able to know exactly how the SQL query will end up. (As opposed to being a relational algebra EDSL such as HaskellDB, which is non-trivial to translate into SQL.) - Support the most widely used SQL features. We'd like you to be
able to use
esqueleto
for all of your queries, no exceptions. Send a pull request or open an issue on our project page (https://github.com/prowdsponsor/esqueleto) if there's anything missing that you'd like to see. - Be as type-safe as possible. We strive to provide as many type checks as possible. If you get bitten by some invalid code that type-checks, please open an issue on our project page so we can take a look.
However, it is not a goal to be able to write portable SQL.
We do not try to hide the differences between DBMSs from you,
and esqueleto
code that works for one database may not work
on another. This is a compromise we have to make in order to
give you as much control over the raw SQL as possible without
losing too much convenience. This also means that you may
type-check a query that doesn't work on your DBMS.
Getting started
We like clean, easy-to-read EDSLs. However, in order to achieve this goal we've used a lot of type hackery, leading to some hard-to-read type signatures. On this section, we'll try to build some intuition about the syntax.
For the following examples, we'll use this example schema:
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 |]
Most of esqueleto
was created with SELECT
statements in
mind, not only because they're the most common but also
because they're the most complex kind of statement. The most
simple kind of SELECT
would be:
SELECT * FROM Person
In esqueleto
, we may write the same query above as:
do people <-select
$from
$ \person -> do return person liftIO $ mapM_ (putStrLn . personName . entityVal) people
The expression above has type SqlPersist m ()
, while
people
has type [Entity Person]
. The query above will be
translated into exactly the same query we wrote manually, but
instead of SELECT *
it will list all entity fields (using
*
is not robust). Note that esqueleto
knows that we want
an Entity Person
just because of the personName
that we're
printing later.
However, most of the time we need to filter our queries using
WHERE
. For example:
SELECT * FROM Person WHERE Person.name = "John"
In esqueleto
, we may write the same query above as:
select
$from
$ \p -> dowhere_
(p^.
PersonName==.
val
"John") return p
Although esqueleto
's code is a bit more noisy, it's has
almost the same structure (save from the return
). The
(
operator is used to project a field from an entity.
The field name is the same one generated by ^.
)persistent
's
Template Haskell functions. We use val
to lift a constant
Haskell value into the SQL query.
Another example would be:
SELECT * FROM Person WHERE Person.age >= 18
In esqueleto
, we may write the same query above as:
select
$from
$ \p -> dowhere_
(p^.
PersonAge>=.
just
(val
18)) return p
Since age
is an optional Person
field, we use just
to lift
into val
18 :: SqlExpr (Value Int)just (
.val
18) ::
SqlExpr (Value (Maybe Int))
Implicit joins are represented by tuples. For example, to get the list of all blog posts and their authors, we could write:
SELECT BlogPost.*, Person.* FROM BlogPost, Person WHERE BlogPost.authorId = Person.id ORDER BY BlogPost.title ASC
In esqueleto
, we may write the same query above as:
select
$from
$ \(b, p) -> dowhere_
(b^.
BlogPostAuthorId==.
p^.
PersonId)orderBy
[asc
(b^.
BlogPostTitle)] return (b, p)
However, you may want your results to include people who don't
have any blog posts as well using a LEFT OUTER JOIN
:
SELECT Person.*, BlogPost.* FROM Person LEFT OUTER JOIN BlogPost ON Person.id = BlogPost.authorId ORDER BY Person.name ASC, BlogPost.title ASC
In esqueleto
, we may write the same query above as:
select
$from
$ \(p `LeftOuterJoin
` mb) -> doon
(just
(p^.
PersonId)==.
mb?.
BlogPostAuthorId)orderBy
[asc
(p^.
PersonName),asc
(mb?.
BlogPostTitle)] return (p, mb)
On a LEFT OUTER JOIN
the entity on the right hand side may
not exist (i.e. there may be a Person
without any
BlogPost
s), so while p :: SqlExpr (Entity Person)
, we have
mb :: SqlExpr (Maybe (Entity BlogPost))
. The whole
expression above has type SqlPersist m [(Entity Person, Maybe
(Entity BlogPost))]
. Instead of using (^.)
, we used
(
to project a field from a ?.
)Maybe (Entity a)
.
We are by no means limited to joins of two tables, nor by
joins of different tables. For example, we may want a list
of the Follow
entity:
SELECT P1.*, Follow.*, P2.* FROM Person AS P1 INNER JOIN Follow ON P1.id = Follow.follower INNER JOIN P2 ON P2.id = Follow.followed
In esqueleto
, we may write the same query above as:
select
$from
$ \(p1 `InnerJoin
` f `InnerJoin
` p2) -> doon
(p2^.
PersonId==.
f^.
FollowFollowed)on
(p1^.
PersonId==.
f^.
FollowFollower) return (p1, f, p2)
Note carefully that the order of the ON clauses is
reversed! You're required to write your on
s in reverse
order because that helps composability (see the documentation
of on
for more details).
We also currently support UPDATE
and DELETE
statements.
For example:
doupdate
$ \p -> doset
p [ PersonName=.
val
"João" ]where_
(p^.
PersonName==.
val
"Joao")delete
$from
$ \p -> dowhere_
(p^.
PersonAge<.
just
(val
14))
The results of queries can also be used for insertions.
In SQL
, we might write the following, inserting a new blog
post for every user:
INSERT INTO BlogPost SELECT ('Group Blog Post', id) FROM Person
In esqueleto
, we may write the same query above as:
insertSelect
$from
$ \p-> return $ BlogPost<#
"Group Blog Post"<&>
(p^.
PersonId)
Individual insertions can be performed through Persistent's
insert
function, reexported for convenience.
esqueleto
's Language
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.
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
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) -> 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 on
s are applied on the reverse
order that the JOIN
s 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) -> doon
(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) -> 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' =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
.
Multiple calls to orderBy
get concatenated on the final
query, including distinctOnOrderBy
.
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
.
distinct :: query a -> query 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 :: [expr DistinctOn] -> query a -> query a Source #
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 Source #
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 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] $ doorderBy
[asc foo, desc bar, desc quux] ...
Since: 2.2.4
ORDER BY random()
clause.
Since: 1.3.10
having :: expr (Value Bool) -> query () Source #
HAVING
.
Since: 1.2.2
locking :: LockingKind -> query () Source #
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) 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 #
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 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 Maybe
s 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
.
countDistinct :: Num a => expr (Value typ) -> expr (Value a) Source #
COUNT(DISTINCT x)
.
Since: 2.4.1
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 #
castNum :: (Num a, Num b) => expr (Value a) -> expr (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) => expr (Value (Maybe a)) -> expr (Value (Maybe b)) Source #
Same as castNum
, but for nullable values.
Since: 2.2.9
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
lower_ :: SqlString s => expr (Value s) -> expr (Value s) Source #
LOWER
function.
like :: SqlString s => expr (Value s) -> expr (Value s) -> expr (Value Bool) infixr 2 Source #
LIKE
operator.
ilike :: SqlString s => expr (Value s) -> expr (Value s) -> expr (Value Bool) infixr 2 Source #
ILIKE
operator (case-insensitive LIKE
).
Supported by PostgreSQL only.
Since: 2.2.3
(%) :: SqlString 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 have to type the parenthesis,
for example:
name `like
` (%) ++.val
"John" ++. (%)
concat_ :: SqlString s => [expr (Value s)] -> expr (Value s) Source #
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 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) => expr (Value s) -> expr (Value r) Source #
Cast a string type into Text
. This function
is very useful if you want to use newtype
s, 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) 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 #
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) Source #
Lift a list of constant value from Haskell-land to the query.
justList :: expr (ValueList typ) -> expr (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 => expr (Value typ) -> expr (ValueList typ) -> expr (Value Bool) Source #
IN
operator. For example if you want to select all Person
s 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^.
PersonId `in_
`valList
personIds return person
Where personIds
is of type [Key Person]
.
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 -> dowhere_
$exists
$from
$ \post -> dowhere_
(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 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) 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 -> 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_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_
andthen_
is mandatory otherwise it will emit an error. - The
else_
is also mandatory, unlike the SQL statement in which if theELSE
is 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))) 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 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
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
).
Minimal complete definition
when_ :: expr (Value Bool) -> () -> expr a -> (expr (Value Bool), expr a) Source #
Syntax sugar for case_
.
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 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 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 JOIN
s.
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 Source # | Since: 1.4.4 |
ToSomeValues SqlExpr (SqlExpr (Value a)) Source # | |
Eq a => Eq (Value a) Source # | |
Ord a => Ord (Value a) Source # | |
Show a => Show (Value a) Source # | |
PersistField a => SqlSelect (SqlExpr (Value a)) (Value a) Source # | You may return any single value (i.e. a single column) from
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 |
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 |
Since: 2.2.7 |
ForShare |
Since: 2.2.7 |
LockInShareMode |
Since: 2.2.7 |
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
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 |
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 |
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
IsJoinKind LeftOuterJoin Source # | |
(Esqueleto query expr backend, FromPreprocess query expr backend (LeftOuterJoin a b)) => From query expr backend (LeftOuterJoin a b) 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
IsJoinKind RightOuterJoin Source # | |
(Esqueleto query expr backend, FromPreprocess query expr backend (RightOuterJoin a b)) => From query expr backend (RightOuterJoin a 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
IsJoinKind FullOuterJoin Source # | |
(Esqueleto query expr backend, FromPreprocess query expr backend (FullOuterJoin a b)) => From query expr backend (FullOuterJoin a b) Source # | |
data OnClauseWithoutMatchingJoinException Source #
Exception thrown whenever on
is used to create an ON
clause but no matching JOIN
is found.
Constructors
OnClauseWithoutMatchingJoinException String |
SQL backend
SQL backend for esqueleto
using SqlPersistT
.
An expression on the SQL backend.
There are many comments describing the constructors of this data type. However, Haddock doesn't like GADTs, so you'll have to read them by hitting "Source".
Instances
Esqueleto SqlQuery SqlExpr SqlBackend Source # | |
ToSomeValues SqlExpr (SqlExpr (Value a)) Source # | |
(~) * a (Value b) => UnsafeSqlFunctionArgument (SqlExpr a) Source # | |
PersistEntity a => SqlSelect (SqlExpr (Maybe (Entity a))) (Maybe (Entity a)) Source # | |
PersistEntity a => SqlSelect (SqlExpr (Entity a)) (Entity a) Source # | |
PersistField a => SqlSelect (SqlExpr (Value a)) (Value a) Source # | You may return any single value (i.e. a single column) from
a |
type SqlEntity ent = (PersistEntity ent, PersistEntityBackend ent ~ SqlBackend) Source #
Constraint synonym for persistent
entities whose backend
is SqlPersistT
.
select :: (SqlSelect a r, MonadIO m) => SqlQuery a -> SqlReadT 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 (
for an entityEntity
v)v
(i.e., like the*
in SQL), which is then returned to Haskell-land as justEntity v
. - You may return a
SqlExpr (Maybe (Entity v))
for an entityv
that may beNULL
, which is then returned to Haskell-land asMaybe (Entity v)
. Used forOUTER JOIN
s. - You may return a
SqlExpr (
for a valueValue
t)t
(i.e., a single column), wheret
is any instance ofPersistField
, which is then returned to Haskell-land asValue t
. You may useValue
to return projections of anEntity
(see(
and^.
)(
) or to return any other value calculated on the query (e.g.,?.
)countRows
orsub_select
).
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
alone is ambiguous, but
in the context ofselect
$ from $ \p -> return p
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)
.
selectDistinct :: (SqlSelect a r, MonadIO m) => SqlQuery a -> SqlPersistT m [r] Source #
Execute an esqueleto
SELECT DISTINCT
query inside
persistent
's SqlPersistT
monad and return a list of rows.
selectSource :: (SqlSelect a r, MonadResource m) => SqlQuery a -> Source (SqlPersistT m) r Source #
Execute an esqueleto
SELECT
query inside persistent
's
SqlPersistT
monad and return a Source
of rows.
selectDistinctSource :: (SqlSelect a r, MonadResource m) => SqlQuery a -> Source (SqlPersistT m) r Source #
Deprecated: Since 2.2.4: use selectSource
and distinct
.
Execute an esqueleto
SELECT DISTINCT
query inside
persistent
's SqlPersistT
monad and return a Source
of
rows.
delete :: MonadIO m => SqlQuery () -> SqlWriteT 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 ()
deleteCount :: MonadIO m => SqlQuery () -> SqlWriteT m Int64 Source #
Same as delete
, but returns the number of rows affected.
update :: (MonadIO m, SqlEntity val) => (SqlExpr (Entity val) -> SqlQuery ()) -> SqlWriteT 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 -> doset
p [ PersonAge=.
just
(val
thisYear) -. p^.
PersonBorn ]where_
$ isNothing (p^.
PersonAge)
updateCount :: (MonadIO m, SqlEntity val) => (SqlExpr (Entity val) -> SqlQuery ()) -> SqlWriteT m Int64 Source #
Same as update
, but returns the number of rows affected.
insertSelect :: (MonadIO m, PersistEntity a) => SqlQuery (SqlExpr (Insertion a)) -> SqlWriteT m () Source #
Insert a PersistField
for every selected value.
Since: 2.4.2
insertSelectCount :: (MonadIO m, PersistEntity a) => SqlQuery (SqlExpr (Insertion a)) -> SqlWriteT m Int64 Source #
Insert a PersistField
for every selected value, return the count afterward
insertSelectDistinct :: (MonadIO m, PersistEntity a) => SqlQuery (SqlExpr (Insertion a)) -> SqlWriteT m () Source #
Deprecated: Since 2.2.4: use insertSelect
and distinct
.
Insert a PersistField
for every unique selected value.
(<#) :: Esqueleto query expr backend => (a -> b) -> expr (Value a) -> expr (Insertion b) Source #
Apply a PersistField
constructor to expr Value
arguments.
(<&>) :: Esqueleto query expr backend => expr (Insertion (a -> b)) -> expr (Value a) -> expr (Insertion b) Source #
Apply extra expr Value
arguments to a PersistField
constructor
RDBMS-specific modules
There are many differences between SQL syntax and functions
supported by different RDBMSs. Since version 2.2.8,
esqueleto
includes modules containing functions that are
specific to a given RDBMS.
- PostgreSQL: Database.Esqueleto.PostgreSQL.
In order to use these functions, you need to explicitly import their corresponding modules, they're not re-exported here.
Helpers
valkey :: (Esqueleto query expr backend, ToBackendKey SqlBackend entity, PersistField (Key entity)) => Int64 -> expr (Value (Key entity)) Source #
valkey i =
(https://github.com/prowdsponsor/esqueleto/issues/9).val
. toSqlKey
valJ :: (Esqueleto query expr backend, PersistField (Key entity)) => Value (Key entity) -> expr (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
Re-exports
We re-export many symbols from persistent
for convenince:
- "Store functions" from Database.Persist.
- Everything from Database.Persist.Class except for
PersistQuery
anddelete
(usedeleteKey
instead). - Everything from Database.Persist.Types except for
Update
,SelectOpt
,BackendSpecificFilter
andFilter
. - Everything from Database.Persist.Sql except for
deleteWhereCount
andupdateWhereCount
.
deleteKey :: (PersistStore backend, BaseBackend backend ~ PersistEntityBackend val, MonadIO m, PersistEntity val) => Key val -> ReaderT backend m () Source #
module Database.Persist.Sql