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

Safe HaskellNone
LanguageHaskell2010

Database.Esqueleto.Internal.Language

Contents

Description

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

Synopsis

The pretty face

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

Finally tagless representation of esqueleto's EDSL.

Methods

fromStart :: (PersistEntity a, BackendCompatible backend (PersistEntityBackend a)) => 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, BackendCompatible backend (PersistEntityBackend a)) => query (expr (PreprocessedFrom (expr (Maybe (Entity a))))) Source #

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

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

(Internal) Do a JOIN.

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

(Internal) Finish a JOIN.

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

WHERE clause: restrict the query's result.

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

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

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

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

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

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

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

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

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

groupBy :: ToSomeValues expr a => a -> query () Source #

GROUP BY clause. You can enclose multiple columns in a tuple.

select $ from \(foo `InnerJoin` bar) -> do
  on (foo ^. FooBarId ==. bar ^. BarId)
  groupBy (bar ^. BarId, bar ^. BarName)
  return (bar ^. BarId, bar ^. BarName, countRows)

With groupBy you can sort by aggregate functions, like so (we used let to restrict the more general countRows to SqlExpr (Value Int) to avoid ambiguity---the second use of countRows has its type restricted by the :: Int below):

r <- select $ from \(foo `InnerJoin` bar) -> do
  on (foo ^. FooBarId ==. bar ^. BarId)
  groupBy $ bar ^. BarName
  let countRows' = countRows
  orderBy [asc countRows']
  return (bar ^. BarName, countRows')
forM_ r $ \(Value name, Value count) -> do
  print name
  print (count :: Int)

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

ORDER BY clause. See also asc and desc.

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] $ do
  orderBy  [asc foo, desc bar, desc quux]
  ...

Since: 2.2.4

rand :: expr OrderBy Source #

Deprecated: Since 2.6.0: rand ordering function is not uniform across all databases! To avoid accidental partiality it will be removed in the next major version.

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.

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

Project a field of an entity.

withNonNull :: PersistField typ => expr (Value (Maybe typ)) -> (expr (Value typ) -> query a) -> query a Source #

Project an expression that may be null, guarding against null cases.

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

Project a field of an entity that may be null.

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

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

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

IS NULL comparison.

just :: expr (Value typ) -> expr (Value (Maybe typ)) Source #

Analogous to Just, promotes a value of type typ into one of type Maybe typ. It should hold that val . Just === just . val.

nothing :: expr (Value (Maybe typ)) Source #

NULL value.

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

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

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

COUNT(*) value.

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

COUNT.

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 #

Deprecated: Since 2.6.0: random_ is not uniform across all databases! Please use a specific one such as random_, random_, or random_

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 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) Source #

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

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 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 -> do
where_ $ 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 -> do
where_ $ exists $
         from $ \post -> do
         where_ (post ^. BlogPostAuthorId ==. person ^. PersonId)
return person

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

NOT EXISTS operator.

set :: PersistEntity val => expr (Entity val) -> [expr (Update val)] -> query () Source #

SET clause used on UPDATEs. Note that while it's not a type error to use this function on a SELECT, it will most certainly result in a runtime error.

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

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

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

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

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

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

Apply a PersistField constructor to expr Value arguments.

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

Apply extra expr Value arguments to a PersistField constructor

case_ :: PersistField a => [(expr (Value Bool), expr (Value a))] -> expr (Value a) -> expr (Value a) Source #

CASE statement. For example:

select $
return $
case_
   [ when_
       (exists $
       from $ \p -> do
       where_ (p ^. PersonName ==. val "Mike"))
     then_
       (sub_select $
       from $ \v -> do
       let sub =
               from $ \c -> do
               where_ (c ^. PersonName ==. val "Mike")
               return (c ^. PersonFavNum)
       where_ (v ^. PersonFavNum >. sub_select sub)
       return $ count (v ^. PersonName) +. val (1 :: Int)) ]
   (else_ $ val (-1))

This query is a bit complicated, but basically it checks if a person named "Mike" exists, and if that person does, run the subquery to find out how many people have a ranking (by Fav Num) higher than "Mike".

NOTE: There are a few things to be aware about this statement.

  • This only implements the full CASE statement, it does not implement the "simple" CASE statement.
  • At least one when_ and then_ is mandatory otherwise it will emit an error.
  • The else_ is also mandatory, unlike the SQL statement in which if the ELSE is omitted it will return a NULL. You can reproduce this via nothing.

Since: 2.1.2

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) -> do
on (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
Esqueleto SqlQuery SqlExpr SqlBackend Source # 
Instance details

Defined in Database.Esqueleto.Internal.Sql

Methods

fromStart :: (PersistEntity a, BackendCompatible SqlBackend (PersistEntityBackend a)) => SqlQuery (SqlExpr (PreprocessedFrom (SqlExpr (Entity a)))) Source #

fromStartMaybe :: (PersistEntity a, BackendCompatible SqlBackend (PersistEntityBackend a)) => SqlQuery (SqlExpr (PreprocessedFrom (SqlExpr (Maybe (Entity a))))) Source #

fromJoin :: IsJoinKind join => SqlExpr (PreprocessedFrom a) -> SqlExpr (PreprocessedFrom b) -> SqlQuery (SqlExpr (PreprocessedFrom (join a b))) Source #

fromFinish :: SqlExpr (PreprocessedFrom a) -> SqlQuery a Source #

where_ :: SqlExpr (Value Bool) -> SqlQuery () Source #

on :: SqlExpr (Value Bool) -> SqlQuery () Source #

groupBy :: ToSomeValues SqlExpr a => a -> SqlQuery () Source #

orderBy :: [SqlExpr OrderBy] -> SqlQuery () Source #

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

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

limit :: Int64 -> SqlQuery () Source #

offset :: Int64 -> SqlQuery () Source #

distinct :: SqlQuery a -> SqlQuery a Source #

distinctOn :: [SqlExpr DistinctOn] -> SqlQuery a -> SqlQuery a Source #

don :: SqlExpr (Value a) -> SqlExpr DistinctOn Source #

distinctOnOrderBy :: [SqlExpr OrderBy] -> SqlQuery a -> SqlQuery a Source #

rand :: SqlExpr OrderBy Source #

having :: SqlExpr (Value Bool) -> SqlQuery () Source #

locking :: LockingKind -> SqlQuery () Source #

sub_select :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (Value a) Source #

(^.) :: (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Source #

withNonNull :: PersistField typ => SqlExpr (Value (Maybe typ)) -> (SqlExpr (Value typ) -> SqlQuery a) -> SqlQuery a Source #

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

val :: PersistField typ => typ -> SqlExpr (Value typ) Source #

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

just :: SqlExpr (Value typ) -> SqlExpr (Value (Maybe typ)) Source #

nothing :: SqlExpr (Value (Maybe typ)) Source #

joinV :: SqlExpr (Value (Maybe (Maybe typ))) -> SqlExpr (Value (Maybe typ)) Source #

countRows :: Num a => SqlExpr (Value a) Source #

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

countDistinct :: Num a => SqlExpr (Value typ) -> SqlExpr (Value a) Source #

not_ :: SqlExpr (Value Bool) -> SqlExpr (Value Bool) Source #

(==.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) Source #

(>=.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) Source #

(>.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) Source #

(<=.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) Source #

(<.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) Source #

(!=.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) Source #

(&&.) :: SqlExpr (Value Bool) -> SqlExpr (Value Bool) -> SqlExpr (Value Bool) Source #

(||.) :: SqlExpr (Value Bool) -> SqlExpr (Value Bool) -> SqlExpr (Value Bool) Source #

(+.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a) Source #

(-.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a) Source #

(/.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a) Source #

(*.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a) Source #

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

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

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

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

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

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

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

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

castNum :: (Num a, Num b) => SqlExpr (Value a) -> SqlExpr (Value b) Source #

castNumM :: (Num a, Num b) => SqlExpr (Value (Maybe a)) -> SqlExpr (Value (Maybe b)) Source #

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

coalesceDefault :: PersistField a => [SqlExpr (Value (Maybe a))] -> SqlExpr (Value a) -> SqlExpr (Value a) Source #

lower_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) Source #

like :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) -> SqlExpr (Value Bool) Source #

ilike :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) -> SqlExpr (Value Bool) Source #

(%) :: SqlString s => SqlExpr (Value s) Source #

concat_ :: SqlString s => [SqlExpr (Value s)] -> SqlExpr (Value s) Source #

(++.) :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) -> SqlExpr (Value s) Source #

castString :: (SqlString s, SqlString r) => SqlExpr (Value s) -> SqlExpr (Value r) Source #

subList_select :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (ValueList a) Source #

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

justList :: SqlExpr (ValueList typ) -> SqlExpr (ValueList (Maybe typ)) Source #

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

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

exists :: SqlQuery () -> SqlExpr (Value Bool) Source #

notExists :: SqlQuery () -> SqlExpr (Value Bool) Source #

set :: PersistEntity val => SqlExpr (Entity val) -> [SqlExpr (Update val)] -> SqlQuery () Source #

(=.) :: (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Update val) Source #

(+=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Update val) Source #

(-=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Update val) Source #

(*=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Update val) Source #

(/=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Update val) Source #

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

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

case_ :: PersistField a => [(SqlExpr (Value Bool), SqlExpr (Value a))] -> SqlExpr (Value a) -> SqlExpr (Value a) Source #

toBaseId :: ToBaseId ent => SqlExpr (Value (Key ent)) -> SqlExpr (Value (Key (BaseEnt ent))) Source #

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

FROM clause: bring entities into scope.

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

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

  • expr (Entity val), which brings a single entity into scope.
  • expr (Maybe (Entity val)), which brings a single entity that may be NULL into scope. Used for OUTER JOINs.
  • A JOIN of any other two types allowed by the innermost magic, where a JOIN may be an InnerJoin, a CrossJoin, a LeftOuterJoin, a RightOuterJoin, or a FullOuterJoin. The JOINs have 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.

newtype 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 

Fields

Instances
Monad Value Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

(>>=) :: Value a -> (a -> Value b) -> Value b #

(>>) :: Value a -> Value b -> Value b #

return :: a -> Value a #

fail :: String -> Value a #

Functor Value Source #

Since: 1.4.4

Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

fmap :: (a -> b) -> Value a -> Value b #

(<$) :: a -> Value b -> Value a #

Applicative Value Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

pure :: a -> Value a #

(<*>) :: Value (a -> b) -> Value a -> Value b #

liftA2 :: (a -> b -> c) -> Value a -> Value b -> Value c #

(*>) :: Value a -> Value b -> Value b #

(<*) :: Value a -> Value b -> Value a #

ToSomeValues SqlExpr (SqlExpr (Value a)) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Sql

Eq a => Eq (Value a) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

(==) :: Value a -> Value a -> Bool #

(/=) :: Value a -> Value a -> Bool #

Ord a => Ord (Value a) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

compare :: Value a -> Value a -> Ordering #

(<) :: Value a -> Value a -> Bool #

(<=) :: Value a -> Value a -> Bool #

(>) :: Value a -> Value a -> Bool #

(>=) :: Value a -> Value a -> Bool #

max :: Value a -> Value a -> Value a #

min :: Value a -> Value a -> Value a #

Show a => Show (Value a) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

showsPrec :: Int -> Value a -> ShowS #

show :: Value a -> String #

showList :: [Value a] -> ShowS #

PersistField a => SqlSelect (SqlExpr (Value a)) (Value a) Source #

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

Instance details

Defined in Database.Esqueleto.Internal.Sql

newtype ValueList a Source #

A list of single values. There's a limited set of functions able to work with this data type (such as subList_select, valList, in_ and exists).

Constructors

ValueList a 
Instances
Eq a => Eq (ValueList a) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

(==) :: ValueList a -> ValueList a -> Bool #

(/=) :: ValueList a -> ValueList a -> Bool #

Ord a => Ord (ValueList a) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Show a => Show (ValueList a) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

data SomeValue expr where Source #

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

Constructors

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

class ToSomeValues expr a where Source #

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

Methods

toSomeValues :: a -> [SomeValue expr] Source #

Instances
ToSomeValues SqlExpr (SqlExpr (Value a)) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Sql

(ToSomeValues expr a, ToSomeValues expr b) => ToSomeValues expr (a, b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

toSomeValues :: (a, b) -> [SomeValue expr] Source #

(ToSomeValues expr a, ToSomeValues expr b, ToSomeValues expr c) => ToSomeValues expr (a, b, c) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

toSomeValues :: (a, b, c) -> [SomeValue expr] Source #

(ToSomeValues expr a, ToSomeValues expr b, ToSomeValues expr c, ToSomeValues expr d) => ToSomeValues expr (a, b, c, d) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

toSomeValues :: (a, b, c, d) -> [SomeValue expr] Source #

(ToSomeValues expr a, ToSomeValues expr b, ToSomeValues expr c, ToSomeValues expr d, ToSomeValues expr e) => ToSomeValues expr (a, b, c, d, e) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

toSomeValues :: (a, b, c, d, e) -> [SomeValue expr] Source #

(ToSomeValues expr a, ToSomeValues expr b, ToSomeValues expr c, ToSomeValues expr d, ToSomeValues expr e, ToSomeValues expr f) => ToSomeValues expr (a, b, c, d, e, f) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

toSomeValues :: (a, b, c, d, e, f) -> [SomeValue expr] Source #

(ToSomeValues expr a, ToSomeValues expr b, ToSomeValues expr c, ToSomeValues expr d, ToSomeValues expr e, ToSomeValues expr f, ToSomeValues expr g) => ToSomeValues expr (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

toSomeValues :: (a, b, c, d, e, f, g) -> [SomeValue expr] Source #

(ToSomeValues expr a, ToSomeValues expr b, ToSomeValues expr c, ToSomeValues expr d, ToSomeValues expr e, ToSomeValues expr f, ToSomeValues expr g, ToSomeValues expr h) => ToSomeValues expr (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

toSomeValues :: (a, b, c, d, e, f, g, h) -> [SomeValue expr] Source #

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 
Instances
IsJoinKind InnerJoin Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

(Esqueleto query expr backend, FromPreprocess query expr backend (InnerJoin a b)) => From query expr backend (InnerJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

from_ :: query (InnerJoin a b)

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 
Instances
IsJoinKind CrossJoin Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

(Esqueleto query expr backend, FromPreprocess query expr backend (CrossJoin a b)) => From query expr backend (CrossJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

from_ :: query (CrossJoin a b)

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 # 
Instance details

Defined in Database.Esqueleto.Internal.Language

(Esqueleto query expr backend, FromPreprocess query expr backend (LeftOuterJoin a b)) => From query expr backend (LeftOuterJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

from_ :: query (LeftOuterJoin a b)

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 # 
Instance details

Defined in Database.Esqueleto.Internal.Language

(Esqueleto query expr backend, FromPreprocess query expr backend (RightOuterJoin a b)) => From query expr backend (RightOuterJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

from_ :: query (RightOuterJoin a b)

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 # 
Instance details

Defined in Database.Esqueleto.Internal.Language

(Esqueleto query expr backend, FromPreprocess query expr backend (FullOuterJoin a b)) => From query expr backend (FullOuterJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

from_ :: query (FullOuterJoin a b)

data OnClauseWithoutMatchingJoinException Source #

Exception thrown whenever on is used to create an ON clause but no matching JOIN is found.

Instances
Eq OnClauseWithoutMatchingJoinException Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Ord OnClauseWithoutMatchingJoinException Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Show OnClauseWithoutMatchingJoinException Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Exception OnClauseWithoutMatchingJoinException Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

data OrderBy Source #

Phantom type used by orderBy, asc and desc.

data DistinctOn Source #

Phantom type used by distinctOn and don.

data Update typ Source #

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

data Insertion a Source #

Phantom type used by insertSelect.

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

FOR UPDATE syntax. Supported by MySQL, Oracle and PostgreSQL.

Since: 2.2.7

ForUpdateSkipLocked

FOR UPDATE SKIP LOCKED syntax. Supported by MySQL, Oracle and PostgreSQL.

Since: 2.2.7

ForShare

FOR SHARE syntax. Supported by PostgreSQL.

Since: 2.2.7

LockInShareMode

LOCK IN SHARE MODE syntax. Supported by MySQL.

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

Instances
SqlString ByteString Source #

Since: 2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Language

SqlString Text Source #

Since: 2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Language

SqlString Text Source #

Since: 2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Language

SqlString Html Source #

Since: 2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Language

a ~ Char => SqlString [a] Source #

Since: 2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Language

SqlString a => SqlString (Maybe a) Source #

Since: 2.4.0

Instance details

Defined in Database.Esqueleto.Internal.Language

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

Associated Types

type BaseEnt ent :: * Source #

Methods

toBaseIdWitness :: Key (BaseEnt ent) -> Key ent Source #

The guts

data JoinKind Source #

(Internal) A kind of JOIN.

Constructors

InnerJoinKind
INNER JOIN
CrossJoinKind
CROSS JOIN
LeftOuterJoinKind
LEFT OUTER JOIN
RightOuterJoinKind
RIGHT OUTER JOIN
FullOuterJoinKind
FULL OUTER JOIN
Instances
Eq JoinKind Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

class IsJoinKind join where Source #

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

Methods

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

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

reifyJoinKind :: join a b -> JoinKind Source #

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

class BackendCompatible sup sub where #

This class witnesses that two backend are compatible, and that you can convert from the sub backend into the sup backend. This is similar to the HasPersistBackend and IsPersistBackend classes, but where you don't want to fix the type associated with the PersistEntityBackend of a record.

Generally speaking, where you might have:

foo ::
  ( PersistEntity record
  , PeristEntityBackend record ~ BaseBackend backend
  , IsSqlBackend backend
  )

this can be replaced with:

foo ::
  ( PersistEntity record,
  , PersistEntityBackend record ~ backend
  , BackendCompatible SqlBackend backend
  )

This works for SqlReadBackend because of the instance BackendCompatible SqlBackend SqlReadBackend, without needing to go through the BaseBackend type family.

Likewise, functions that are currently hardcoded to use SqlBackend can be generalized:

-- before:
asdf :: ReaderT SqlBackend m ()
asdf = pure ()

-- after:
asdf' :: BackendCompatible SqlBackend backend => ReaderT backend m ()
asdf' = withReaderT projectBackend asdf

Since: persistent-2.7.1

Methods

projectBackend :: sub -> sup #

data PreprocessedFrom a Source #

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

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

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

Minimal complete definition

from_

Instances
(Esqueleto query expr backend, FromPreprocess query expr backend (expr (Maybe (Entity val)))) => From query expr backend (expr (Maybe (Entity val))) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

from_ :: query (expr (Maybe (Entity val)))

(Esqueleto query expr backend, FromPreprocess query expr backend (expr (Entity val))) => From query expr backend (expr (Entity val)) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

from_ :: query (expr (Entity val))

(From query expr backend a, From query expr backend b) => From query expr backend (a, b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

from_ :: query (a, b)

(Esqueleto query expr backend, FromPreprocess query expr backend (FullOuterJoin a b)) => From query expr backend (FullOuterJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

from_ :: query (FullOuterJoin a b)

(Esqueleto query expr backend, FromPreprocess query expr backend (RightOuterJoin a b)) => From query expr backend (RightOuterJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

from_ :: query (RightOuterJoin a b)

(Esqueleto query expr backend, FromPreprocess query expr backend (LeftOuterJoin a b)) => From query expr backend (LeftOuterJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

from_ :: query (LeftOuterJoin a b)

(Esqueleto query expr backend, FromPreprocess query expr backend (CrossJoin a b)) => From query expr backend (CrossJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

from_ :: query (CrossJoin a b)

(Esqueleto query expr backend, FromPreprocess query expr backend (InnerJoin a b)) => From query expr backend (InnerJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

from_ :: query (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) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

from_ :: query (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) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

from_ :: query (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) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

from_ :: query (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) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

from_ :: query (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) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

from_ :: query (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) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

from_ :: query (a, b, c, d, e, f, g, h)

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

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

Minimal complete definition

fromPreprocess

Instances
(Esqueleto query expr backend, PersistEntity val, BackendCompatible backend (PersistEntityBackend val)) => FromPreprocess query expr backend (expr (Maybe (Entity val))) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

fromPreprocess :: query (expr (PreprocessedFrom (expr (Maybe (Entity val)))))

(Esqueleto query expr backend, PersistEntity val, BackendCompatible backend (PersistEntityBackend val)) => FromPreprocess query expr backend (expr (Entity val)) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

fromPreprocess :: query (expr (PreprocessedFrom (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) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Language

Methods

fromPreprocess :: query (expr (PreprocessedFrom (join a b)))

when_ :: expr (Value Bool) -> () -> expr a -> (expr (Value Bool), expr a) Source #

Syntax sugar for case_.

Since: 2.1.2

then_ :: () Source #

Syntax sugar for case_.

Since: 2.1.2

else_ :: expr a -> expr a Source #

Syntax sugar for case_.

Since: 2.1.2