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

Safe HaskellNone
LanguageHaskell2010

Database.Esqueleto.Internal.Internal

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.

If you use this module, please report what your use case is on the issue tracker so we can safely support it.

Synopsis

Documentation

fromStart :: (PersistEntity a, BackendCompatible SqlBackend (PersistEntityBackend a)) => SqlQuery (SqlExpr (PreprocessedFrom (SqlExpr (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.

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

(Internal) Do a JOIN.

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

(Internal) Finish a JOIN.

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

WHERE clause: restrict the query's result.

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

An ON clause, useful to describe how two tables are related. Cross joins and tuple-joins do not need an on clause, but InnerJoin and the various outer joins do.

If you don't include an on clause (or include too many!) then a runtime exception will be thrown.

As an example, consider this simple join:

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

We need to specify the clause for joining the two columns together. If we had this:

select $
from $ \(foo `CrossJoin` bar) -> do
  ...

Then we can safely omit the on clause, because the cross join will make pairs of all records possible.

You can do multiple on clauses in a query. This query joins three tables, and has two on clauses:

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

Old versions of esqueleto required that you provide the on clauses in reverse order. This restriction has been lifted - you can now provide on clauses in any order, and the SQL should work itself out. The above query is now totally equivalent to this:

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

groupBy :: ToSomeValues a => a -> SqlQuery () 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 SqlSqlExpr (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)

Need more columns?

The ToSomeValues class is defined for SqlExpr and tuples of SqlExprs. We only have definitions for up to 8 elements in a tuple right now, so it's possible that you may need to have more than 8 elements.

For example, consider a query with a groupBy call like this:

groupBy (e0, e1, e2, e3, e4, e5, e6, e7)

This is the biggest you can get with a single tuple. However, you can easily nest the tuples to add more:

groupBy ((e0, e1, e2, e3, e4, e5, e6, e7), e8, e9)

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

ORDER BY clause. See also asc and desc.

Multiple calls to orderBy get concatenated on the final query, including distinctOnOrderBy.

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

Ascending order of this field or SqlExpression.

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

Descending order of this field or SqlExpression.

limit :: Int64 -> SqlQuery () Source #

LIMIT. Limit the number of returned rows.

offset :: Int64 -> SqlQuery () Source #

OFFSET. Usually used with limit.

distinct :: SqlQuery a -> SqlQuery 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 :: [SqlExpr DistinctOn] -> SqlQuery a -> SqlQuery a Source #

DISTINCT ON. Change the current SELECT into SELECT DISTINCT ON (SqlExpressions). 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 SqlExpressions. Calls to distinctOn override any calls to distinct.

Note that PostgreSQL requires the SqlExpressions 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 :: SqlExpr (Value a) -> SqlExpr DistinctOn Source #

Erase an SqlExpression's type so that it's suitable to be used by distinctOn.

Since: 2.2.4

distinctOnOrderBy :: [SqlExpr OrderBy] -> SqlQuery a -> SqlQuery 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 :: SqlExpr 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 :: SqlExpr (Value Bool) -> SqlQuery () Source #

HAVING.

Since: 1.2.2

locking :: LockingKind -> SqlQuery () 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 => SqlQuery (SqlExpr (Value a)) -> SqlExpr (Value a) Source #

Deprecated: sub_select sub_select is an unsafe function to use. If used with a SqlQuery that returns 0 results, then it may return NULL despite not mentioning Maybe in the return type. If it returns more than 1 result, then it will throw a SQL error. Instead, consider using one of the following alternatives: - subSelect: attaches a LIMIT 1 and the Maybe return type, totally safe. - subSelectMaybe: Attaches a LIMIT 1, useful for a query that already has a Maybe in the return type. - subSelectCount: Performs a count of the query - this is always safe. - subSelectUnsafe: Performs no checks or guarantees. Safe to use with countRows and friends.

Execute a subquery SELECT in an SqlExpression. Returns a simple value so should be used only when the SELECT query is guaranteed to return just one row.

Deprecated in 3.2.0.

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

Execute a subquery SELECT in a SqlExpr. The query passed to this function will only return a single result - it has a LIMIT 1 passed in to the query to make it safe, and the return type is Maybe to indicate that the subquery might result in 0 rows.

If you find yourself writing joinV . subSelect, then consider using subSelectMaybe.

If you're performing a countRows, then you can use subSelectCount which is safe.

If you know that the subquery will always return exactly one row (eg a foreign key constraint guarantees that you'll get exactly one row), then consider subSelectUnsafe, along with a comment explaining why it is safe.

Since: 3.2.0

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

Execute a subquery SELECT in a SqlExpr. This function is a shorthand for the common joinV . subSelect idiom, where you are calling subSelect on an expression that would be Maybe already.

As an example, you would use this function when calling sum_ or max_, which have Maybe in the result type (for a 0 row query).

Since: 3.2.0

subSelectCount :: (Num a, PersistField a) => SqlQuery ignored -> SqlExpr (Value a) Source #

Performs a COUNT of the given query in a subSelect manner. This is always guaranteed to return a result value, and is completely safe.

Since: 3.2.0

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

Execute a subquery SELECT in a SqlExpr that returns a list. This is an alias for subList_select and is provided for symmetry with the other safe subselect functions.

Since: 3.2.0

subSelectForeign Source #

Arguments

:: (BackendCompatible SqlBackend (PersistEntityBackend val1), PersistEntity val1, PersistEntity val2, PersistField a) 
=> SqlExpr (Entity val2)

An expression representing the table you have access to now.

-> EntityField val2 (Key val1)

The foreign key field on the table.

-> (SqlExpr (Entity val1) -> SqlExpr (Value a))

A function to extract a value from the foreign reference table.

-> SqlExpr (Value a) 

Performs a sub-select using the given foreign key on the entity. This is useful to extract values that are known to be present by the database schema.

As an example, consider the following persistent definition:

User
  profile ProfileId

Profile
  name    Text

The following query will return the name of the user.

getUserWithName =
    select $
    from $ user ->
    pure (user, subSelectForeign user UserProfile (^. ProfileName)

Since: 3.2.0

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

Execute a subquery SELECT in a SqlExpr. This function is unsafe, because it can throw runtime exceptions in two cases:

  1. If the query passed has 0 result rows, then it will return a NULL value. The persistent parsing operations will fail on an unexpected NULL.
  2. If the query passed returns more than one row, then the SQL engine will fail with an error like "More than one row returned by a subquery used as an expression".

This function is safe if you guarantee that exactly one row will be returned, or if the result already has a Maybe type for some reason.

For variants with the safety encoded already, see subSelect and subSelectMaybe. For the most common safe use of this, see subSelectCount.

Since: 3.2.0

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

Project a field of an entity.

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

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

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

Project a field of an entity that may be null.

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

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

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

IS NULL comparison.

just :: SqlExpr (Value typ) -> SqlExpr (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 :: SqlExpr (Value (Maybe typ)) Source #

NULL value.

joinV :: SqlExpr (Value (Maybe (Maybe typ))) -> SqlExpr (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 => SqlExpr (Value a) Source #

COUNT(*) value.

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

COUNT.

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

COUNT(DISTINCT x).

Since: 2.4.1

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

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

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

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

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

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

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

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

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

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

between :: PersistField a => SqlExpr (Value a) -> (SqlExpr (Value a), SqlExpr (Value a)) -> SqlExpr (Value Bool) Source #

BETWEEN.

@since: 3.1.0

random_ :: (PersistField a, Num a) => SqlExpr (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_

castNum :: (Num a, Num b) => SqlExpr (Value a) -> SqlExpr (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) => SqlExpr (Value (Maybe a)) -> SqlExpr (Value (Maybe b)) Source #

Same as castNum, but for nullable values.

Since: 2.2.9

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

COALESCE function. Evaluates the arguments in order and returns the value of the first non-NULL SqlExpression, 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 => [SqlExpr (Value (Maybe a))] -> SqlExpr (Value a) -> SqlExpr (Value a) Source #

Like coalesce, but takes a non-nullable SqlExpression placed at the end of the SqlExpression list, which guarantees a non-NULL result.

Since: 1.4.3

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

LOWER function.

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

UPPER function. Since: 3.3.0

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

TRIM function. Since: 3.3.0

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

RTRIM function. Since: 3.3.0

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

LTRIM function. Since: 3.3.0

length_ :: (SqlString s, Num a) => SqlExpr (Value s) -> SqlExpr (Value a) Source #

LENGTH function. Since: 3.3.0

left_ :: (SqlString s, Num a) => (SqlExpr (Value s), SqlExpr (Value a)) -> SqlExpr (Value s) Source #

LEFT function. Since: 3.3.0

right_ :: (SqlString s, Num a) => (SqlExpr (Value s), SqlExpr (Value a)) -> SqlExpr (Value s) Source #

RIGHT function. Since: 3.3.0

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

LIKE operator.

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

ILIKE operator (case-insensitive LIKE).

Supported by PostgreSQL only.

Since: 2.2.3

(%) :: SqlString s => SqlExpr (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 => [SqlExpr (Value s)] -> SqlExpr (Value s) Source #

The CONCAT function with a variable number of parameters. Supported by MySQL and PostgreSQL.

(++.) :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) -> SqlExpr (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) => SqlExpr (Value s) -> SqlExpr (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 => SqlQuery (SqlExpr (Value a)) -> SqlExpr (ValueList a) Source #

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

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

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

justList :: SqlExpr (ValueList typ) -> SqlExpr (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 => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (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 => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool) Source #

NOT IN operator.

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

EXISTS operator. For example:

select $
from $ \person -> do
where_ $ exists $
         from $ \post -> do
         where_ (post ^. BlogPostAuthorId ==. person ^. PersonId)
return person

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

NOT EXISTS operator.

set :: PersistEntity val => SqlExpr (Entity val) -> [SqlExpr (Update val)] -> SqlQuery () 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 -> SqlExpr (Value typ) -> SqlExpr (Update val) infixr 3 Source #

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

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

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

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

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

Apply a PersistField constructor to SqlExpr Value arguments.

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

Apply extra SqlExpr Value arguments to a PersistField constructor

case_ :: PersistField a => [(SqlExpr (Value Bool), SqlExpr (Value a))] -> SqlExpr (Value a) -> SqlExpr (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 => SqlExpr (Value (Key ent)) -> SqlExpr (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
  bar BarId
  fooNum Int
  Primary bar

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

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

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

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

Methods

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

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

Applicative Value Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

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 #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

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

Defined in Database.Esqueleto.Internal.Internal

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

Methods

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

show :: Value a -> String #

showList :: [Value a] -> ShowS #

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

Defined in Database.Esqueleto.Internal.Internal

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

Defined in Database.Esqueleto.Experimental

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

Defined in Database.Esqueleto.Experimental

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

Defined in Database.Esqueleto.Experimental

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

(ToFrom a, ToFromT a ~ a', ToFrom b, ToFromT b ~ b', ToMaybe a', ma ~ ToMaybeT a', ToMaybe b', mb ~ ToMaybeT b') => ToFrom (FullOuterJoin a (b, (ma :& mb) -> SqlExpr (Value Bool))) Source # 
Instance details

Defined in Database.Esqueleto.Experimental

Methods

toFrom :: FullOuterJoin a (b, (ma :& mb) -> SqlExpr (Value Bool)) -> From (ToFromT (FullOuterJoin a (b, (ma :& mb) -> SqlExpr (Value Bool)))) Source #

(ToFrom a, ToFromT a ~ a', ToFrom b, ToFromT b ~ b', ToMaybe a', ma ~ ToMaybeT a') => ToFrom (RightOuterJoin a (b, (ma :& b') -> SqlExpr (Value Bool))) Source # 
Instance details

Defined in Database.Esqueleto.Experimental

Methods

toFrom :: RightOuterJoin a (b, (ma :& b') -> SqlExpr (Value Bool)) -> From (ToFromT (RightOuterJoin a (b, (ma :& b') -> SqlExpr (Value Bool)))) Source #

(ToFrom a, ToFromT a ~ a', ToFrom b, ToFromT b ~ b', ToMaybe b', mb ~ ToMaybeT b') => ToFrom (LeftOuterJoin a (b, (a' :& mb) -> SqlExpr (Value Bool))) Source # 
Instance details

Defined in Database.Esqueleto.Experimental

Methods

toFrom :: LeftOuterJoin a (b, (a' :& mb) -> SqlExpr (Value Bool)) -> From (ToFromT (LeftOuterJoin a (b, (a' :& mb) -> SqlExpr (Value Bool)))) Source #

(ToFrom a, ToFromT a ~ a', ToFrom b, ToFromT b ~ b') => ToFrom (InnerJoin a (b, (a' :& b') -> SqlExpr (Value Bool))) Source # 
Instance details

Defined in Database.Esqueleto.Experimental

Methods

toFrom :: InnerJoin a (b, (a' :& b') -> SqlExpr (Value Bool)) -> From (ToFromT (InnerJoin a (b, (a' :& b') -> SqlExpr (Value Bool)))) Source #

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

Methods

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

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

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

Defined in Database.Esqueleto.Internal.Internal

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

Defined in Database.Esqueleto.Internal.Internal

data SomeValue where Source #

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

Constructors

SomeValue :: SqlExpr (Value a) -> SomeValue 

class ToSomeValues 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] Source #

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

Defined in Database.Esqueleto.Internal.Internal

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

type family KnowResult a where ... Source #

Equations

KnowResult (i -> o) = KnowResult o 
KnowResult a = a 

class FinalResult a where Source #

A class for constructors or function which result type is known.

Since: 3.1.3

Methods

finalR :: a -> KnowResult a Source #

Instances
FinalResult (Unique val) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

finalR :: Unique val -> KnowResult (Unique val) Source #

FinalResult b => FinalResult (a -> b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

finalR :: (a -> b) -> KnowResult (a -> b) Source #

toUniqueDef :: forall a val. (KnowResult a ~ Unique val, PersistEntity val, FinalResult a) => a -> UniqueDef Source #

Convert a constructor for a Unique key on a record to the UniqueDef that defines it. You can supply just the constructor itself, or a value of the type - the library is capable of figuring it out from there.

Since: 3.1.3

renderUpdates :: BackendCompatible SqlBackend backend => backend -> [SqlExpr (Update val)] -> (Builder, [PersistValue]) Source #

Render updates to be use in a SET clause for a given sql backend.

Since: 3.1.3

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

FromPreprocess (InnerJoin a b) => From (InnerJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (InnerJoin a b) Source #

(ToFrom a, ToFromT a ~ a', ToFrom b, ToFromT b ~ b') => ToFrom (InnerJoin a (b, (a' :& b') -> SqlExpr (Value Bool))) Source # 
Instance details

Defined in Database.Esqueleto.Experimental

Methods

toFrom :: InnerJoin a (b, (a' :& b') -> SqlExpr (Value Bool)) -> From (ToFromT (InnerJoin a (b, (a' :& b') -> SqlExpr (Value Bool)))) Source #

ToFrom (InnerJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Experimental

Methods

toFrom :: InnerJoin a b -> From (ToFromT (InnerJoin a b)) Source #

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

FromPreprocess (CrossJoin a b) => From (CrossJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (CrossJoin a b) Source #

(ToFrom a, ToFrom b) => ToFrom (CrossJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Experimental

Methods

toFrom :: CrossJoin a b -> From (ToFromT (CrossJoin a b)) Source #

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

FromPreprocess (LeftOuterJoin a b) => From (LeftOuterJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

(ToFrom a, ToFromT a ~ a', ToFrom b, ToFromT b ~ b', ToMaybe b', mb ~ ToMaybeT b') => ToFrom (LeftOuterJoin a (b, (a' :& mb) -> SqlExpr (Value Bool))) Source # 
Instance details

Defined in Database.Esqueleto.Experimental

Methods

toFrom :: LeftOuterJoin a (b, (a' :& mb) -> SqlExpr (Value Bool)) -> From (ToFromT (LeftOuterJoin a (b, (a' :& mb) -> SqlExpr (Value Bool)))) Source #

ToFrom (LeftOuterJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Experimental

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

FromPreprocess (RightOuterJoin a b) => From (RightOuterJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

(ToFrom a, ToFromT a ~ a', ToFrom b, ToFromT b ~ b', ToMaybe a', ma ~ ToMaybeT a') => ToFrom (RightOuterJoin a (b, (ma :& b') -> SqlExpr (Value Bool))) Source # 
Instance details

Defined in Database.Esqueleto.Experimental

Methods

toFrom :: RightOuterJoin a (b, (ma :& b') -> SqlExpr (Value Bool)) -> From (ToFromT (RightOuterJoin a (b, (ma :& b') -> SqlExpr (Value Bool)))) Source #

ToFrom (RightOuterJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Experimental

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

FromPreprocess (FullOuterJoin a b) => From (FullOuterJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

(ToFrom a, ToFromT a ~ a', ToFrom b, ToFromT b ~ b', ToMaybe a', ma ~ ToMaybeT a', ToMaybe b', mb ~ ToMaybeT b') => ToFrom (FullOuterJoin a (b, (ma :& mb) -> SqlExpr (Value Bool))) Source # 
Instance details

Defined in Database.Esqueleto.Experimental

Methods

toFrom :: FullOuterJoin a (b, (ma :& mb) -> SqlExpr (Value Bool)) -> From (ToFromT (FullOuterJoin a (b, (ma :& mb) -> SqlExpr (Value Bool)))) Source #

ToFrom (FullOuterJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Experimental

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

Show JoinKind Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

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.

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

Ord OnClauseWithoutMatchingJoinException Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Show OnClauseWithoutMatchingJoinException Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Exception OnClauseWithoutMatchingJoinException Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

data PreprocessedFrom a Source #

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

data OrderBy Source #

Phantom type used by orderBy, asc and desc.

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

SqlString Text Source #

Since: 2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlString Text Source #

Since: 2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlString Html Source #

Since: 2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

a ~ Char => SqlString [a] Source #

Since: 2.3.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlString a => SqlString (Maybe a) Source #

Since: 2.4.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

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 #

from :: From a => (a -> SqlQuery b) -> SqlQuery 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.

class From a where Source #

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

Methods

from_ :: SqlQuery a Source #

Instances
FromPreprocess (SqlExpr (Maybe (Entity val))) => From (SqlExpr (Maybe (Entity val))) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (SqlExpr (Maybe (Entity val))) Source #

FromPreprocess (SqlExpr (Entity val)) => From (SqlExpr (Entity val)) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (SqlExpr (Entity val)) Source #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (a, b) Source #

FromPreprocess (FullOuterJoin a b) => From (FullOuterJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

FromPreprocess (RightOuterJoin a b) => From (RightOuterJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

FromPreprocess (LeftOuterJoin a b) => From (LeftOuterJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

FromPreprocess (CrossJoin a b) => From (CrossJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (CrossJoin a b) Source #

FromPreprocess (InnerJoin a b) => From (InnerJoin a b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (InnerJoin a b) Source #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (a, b, c) Source #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (a, b, c, d) Source #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (a, b, c, d, e) Source #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (a, b, c, d, e, f) Source #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (a, b, c, d, e, f, g) Source #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (a, b, c, d, e, f, g, h) Source #

newtype SqlQuery a Source #

SQL backend for esqueleto using SqlPersistT.

Constructors

Q 
Instances
Monad SqlQuery Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

return :: a -> SqlQuery a #

fail :: String -> SqlQuery a #

Functor SqlQuery Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

Applicative SqlQuery Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

pure :: a -> SqlQuery a #

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

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

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

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

type SqlEntity ent = (PersistEntity ent, PersistEntityBackend ent ~ SqlBackend) Source #

Constraint synonym for persistent entities whose backend is SqlPersistT.

newtype SetClause Source #

A part of a SET clause.

Constructors

SetClause (SqlExpr (Value ())) 

collectOnClauses :: SqlBackend -> [FromClause] -> Either (SqlExpr (Value Bool)) [FromClause] Source #

Collect OnClauses on FromJoins. Returns the first unmatched OnClauses data on error. Returns a list without OnClauses on success.

type HavingClause = WhereClause Source #

A HAVING cause.

type OrderByClause = SqlExpr OrderBy Source #

A ORDER BY clause.

type LockingClause = Last LockingKind Source #

A locking clause.

newtype Ident Source #

Identifier used for table names.

Constructors

I Text 
Instances
Eq Ident Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

(==) :: Ident -> Ident -> Bool #

(/=) :: Ident -> Ident -> Bool #

Ord Ident Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

compare :: Ident -> Ident -> Ordering #

(<) :: Ident -> Ident -> Bool #

(<=) :: Ident -> Ident -> Bool #

(>) :: Ident -> Ident -> Bool #

(>=) :: Ident -> Ident -> Bool #

max :: Ident -> Ident -> Ident #

min :: Ident -> Ident -> Ident #

Show Ident Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

newtype IdentState Source #

List of identifiers already in use and supply of temporary identifiers.

Constructors

IdentState 

Fields

newIdentFor :: DBName -> SqlQuery Ident Source #

Create a fresh Ident. If possible, use the given DBName.

type IdentInfo = (SqlBackend, IdentState) Source #

Information needed to escape and use identifiers.

useIdent :: IdentInfo -> Ident -> Builder Source #

Use an identifier.

data SqlExpr a where Source #

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

Constructors

EEntity :: Ident -> SqlExpr (Entity val) 
EAliasedEntity :: Ident -> Ident -> SqlExpr (Entity val) 
EAliasedEntityReference :: Ident -> Ident -> SqlExpr (Entity val) 
EMaybe :: SqlExpr a -> SqlExpr (Maybe a) 
ERaw :: NeedParens -> (IdentInfo -> (Builder, [PersistValue])) -> SqlExpr (Value a) 
EAliasedValue :: Ident -> SqlExpr (Value a) -> SqlExpr (Value a) 
EValueReference :: Ident -> (IdentInfo -> Ident) -> SqlExpr (Value a) 
ECompositeKey :: (IdentInfo -> [Builder]) -> SqlExpr (Value a) 
EList :: SqlExpr (Value a) -> SqlExpr (ValueList a) 
EEmptyList :: SqlExpr (ValueList a) 
EOrderBy :: OrderByType -> SqlExpr (Value a) -> SqlExpr OrderBy 
EOrderRandom :: SqlExpr OrderBy

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.

EDistinctOn :: SqlExpr (Value a) -> SqlExpr DistinctOn 
ESet :: (SqlExpr (Entity val) -> SqlExpr (Value ())) -> SqlExpr (Update val) 
EPreprocessedFrom :: a -> FromClause -> SqlExpr (PreprocessedFrom a) 
EInsert :: Proxy a -> (IdentInfo -> (Builder, [PersistValue])) -> SqlExpr (Insertion a) 
EInsertFinal :: PersistEntity a => SqlExpr (Insertion a) -> SqlExpr InsertFinal 
Instances
a ~ Value b => UnsafeSqlFunctionArgument (SqlExpr a) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

toArgList :: SqlExpr a -> [SqlExpr (Value ())] Source #

(PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => FromPreprocess (SqlExpr (Maybe (Entity val))) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

(PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => FromPreprocess (SqlExpr (Entity val)) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

FromPreprocess (SqlExpr (Maybe (Entity val))) => From (SqlExpr (Maybe (Entity val))) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (SqlExpr (Maybe (Entity val))) Source #

FromPreprocess (SqlExpr (Entity val)) => From (SqlExpr (Entity val)) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

from_ :: SqlQuery (SqlExpr (Entity val)) Source #

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

Defined in Database.Esqueleto.Internal.Internal

ToAliasReference (SqlExpr (Entity a)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental

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

Defined in Database.Esqueleto.Experimental

ToAlias (SqlExpr (Entity a)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental

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

Defined in Database.Esqueleto.Experimental

ToMaybe (SqlExpr (Maybe a)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental

ToMaybe (SqlExpr (Entity a)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental

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

Defined in Database.Esqueleto.Experimental

SqlSelect (SqlExpr InsertFinal) InsertFinal Source #

INSERT INTO hack.

Instance details

Defined in Database.Esqueleto.Internal.Internal

PersistEntity a => SqlSelect (SqlExpr (Maybe (Entity a))) (Maybe (Entity a)) Source #

You may return a possibly-NULL Entity from a select query.

Instance details

Defined in Database.Esqueleto.Internal.Internal

PersistEntity a => SqlSelect (SqlExpr (Entity a)) (Entity a) Source #

You may return an Entity from a select query.

Instance details

Defined in Database.Esqueleto.Internal.Internal

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

(ToFrom a, ToFromT a ~ a', ToFrom b, ToFromT b ~ b', ToMaybe a', ma ~ ToMaybeT a', ToMaybe b', mb ~ ToMaybeT b') => ToFrom (FullOuterJoin a (b, (ma :& mb) -> SqlExpr (Value Bool))) Source # 
Instance details

Defined in Database.Esqueleto.Experimental

Methods

toFrom :: FullOuterJoin a (b, (ma :& mb) -> SqlExpr (Value Bool)) -> From (ToFromT (FullOuterJoin a (b, (ma :& mb) -> SqlExpr (Value Bool)))) Source #

(ToFrom a, ToFromT a ~ a', ToFrom b, ToFromT b ~ b', ToMaybe a', ma ~ ToMaybeT a') => ToFrom (RightOuterJoin a (b, (ma :& b') -> SqlExpr (Value Bool))) Source # 
Instance details

Defined in Database.Esqueleto.Experimental

Methods

toFrom :: RightOuterJoin a (b, (ma :& b') -> SqlExpr (Value Bool)) -> From (ToFromT (RightOuterJoin a (b, (ma :& b') -> SqlExpr (Value Bool)))) Source #

(ToFrom a, ToFromT a ~ a', ToFrom b, ToFromT b ~ b', ToMaybe b', mb ~ ToMaybeT b') => ToFrom (LeftOuterJoin a (b, (a' :& mb) -> SqlExpr (Value Bool))) Source # 
Instance details

Defined in Database.Esqueleto.Experimental

Methods

toFrom :: LeftOuterJoin a (b, (a' :& mb) -> SqlExpr (Value Bool)) -> From (ToFromT (LeftOuterJoin a (b, (a' :& mb) -> SqlExpr (Value Bool)))) Source #

(ToFrom a, ToFromT a ~ a', ToFrom b, ToFromT b ~ b') => ToFrom (InnerJoin a (b, (a' :& b') -> SqlExpr (Value Bool))) Source # 
Instance details

Defined in Database.Esqueleto.Experimental

Methods

toFrom :: InnerJoin a (b, (a' :& b') -> SqlExpr (Value Bool)) -> From (ToFromT (InnerJoin a (b, (a' :& b') -> SqlExpr (Value Bool)))) Source #

data NeedParens Source #

Constructors

Parens 
Never 

data OrderByType Source #

Constructors

ASC 
DESC 

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

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

(Internal) Create a case statement.

Since: 2.1.1

unsafeSqlBinOp :: Builder -> SqlExpr (Value a) -> SqlExpr (Value b) -> SqlExpr (Value c) Source #

(Internal) Create a custom binary operator. You should not use this function directly since its type is very general, you should always use it with an explicit type signature. For example:

(==.) :: SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value Bool)
(==.) = unsafeSqlBinOp " = "

In the example above, we constraint the arguments to be of the same type and constraint the result to be a boolean value.

unsafeSqlBinOpComposite :: Builder -> Builder -> SqlExpr (Value a) -> SqlExpr (Value b) -> SqlExpr (Value c) Source #

Similar to unsafeSqlBinOp, but may also be applied to composite keys. Uses the operator given as the second argument whenever applied to composite keys.

Usage example:

(==.) :: SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value Bool)
(==.) = unsafeSqlBinOpComposite " = " " AND "

Persistent has a hack for implementing composite keys (see ECompositeKey doc for more details), so we're forced to use a hack here as well. We deconstruct ERaw values based on two rules:

  • If it is a single placeholder, then it's assumed to be coming from a PersistList and thus its components are separated so that they may be applied to a composite key.
  • If it is not a single placeholder, then it's assumed to be a foreign (composite or not) key, so we enforce that it has no placeholders and split it on the commas.

unsafeSqlValue :: Builder -> SqlExpr (Value a) Source #

(Internal) A raw SQL value. The same warning from unsafeSqlBinOp applies to this function as well.

unsafeSqlFunction :: UnsafeSqlFunctionArgument a => Builder -> a -> SqlExpr (Value b) Source #

(Internal) A raw SQL function. Once again, the same warning from unsafeSqlBinOp applies to this function as well.

unsafeSqlExtractSubField :: UnsafeSqlFunctionArgument a => Builder -> a -> SqlExpr (Value b) Source #

(Internal) An unsafe SQL function to extract a subfield from a compound field, e.g. datetime. See unsafeSqlBinOp for warnings.

Since: 1.3.6.

unsafeSqlFunctionParens :: UnsafeSqlFunctionArgument a => Builder -> a -> SqlExpr (Value b) Source #

(Internal) A raw SQL function. Preserves parentheses around arguments. See unsafeSqlBinOp for warnings.

unsafeSqlCastAs :: Text -> SqlExpr (Value a) -> SqlExpr (Value b) Source #

(Internal) An explicit SQL type cast using CAST(value as type). See unsafeSqlBinOp for warnings.

class UnsafeSqlFunctionArgument a where Source #

(Internal) This class allows unsafeSqlFunction to work with different numbers of arguments; specifically it allows providing arguments to a sql function via an n-tuple of SqlExpr (Value _) values, which are not all necessarily required to be the same type. There are instances for up to 10-tuples, but for sql functions which take more than 10 arguments, you can also nest tuples, as e.g. toArgList ((a,b),(c,d)) is the same as toArgList (a,b,c,d).

Methods

toArgList :: a -> [SqlExpr (Value ())] Source #

Instances
UnsafeSqlFunctionArgument () Source #

Useful for 0-argument functions, like now in Postgresql.

Since: 3.2.1

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

toArgList :: () -> [SqlExpr (Value ())] Source #

UnsafeSqlFunctionArgument a => UnsafeSqlFunctionArgument [a] Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

toArgList :: [a] -> [SqlExpr (Value ())] Source #

a ~ Value b => UnsafeSqlFunctionArgument (SqlExpr a) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

toArgList :: SqlExpr a -> [SqlExpr (Value ())] Source #

(UnsafeSqlFunctionArgument a, UnsafeSqlFunctionArgument b) => UnsafeSqlFunctionArgument (a, b) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

toArgList :: (a, b) -> [SqlExpr (Value ())] Source #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

toArgList :: (a, b, c) -> [SqlExpr (Value ())] Source #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

toArgList :: (a, b, c, d) -> [SqlExpr (Value ())] Source #

(UnsafeSqlFunctionArgument a, UnsafeSqlFunctionArgument b, UnsafeSqlFunctionArgument c, UnsafeSqlFunctionArgument d, UnsafeSqlFunctionArgument e) => UnsafeSqlFunctionArgument (a, b, c, d, e) Source #

Since: 3.2.3

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

toArgList :: (a, b, c, d, e) -> [SqlExpr (Value ())] Source #

(UnsafeSqlFunctionArgument a, UnsafeSqlFunctionArgument b, UnsafeSqlFunctionArgument c, UnsafeSqlFunctionArgument d, UnsafeSqlFunctionArgument e, UnsafeSqlFunctionArgument f) => UnsafeSqlFunctionArgument (a, b, c, d, e, f) Source #

Since: 3.2.3

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

toArgList :: (a, b, c, d, e, f) -> [SqlExpr (Value ())] Source #

(UnsafeSqlFunctionArgument a, UnsafeSqlFunctionArgument b, UnsafeSqlFunctionArgument c, UnsafeSqlFunctionArgument d, UnsafeSqlFunctionArgument e, UnsafeSqlFunctionArgument f, UnsafeSqlFunctionArgument g) => UnsafeSqlFunctionArgument (a, b, c, d, e, f, g) Source #

Since: 3.2.3

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

toArgList :: (a, b, c, d, e, f, g) -> [SqlExpr (Value ())] Source #

(UnsafeSqlFunctionArgument a, UnsafeSqlFunctionArgument b, UnsafeSqlFunctionArgument c, UnsafeSqlFunctionArgument d, UnsafeSqlFunctionArgument e, UnsafeSqlFunctionArgument f, UnsafeSqlFunctionArgument g, UnsafeSqlFunctionArgument h) => UnsafeSqlFunctionArgument (a, b, c, d, e, f, g, h) Source #

Since: 3.2.3

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

toArgList :: (a, b, c, d, e, f, g, h) -> [SqlExpr (Value ())] Source #

(UnsafeSqlFunctionArgument a, UnsafeSqlFunctionArgument b, UnsafeSqlFunctionArgument c, UnsafeSqlFunctionArgument d, UnsafeSqlFunctionArgument e, UnsafeSqlFunctionArgument f, UnsafeSqlFunctionArgument g, UnsafeSqlFunctionArgument h, UnsafeSqlFunctionArgument i) => UnsafeSqlFunctionArgument (a, b, c, d, e, f, g, h, i) Source #

Since: 3.2.3

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

toArgList :: (a, b, c, d, e, f, g, h, i) -> [SqlExpr (Value ())] Source #

(UnsafeSqlFunctionArgument a, UnsafeSqlFunctionArgument b, UnsafeSqlFunctionArgument c, UnsafeSqlFunctionArgument d, UnsafeSqlFunctionArgument e, UnsafeSqlFunctionArgument f, UnsafeSqlFunctionArgument g, UnsafeSqlFunctionArgument h, UnsafeSqlFunctionArgument i, UnsafeSqlFunctionArgument j) => UnsafeSqlFunctionArgument (a, b, c, d, e, f, g, h, i, j) Source #

Since: 3.2.3

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

toArgList :: (a, b, c, d, e, f, g, h, i, j) -> [SqlExpr (Value ())] Source #

veryUnsafeCoerceSqlExprValue :: SqlExpr (Value a) -> SqlExpr (Value b) Source #

(Internal) Coerce a value's type from 'SqlExpr (Value a)' to 'SqlExpr (Value b)'. You should not use this function unless you know what you're doing!

veryUnsafeCoerceSqlExprValueList :: SqlExpr (ValueList a) -> SqlExpr (Value a) Source #

(Internal) Coerce a value's type from 'SqlExpr (ValueList a)' to 'SqlExpr (Value a)'. Does not work with empty lists.

rawSelectSource :: (SqlSelect a r, MonadIO m1, MonadIO m2) => Mode -> SqlQuery a -> SqlReadT m1 (Acquire (ConduitT () r m2 ())) Source #

(Internal) Execute an esqueleto SELECT SqlQuery inside persistent's SqlPersistT monad.

selectSource :: (SqlSelect a r, BackendCompatible SqlBackend backend, IsPersistBackend backend, PersistQueryRead backend, PersistStoreRead backend, PersistUniqueRead backend, MonadResource m) => SqlQuery a -> ConduitT () r (ReaderT backend m) () Source #

Execute an esqueleto SELECT query inside persistent's SqlPersistT monad and return a Source of rows.

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 (Entity v) for an entity v (i.e., like the * in SQL), which is then returned to Haskell-land as just Entity v.
  • You may return a SqlExpr (Maybe (Entity v)) for an entity v that may be NULL, which is then returned to Haskell-land as Maybe (Entity v). Used for OUTER JOINs.
  • You may return a SqlExpr (Value t) for a value t (i.e., a single column), where t is any instance of PersistField, which is then returned to Haskell-land as Value t. You may use Value to return projections of an Entity (see (^.) and (?.)) or to return any other value calculated on the query (e.g., countRows or subSelect).

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 select $ from $ \p -> return p alone is ambiguous, but in the context of

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

runSource :: Monad m => ConduitT () r (ReaderT backend m) () -> ReaderT backend m [r] Source #

(Internal) Run a Source of rows.

rawEsqueleto :: (MonadIO m, SqlSelect a r, BackendCompatible SqlBackend backend) => Mode -> SqlQuery a -> ReaderT backend m Int64 Source #

(Internal) Execute an esqueleto statement inside persistent's SqlPersistT monad.

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, PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend 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 -> do
set p [ PersonAge =. just (val thisYear) -. p ^. PersonBorn ]
where_ $ isNothing (p ^. PersonAge)

updateCount :: (MonadIO m, PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => (SqlExpr (Entity val) -> SqlQuery ()) -> SqlWriteT m Int64 Source #

Same as update, but returns the number of rows affected.

toRawSql :: (SqlSelect a r, BackendCompatible SqlBackend backend) => Mode -> (backend, IdentState) -> SqlQuery a -> (Builder, [PersistValue]) Source #

(Internal) Pretty prints a SqlQuery into a SQL query.

Note: if you're curious about the SQL query being generated by esqueleto, instead of manually using this function (which is possible but tedious), see the renderQueryToText function (along with renderQuerySelect, renderQueryUpdate, etc).

renderQueryToText Source #

Arguments

:: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) 
=> Mode

Whether to render as an SELECT, DELETE, etc.

-> SqlQuery a

The SQL query you want to render.

-> ReaderT backend m (Text, [PersistValue]) 

Renders a SqlQuery into a Text value along with the list of PersistValues that would be supplied to the database for ? placeholders.

You must ensure that the Mode you pass to this function corresponds with the actual SqlQuery. If you pass a query that uses incompatible features (like an INSERT statement with a SELECT mode) then you'll get a weird result.

Since: 3.1.1

renderQuerySelect Source #

Arguments

:: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) 
=> SqlQuery a

The SQL query you want to render.

-> ReaderT backend m (Text, [PersistValue]) 

Renders a SqlQuery into a Text value along with the list of PersistValues that would be supplied to the database for ? placeholders.

You must ensure that the Mode you pass to this function corresponds with the actual SqlQuery. If you pass a query that uses incompatible features (like an INSERT statement with a SELECT mode) then you'll get a weird result.

Since: 3.1.1

renderQueryDelete Source #

Arguments

:: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) 
=> SqlQuery a

The SQL query you want to render.

-> ReaderT backend m (Text, [PersistValue]) 

Renders a SqlQuery into a Text value along with the list of PersistValues that would be supplied to the database for ? placeholders.

You must ensure that the Mode you pass to this function corresponds with the actual SqlQuery. If you pass a query that uses incompatible features (like an INSERT statement with a SELECT mode) then you'll get a weird result.

Since: 3.1.1

renderQueryUpdate Source #

Arguments

:: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) 
=> SqlQuery a

The SQL query you want to render.

-> ReaderT backend m (Text, [PersistValue]) 

Renders a SqlQuery into a Text value along with the list of PersistValues that would be supplied to the database for ? placeholders.

You must ensure that the Mode you pass to this function corresponds with the actual SqlQuery. If you pass a query that uses incompatible features (like an INSERT statement with a SELECT mode) then you'll get a weird result.

Since: 3.1.1

renderQueryInsertInto Source #

Arguments

:: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) 
=> SqlQuery a

The SQL query you want to render.

-> ReaderT backend m (Text, [PersistValue]) 

Renders a SqlQuery into a Text value along with the list of PersistValues that would be supplied to the database for ? placeholders.

You must ensure that the Mode you pass to this function corresponds with the actual SqlQuery. If you pass a query that uses incompatible features (like an INSERT statement with a SELECT mode) then you'll get a weird result.

Since: 3.1.1

data Mode Source #

(Internal) Mode of query being converted by toRawSql.

Constructors

SELECT 
DELETE 
UPDATE 
INSERT_INTO 

uncommas' :: Monoid a => [(Builder, a)] -> (Builder, a) Source #

class SqlSelect a r | a -> r, r -> a where Source #

(Internal) Class for mapping results coming from SqlQuery into actual results.

This looks very similar to RawSql, and it is! However, there are some crucial differences and ultimately they're different classes.

Methods

sqlSelectCols :: IdentInfo -> a -> (Builder, [PersistValue]) Source #

Creates the variable part of the SELECT query and returns the list of PersistValues that will be given to rawQuery.

sqlSelectColCount :: Proxy a -> Int Source #

Number of columns that will be consumed.

sqlSelectProcessRow :: [PersistValue] -> Either Text r Source #

Transform a row of the result into the data type.

sqlInsertInto :: IdentInfo -> a -> (Builder, [PersistValue]) Source #

Create INSERT INTO clause instead.

Instances
SqlSelect () () Source #

Not useful for select, but used for update and delete.

Instance details

Defined in Database.Esqueleto.Internal.Internal

SqlSelect (SqlExpr InsertFinal) InsertFinal Source #

INSERT INTO hack.

Instance details

Defined in Database.Esqueleto.Internal.Internal

PersistEntity a => SqlSelect (SqlExpr (Maybe (Entity a))) (Maybe (Entity a)) Source #

You may return a possibly-NULL Entity from a select query.

Instance details

Defined in Database.Esqueleto.Internal.Internal

PersistEntity a => SqlSelect (SqlExpr (Entity a)) (Entity a) Source #

You may return an Entity from a select query.

Instance details

Defined in Database.Esqueleto.Internal.Internal

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

(SqlSelect a ra, SqlSelect b rb) => SqlSelect (a, b) (ra, rb) Source #

You may return tuples (up to 16-tuples) and tuples of tuples from a select query.

Instance details

Defined in Database.Esqueleto.Internal.Internal

(SqlSelect a ra, SqlSelect b rb, SqlSelect c rc) => SqlSelect (a, b, c) (ra, rb, rc) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

(SqlSelect a ra, SqlSelect b rb, SqlSelect c rc, SqlSelect d rd) => SqlSelect (a, b, c, d) (ra, rb, rc, rd) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

sqlSelectCols :: IdentInfo -> (a, b, c, d) -> (Builder, [PersistValue]) Source #

sqlSelectColCount :: Proxy (a, b, c, d) -> Int Source #

sqlSelectProcessRow :: [PersistValue] -> Either Text (ra, rb, rc, rd) Source #

sqlInsertInto :: IdentInfo -> (a, b, c, d) -> (Builder, [PersistValue]) Source #

(SqlSelect a ra, SqlSelect b rb, SqlSelect c rc, SqlSelect d rd, SqlSelect e re) => SqlSelect (a, b, c, d, e) (ra, rb, rc, rd, re) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

sqlSelectCols :: IdentInfo -> (a, b, c, d, e) -> (Builder, [PersistValue]) Source #

sqlSelectColCount :: Proxy (a, b, c, d, e) -> Int Source #

sqlSelectProcessRow :: [PersistValue] -> Either Text (ra, rb, rc, rd, re) Source #

sqlInsertInto :: IdentInfo -> (a, b, c, d, e) -> (Builder, [PersistValue]) Source #

(SqlSelect a ra, SqlSelect b rb, SqlSelect c rc, SqlSelect d rd, SqlSelect e re, SqlSelect f rf) => SqlSelect (a, b, c, d, e, f) (ra, rb, rc, rd, re, rf) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

sqlSelectCols :: IdentInfo -> (a, b, c, d, e, f) -> (Builder, [PersistValue]) Source #

sqlSelectColCount :: Proxy (a, b, c, d, e, f) -> Int Source #

sqlSelectProcessRow :: [PersistValue] -> Either Text (ra, rb, rc, rd, re, rf) Source #

sqlInsertInto :: IdentInfo -> (a, b, c, d, e, f) -> (Builder, [PersistValue]) Source #

(SqlSelect a ra, SqlSelect b rb, SqlSelect c rc, SqlSelect d rd, SqlSelect e re, SqlSelect f rf, SqlSelect g rg) => SqlSelect (a, b, c, d, e, f, g) (ra, rb, rc, rd, re, rf, rg) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

sqlSelectCols :: IdentInfo -> (a, b, c, d, e, f, g) -> (Builder, [PersistValue]) Source #

sqlSelectColCount :: Proxy (a, b, c, d, e, f, g) -> Int Source #

sqlSelectProcessRow :: [PersistValue] -> Either Text (ra, rb, rc, rd, re, rf, rg) Source #

sqlInsertInto :: IdentInfo -> (a, b, c, d, e, f, g) -> (Builder, [PersistValue]) Source #

(SqlSelect a ra, SqlSelect b rb, SqlSelect c rc, SqlSelect d rd, SqlSelect e re, SqlSelect f rf, SqlSelect g rg, SqlSelect h rh) => SqlSelect (a, b, c, d, e, f, g, h) (ra, rb, rc, rd, re, rf, rg, rh) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

sqlSelectCols :: IdentInfo -> (a, b, c, d, e, f, g, h) -> (Builder, [PersistValue]) Source #

sqlSelectColCount :: Proxy (a, b, c, d, e, f, g, h) -> Int Source #

sqlSelectProcessRow :: [PersistValue] -> Either Text (ra, rb, rc, rd, re, rf, rg, rh) Source #

sqlInsertInto :: IdentInfo -> (a, b, c, d, e, f, g, h) -> (Builder, [PersistValue]) Source #

(SqlSelect a ra, SqlSelect b rb, SqlSelect c rc, SqlSelect d rd, SqlSelect e re, SqlSelect f rf, SqlSelect g rg, SqlSelect h rh, SqlSelect i ri) => SqlSelect (a, b, c, d, e, f, g, h, i) (ra, rb, rc, rd, re, rf, rg, rh, ri) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

sqlSelectCols :: IdentInfo -> (a, b, c, d, e, f, g, h, i) -> (Builder, [PersistValue]) Source #

sqlSelectColCount :: Proxy (a, b, c, d, e, f, g, h, i) -> Int Source #

sqlSelectProcessRow :: [PersistValue] -> Either Text (ra, rb, rc, rd, re, rf, rg, rh, ri) Source #

sqlInsertInto :: IdentInfo -> (a, b, c, d, e, f, g, h, i) -> (Builder, [PersistValue]) Source #

(SqlSelect a ra, SqlSelect b rb, SqlSelect c rc, SqlSelect d rd, SqlSelect e re, SqlSelect f rf, SqlSelect g rg, SqlSelect h rh, SqlSelect i ri, SqlSelect j rj) => SqlSelect (a, b, c, d, e, f, g, h, i, j) (ra, rb, rc, rd, re, rf, rg, rh, ri, rj) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

sqlSelectCols :: IdentInfo -> (a, b, c, d, e, f, g, h, i, j) -> (Builder, [PersistValue]) Source #

sqlSelectColCount :: Proxy (a, b, c, d, e, f, g, h, i, j) -> Int Source #

sqlSelectProcessRow :: [PersistValue] -> Either Text (ra, rb, rc, rd, re, rf, rg, rh, ri, rj) Source #

sqlInsertInto :: IdentInfo -> (a, b, c, d, e, f, g, h, i, j) -> (Builder, [PersistValue]) Source #

(SqlSelect a ra, SqlSelect b rb, SqlSelect c rc, SqlSelect d rd, SqlSelect e re, SqlSelect f rf, SqlSelect g rg, SqlSelect h rh, SqlSelect i ri, SqlSelect j rj, SqlSelect k rk) => SqlSelect (a, b, c, d, e, f, g, h, i, j, k) (ra, rb, rc, rd, re, rf, rg, rh, ri, rj, rk) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

sqlSelectCols :: IdentInfo -> (a, b, c, d, e, f, g, h, i, j, k) -> (Builder, [PersistValue]) Source #

sqlSelectColCount :: Proxy (a, b, c, d, e, f, g, h, i, j, k) -> Int Source #

sqlSelectProcessRow :: [PersistValue] -> Either Text (ra, rb, rc, rd, re, rf, rg, rh, ri, rj, rk) Source #

sqlInsertInto :: IdentInfo -> (a, b, c, d, e, f, g, h, i, j, k) -> (Builder, [PersistValue]) Source #

(SqlSelect a ra, SqlSelect b rb, SqlSelect c rc, SqlSelect d rd, SqlSelect e re, SqlSelect f rf, SqlSelect g rg, SqlSelect h rh, SqlSelect i ri, SqlSelect j rj, SqlSelect k rk, SqlSelect l rl) => SqlSelect (a, b, c, d, e, f, g, h, i, j, k, l) (ra, rb, rc, rd, re, rf, rg, rh, ri, rj, rk, rl) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

sqlSelectCols :: IdentInfo -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (Builder, [PersistValue]) Source #

sqlSelectColCount :: Proxy (a, b, c, d, e, f, g, h, i, j, k, l) -> Int Source #

sqlSelectProcessRow :: [PersistValue] -> Either Text (ra, rb, rc, rd, re, rf, rg, rh, ri, rj, rk, rl) Source #

sqlInsertInto :: IdentInfo -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (Builder, [PersistValue]) Source #

(SqlSelect a ra, SqlSelect b rb, SqlSelect c rc, SqlSelect d rd, SqlSelect e re, SqlSelect f rf, SqlSelect g rg, SqlSelect h rh, SqlSelect i ri, SqlSelect j rj, SqlSelect k rk, SqlSelect l rl, SqlSelect m rm) => SqlSelect (a, b, c, d, e, f, g, h, i, j, k, l, m) (ra, rb, rc, rd, re, rf, rg, rh, ri, rj, rk, rl, rm) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

sqlSelectCols :: IdentInfo -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (Builder, [PersistValue]) Source #

sqlSelectColCount :: Proxy (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Int Source #

sqlSelectProcessRow :: [PersistValue] -> Either Text (ra, rb, rc, rd, re, rf, rg, rh, ri, rj, rk, rl, rm) Source #

sqlInsertInto :: IdentInfo -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (Builder, [PersistValue]) Source #

(SqlSelect a ra, SqlSelect b rb, SqlSelect c rc, SqlSelect d rd, SqlSelect e re, SqlSelect f rf, SqlSelect g rg, SqlSelect h rh, SqlSelect i ri, SqlSelect j rj, SqlSelect k rk, SqlSelect l rl, SqlSelect m rm, SqlSelect n rn) => SqlSelect (a, b, c, d, e, f, g, h, i, j, k, l, m, n) (ra, rb, rc, rd, re, rf, rg, rh, ri, rj, rk, rl, rm, rn) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

sqlSelectCols :: IdentInfo -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (Builder, [PersistValue]) Source #

sqlSelectColCount :: Proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Int Source #

sqlSelectProcessRow :: [PersistValue] -> Either Text (ra, rb, rc, rd, re, rf, rg, rh, ri, rj, rk, rl, rm, rn) Source #

sqlInsertInto :: IdentInfo -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (Builder, [PersistValue]) Source #

(SqlSelect a ra, SqlSelect b rb, SqlSelect c rc, SqlSelect d rd, SqlSelect e re, SqlSelect f rf, SqlSelect g rg, SqlSelect h rh, SqlSelect i ri, SqlSelect j rj, SqlSelect k rk, SqlSelect l rl, SqlSelect m rm, SqlSelect n rn, SqlSelect o ro) => SqlSelect (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) (ra, rb, rc, rd, re, rf, rg, rh, ri, rj, rk, rl, rm, rn, ro) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

sqlSelectCols :: IdentInfo -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (Builder, [PersistValue]) Source #

sqlSelectColCount :: Proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Int Source #

sqlSelectProcessRow :: [PersistValue] -> Either Text (ra, rb, rc, rd, re, rf, rg, rh, ri, rj, rk, rl, rm, rn, ro) Source #

sqlInsertInto :: IdentInfo -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (Builder, [PersistValue]) Source #

(SqlSelect a ra, SqlSelect b rb, SqlSelect c rc, SqlSelect d rd, SqlSelect e re, SqlSelect f rf, SqlSelect g rg, SqlSelect h rh, SqlSelect i ri, SqlSelect j rj, SqlSelect k rk, SqlSelect l rl, SqlSelect m rm, SqlSelect n rn, SqlSelect o ro, SqlSelect p rp) => SqlSelect (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) (ra, rb, rc, rd, re, rf, rg, rh, ri, rj, rk, rl, rm, rn, ro, rp) Source # 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

sqlSelectCols :: IdentInfo -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> (Builder, [PersistValue]) Source #

sqlSelectColCount :: Proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> Int Source #

sqlSelectProcessRow :: [PersistValue] -> Either Text (ra, rb, rc, rd, re, rf, rg, rh, ri, rj, rk, rl, rm, rn, ro, rp) Source #

sqlInsertInto :: IdentInfo -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> (Builder, [PersistValue]) Source #

materializeExpr :: IdentInfo -> SqlExpr (Value a) -> (Builder, [PersistValue]) Source #

Materialize a SqlExpr (Value a).

from3P :: Proxy (a, b, c) -> Proxy ((a, b), c) Source #

from3 :: (a, b, c) -> ((a, b), c) Source #

to3 :: ((a, b), c) -> (a, b, c) Source #

from4P :: Proxy (a, b, c, d) -> Proxy ((a, b), (c, d)) Source #

from4 :: (a, b, c, d) -> ((a, b), (c, d)) Source #

to4 :: ((a, b), (c, d)) -> (a, b, c, d) Source #

from5P :: Proxy (a, b, c, d, e) -> Proxy ((a, b), (c, d), e) Source #

from5 :: (a, b, c, d, e) -> ((a, b), (c, d), e) Source #

to5 :: ((a, b), (c, d), e) -> (a, b, c, d, e) Source #

from6P :: Proxy (a, b, c, d, e, f) -> Proxy ((a, b), (c, d), (e, f)) Source #

from6 :: (a, b, c, d, e, f) -> ((a, b), (c, d), (e, f)) Source #

to6 :: ((a, b), (c, d), (e, f)) -> (a, b, c, d, e, f) Source #

from7P :: Proxy (a, b, c, d, e, f, g) -> Proxy ((a, b), (c, d), (e, f), g) Source #

from7 :: (a, b, c, d, e, f, g) -> ((a, b), (c, d), (e, f), g) Source #

to7 :: ((a, b), (c, d), (e, f), g) -> (a, b, c, d, e, f, g) Source #

from8P :: Proxy (a, b, c, d, e, f, g, h) -> Proxy ((a, b), (c, d), (e, f), (g, h)) Source #

from8 :: (a, b, c, d, e, f, g, h) -> ((a, b), (c, d), (e, f), (g, h)) Source #

to8 :: ((a, b), (c, d), (e, f), (g, h)) -> (a, b, c, d, e, f, g, h) Source #

from9P :: Proxy (a, b, c, d, e, f, g, h, i) -> Proxy ((a, b), (c, d), (e, f), (g, h), i) Source #

from9 :: (a, b, c, d, e, f, g, h, i) -> ((a, b), (c, d), (e, f), (g, h), i) Source #

to9 :: ((a, b), (c, d), (e, f), (g, h), i) -> (a, b, c, d, e, f, g, h, i) Source #

from10P :: Proxy (a, b, c, d, e, f, g, h, i, j) -> Proxy ((a, b), (c, d), (e, f), (g, h), (i, j)) Source #

from10 :: (a, b, c, d, e, f, g, h, i, j) -> ((a, b), (c, d), (e, f), (g, h), (i, j)) Source #

to10 :: ((a, b), (c, d), (e, f), (g, h), (i, j)) -> (a, b, c, d, e, f, g, h, i, j) Source #

from11P :: Proxy (a, b, c, d, e, f, g, h, i, j, k) -> Proxy ((a, b), (c, d), (e, f), (g, h), (i, j), k) Source #

to11 :: ((a, b), (c, d), (e, f), (g, h), (i, j), k) -> (a, b, c, d, e, f, g, h, i, j, k) Source #

from12P :: Proxy (a, b, c, d, e, f, g, h, i, j, k, l) -> Proxy ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l)) Source #

to12 :: ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l)) -> (a, b, c, d, e, f, g, h, i, j, k, l) Source #

from13P :: Proxy (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Proxy ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), m) Source #

to13 :: ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

from14P :: Proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Proxy ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n)) Source #

to14 :: ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n)) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

from15P :: Proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Proxy ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n), o) Source #

to15 :: ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n), o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

from16P :: Proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> Proxy ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n), (o, p)) Source #

to16 :: ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n), (o, p)) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source #

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

renderExpr :: SqlBackend -> SqlExpr (Value Bool) -> Text Source #

Renders an expression into Text. Only useful for creating a textual representation of the clauses passed to an On clause.

Since: 3.2.0

data RenderExprException Source #

An exception thrown by RenderExpr - it's not designed to handle composite keys, and will blow up if you give it one.

Since: 3.2.0