Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- from :: From a => (a -> SqlQuery b) -> SqlQuery b
- newtype Value a = Value {
- unValue :: a
- newtype ValueList a = ValueList a
- data SomeValue where
- class ToSomeValues a where
- toSomeValues :: a -> [SomeValue]
- data InnerJoin a b = a `InnerJoin` b
- data CrossJoin a b = a `CrossJoin` b
- data LeftOuterJoin a b = a `LeftOuterJoin` b
- data RightOuterJoin a b = a `RightOuterJoin` b
- data FullOuterJoin a b = a `FullOuterJoin` b
- data OnClauseWithoutMatchingJoinException = OnClauseWithoutMatchingJoinException String
- data OrderBy
- data DistinctOn
- data Update typ
- data Insertion a
- data LockingKind
- class PersistField a => SqlString a
- class ToBaseId ent where
- type BaseEnt ent :: *
- toBaseIdWitness :: Key (BaseEnt ent) -> Key ent
- data JoinKind
- class IsJoinKind join where
- smartJoin :: a -> b -> join a b
- reifyJoinKind :: join a b -> JoinKind
- class BackendCompatible sup sub where
- projectBackend :: sub -> sup
- data PreprocessedFrom a
- class From a
- class FromPreprocess a
- when_ :: expr (Value Bool) -> () -> expr a -> (expr (Value Bool), expr a)
- then_ :: ()
- else_ :: expr a -> expr a
- where_ :: SqlExpr (Value Bool) -> SqlQuery ()
- on :: SqlExpr (Value Bool) -> SqlQuery ()
- groupBy :: ToSomeValues a => a -> SqlQuery ()
- orderBy :: [SqlExpr OrderBy] -> SqlQuery ()
- rand :: SqlExpr OrderBy
- asc :: PersistField a => SqlExpr (Value a) -> SqlExpr OrderBy
- desc :: PersistField a => SqlExpr (Value a) -> SqlExpr OrderBy
- limit :: Int64 -> SqlQuery ()
- offset :: Int64 -> SqlQuery ()
- distinct :: SqlQuery a -> SqlQuery a
- distinctOn :: [SqlExpr DistinctOn] -> SqlQuery a -> SqlQuery a
- don :: SqlExpr (Value a) -> SqlExpr DistinctOn
- distinctOnOrderBy :: [SqlExpr OrderBy] -> SqlQuery a -> SqlQuery a
- having :: SqlExpr (Value Bool) -> SqlQuery ()
- locking :: LockingKind -> SqlQuery ()
- sub_select :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (Value a)
- (^.) :: forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
- (?.) :: (PersistEntity val, PersistField typ) => SqlExpr (Maybe (Entity val)) -> EntityField val typ -> SqlExpr (Value (Maybe typ))
- val :: PersistField typ => typ -> SqlExpr (Value typ)
- isNothing :: PersistField typ => SqlExpr (Value (Maybe typ)) -> SqlExpr (Value Bool)
- just :: SqlExpr (Value typ) -> SqlExpr (Value (Maybe typ))
- nothing :: SqlExpr (Value (Maybe typ))
- joinV :: SqlExpr (Value (Maybe (Maybe typ))) -> SqlExpr (Value (Maybe typ))
- withNonNull :: PersistField typ => SqlExpr (Value (Maybe typ)) -> (SqlExpr (Value typ) -> SqlQuery a) -> SqlQuery a
- countRows :: Num a => SqlExpr (Value a)
- count :: Num a => SqlExpr (Value typ) -> SqlExpr (Value a)
- countDistinct :: Num a => SqlExpr (Value typ) -> SqlExpr (Value a)
- not_ :: SqlExpr (Value Bool) -> SqlExpr (Value Bool)
- (==.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
- (>=.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
- (>.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
- (<=.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
- (<.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
- (!=.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
- (&&.) :: SqlExpr (Value Bool) -> SqlExpr (Value Bool) -> SqlExpr (Value Bool)
- (||.) :: SqlExpr (Value Bool) -> SqlExpr (Value Bool) -> SqlExpr (Value Bool)
- (+.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a)
- (-.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a)
- (/.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a)
- (*.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a)
- random_ :: (PersistField a, Num a) => SqlExpr (Value a)
- round_ :: (PersistField a, Num a, PersistField b, Num b) => SqlExpr (Value a) -> SqlExpr (Value b)
- ceiling_ :: (PersistField a, Num a, PersistField b, Num b) => SqlExpr (Value a) -> SqlExpr (Value b)
- floor_ :: (PersistField a, Num a, PersistField b, Num b) => SqlExpr (Value a) -> SqlExpr (Value b)
- min_ :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value (Maybe a))
- max_ :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value (Maybe a))
- sum_ :: (PersistField a, PersistField b) => SqlExpr (Value a) -> SqlExpr (Value (Maybe b))
- avg_ :: (PersistField a, PersistField b) => SqlExpr (Value a) -> SqlExpr (Value (Maybe b))
- castNum :: (Num a, Num b) => SqlExpr (Value a) -> SqlExpr (Value b)
- castNumM :: (Num a, Num b) => SqlExpr (Value (Maybe a)) -> SqlExpr (Value (Maybe b))
- coalesce :: PersistField a => [SqlExpr (Value (Maybe a))] -> SqlExpr (Value (Maybe a))
- coalesceDefault :: PersistField a => [SqlExpr (Value (Maybe a))] -> SqlExpr (Value a) -> SqlExpr (Value a)
- lower_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s)
- like :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) -> SqlExpr (Value Bool)
- ilike :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) -> SqlExpr (Value Bool)
- (%) :: SqlString s => SqlExpr (Value s)
- concat_ :: SqlString s => [SqlExpr (Value s)] -> SqlExpr (Value s)
- (++.) :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) -> SqlExpr (Value s)
- castString :: (SqlString s, SqlString r) => SqlExpr (Value s) -> SqlExpr (Value r)
- subList_select :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (ValueList a)
- valList :: PersistField typ => [typ] -> SqlExpr (ValueList typ)
- justList :: SqlExpr (ValueList typ) -> SqlExpr (ValueList (Maybe typ))
- in_ :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool)
- notIn :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool)
- exists :: SqlQuery () -> SqlExpr (Value Bool)
- notExists :: SqlQuery () -> SqlExpr (Value Bool)
- set :: PersistEntity val => SqlExpr (Entity val) -> [SqlExpr (Update val)] -> SqlQuery ()
- (=.) :: (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Update val)
- (+=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Update val)
- (-=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Update val)
- (*=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Update val)
- (/=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Update val)
- case_ :: PersistField a => [(SqlExpr (Value Bool), SqlExpr (Value a))] -> SqlExpr (Value a) -> SqlExpr (Value a)
- toBaseId :: ToBaseId ent => SqlExpr (Value (Key ent)) -> SqlExpr (Value (Key (BaseEnt ent)))
- (<#) :: (a -> b) -> SqlExpr (Value a) -> SqlExpr (Insertion b)
- (<&>) :: SqlExpr (Insertion (a -> b)) -> SqlExpr (Value a) -> SqlExpr (Insertion b)
The pretty face
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 beNULL
into scope. Used forOUTER JOIN
s.- A
JOIN
of any other two types allowed by the innermost magic, where aJOIN
may be anInnerJoin
, aCrossJoin
, aLeftOuterJoin
, aRightOuterJoin
, or aFullOuterJoin
. TheJOINs
have left fixity.
The outermost magic allows you to use from
on any tuples of
types supported by innermost magic (and also tuples of tuples,
and so on), up to 8-tuples.
Note that using from
for the same entity twice does work and
corresponds to a self-join. You don't even need to use two
different calls to from
, you may use a JOIN
or a tuple.
The following are valid examples of uses of from
(the types
of the arguments of the lambda are inside square brackets):
from
$ \person -> ...from
$ \(person, blogPost) -> ...from
$ \(p `LeftOuterJoin
` mb) -> ...from
$ \(p1 `InnerJoin
` f `InnerJoin
` p2) -> ...from
$ \((p1 `InnerJoin
` f) `InnerJoin
` p2) -> ...
The types of the arguments to the lambdas above are, respectively:
person :: ( Esqueleto query expr backend , PersistEntity Person , PersistEntityBackend Person ~ backend ) => expr (Entity Person) (person, blogPost) :: (...) => (expr (Entity Person), expr (Entity BlogPost)) (p `LeftOuterJoin
` mb) :: (...) => InnerJoin (expr (Entity Person)) (expr (Maybe (Entity BlogPost))) (p1 `InnerJoin
` f `InnerJoin
` p2) :: (...) => InnerJoin (InnerJoin (expr (Entity Person)) (expr (Entity Follow))) (expr (Entity Person)) (p1 `InnerJoin
` (f `InnerJoin
` p2)) :: :: (...) => InnerJoin (expr (Entity Person)) (InnerJoin (expr (Entity Follow)) (expr (Entity Person)))
Note that some backends may not support all kinds of JOIN
s.
A single value (as opposed to a whole entity). You may use
(
or ^.
)(
to get a ?.
)Value
from an Entity
.
Instances
Monad Value Source # | |
Functor Value Source # | Since: 1.4.4 |
Applicative Value Source # | |
Eq a => Eq (Value a) Source # | |
Ord a => Ord (Value a) Source # | |
Defined in Database.Esqueleto.Internal.Internal | |
Show a => Show (Value a) Source # | |
ToSomeValues (SqlExpr (Value a)) Source # | |
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 |
Defined in Database.Esqueleto.Internal.Internal sqlSelectCols :: IdentInfo -> SqlExpr (Value a) -> (Builder, [PersistValue]) Source # sqlSelectColCount :: Proxy (SqlExpr (Value a)) -> Int Source # sqlSelectProcessRow :: [PersistValue] -> Either Text (Value a) Source # sqlInsertInto :: IdentInfo -> SqlExpr (Value a) -> (Builder, [PersistValue]) 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
).
Instances
Eq a => Eq (ValueList a) Source # | |
Ord a => Ord (ValueList a) Source # | |
Defined in Database.Esqueleto.Internal.Internal | |
Show a => Show (ValueList a) Source # | |
A wrapper type for for any expr (Value a)
for all a.
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)
toSomeValues :: a -> [SomeValue] Source #
Instances
data InnerJoin a b infixl 2 Source #
Data type that represents an INNER JOIN
(see LeftOuterJoin
for an example).
a `InnerJoin` b infixl 2 |
Instances
IsJoinKind InnerJoin Source # | |
Defined in Database.Esqueleto.Internal.Internal | |
FromPreprocess (InnerJoin a b) => From (InnerJoin a b) Source # | |
Defined in Database.Esqueleto.Internal.Internal |
data CrossJoin a b infixl 2 Source #
Data type that represents a CROSS JOIN
(see LeftOuterJoin
for an example).
a `CrossJoin` b infixl 2 |
Instances
IsJoinKind CrossJoin Source # | |
Defined in Database.Esqueleto.Internal.Internal | |
FromPreprocess (CrossJoin a b) => From (CrossJoin a b) Source # | |
Defined in Database.Esqueleto.Internal.Internal |
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
.
a `LeftOuterJoin` b infixl 2 |
Instances
IsJoinKind LeftOuterJoin Source # | |
Defined in Database.Esqueleto.Internal.Internal smartJoin :: a -> b -> LeftOuterJoin a b Source # reifyJoinKind :: LeftOuterJoin a b -> JoinKind Source # | |
FromPreprocess (LeftOuterJoin a b) => From (LeftOuterJoin a b) Source # | |
Defined in Database.Esqueleto.Internal.Internal from_ :: SqlQuery (LeftOuterJoin a b) |
data RightOuterJoin a b infixl 2 Source #
Data type that represents a RIGHT OUTER JOIN
(see LeftOuterJoin
for an example).
a `RightOuterJoin` b infixl 2 |
Instances
IsJoinKind RightOuterJoin Source # | |
Defined in Database.Esqueleto.Internal.Internal smartJoin :: a -> b -> RightOuterJoin a b Source # reifyJoinKind :: RightOuterJoin a b -> JoinKind Source # | |
FromPreprocess (RightOuterJoin a b) => From (RightOuterJoin a b) Source # | |
Defined in Database.Esqueleto.Internal.Internal from_ :: SqlQuery (RightOuterJoin a b) |
data FullOuterJoin a b infixl 2 Source #
Data type that represents a FULL OUTER JOIN
(see LeftOuterJoin
for an example).
a `FullOuterJoin` b infixl 2 |
Instances
IsJoinKind FullOuterJoin Source # | |
Defined in Database.Esqueleto.Internal.Internal smartJoin :: a -> b -> FullOuterJoin a b Source # reifyJoinKind :: FullOuterJoin a b -> JoinKind Source # | |
FromPreprocess (FullOuterJoin a b) => From (FullOuterJoin a b) Source # | |
Defined in Database.Esqueleto.Internal.Internal from_ :: SqlQuery (FullOuterJoin a b) |
data OnClauseWithoutMatchingJoinException Source #
Exception thrown whenever on
is used to create an ON
clause but no matching JOIN
is found.
Instances
data DistinctOn Source #
Phantom type used by distinctOn
and don
.
Phantom type for a SET
operation on an entity of the given
type (see set
and '(=.)').
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
ForUpdate |
Since: 2.2.7 |
ForUpdateSkipLocked |
Since: 2.2.7 |
ForShare |
Since: 2.2.7 |
LockInShareMode |
Since: 2.2.7 |
class PersistField a => SqlString a Source #
Phantom class of data types that are treated as strings by the RDBMS. It has no methods because it's only used to avoid type errors such as trying to concatenate integers.
If you have a custom data type or newtype
, feel free to make
it an instance of this class.
Since: 2.4.0
Instances
SqlString ByteString Source # | Since: 2.3.0 |
Defined in Database.Esqueleto.Internal.Internal | |
SqlString Text Source # | Since: 2.3.0 |
Defined in Database.Esqueleto.Internal.Internal | |
SqlString Text Source # | Since: 2.3.0 |
Defined in Database.Esqueleto.Internal.Internal | |
SqlString Html Source # | Since: 2.3.0 |
Defined in Database.Esqueleto.Internal.Internal | |
a ~ Char => SqlString [a] Source # | Since: 2.3.0 |
Defined in Database.Esqueleto.Internal.Internal | |
SqlString a => SqlString (Maybe a) Source # | Since: 2.4.0 |
Defined in Database.Esqueleto.Internal.Internal |
The guts
(Internal) A kind of JOIN
.
InnerJoinKind | INNER JOIN |
CrossJoinKind | CROSS JOIN |
LeftOuterJoinKind | LEFT OUTER JOIN |
RightOuterJoinKind | RIGHT OUTER JOIN |
FullOuterJoinKind | FULL OUTER JOIN |
class IsJoinKind join where Source #
(Internal) Functions that operate on types (that should be)
of kind JoinKind
.
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.
Instances
IsJoinKind FullOuterJoin Source # | |
Defined in Database.Esqueleto.Internal.Internal smartJoin :: a -> b -> FullOuterJoin a b Source # reifyJoinKind :: FullOuterJoin a b -> JoinKind Source # | |
IsJoinKind RightOuterJoin Source # | |
Defined in Database.Esqueleto.Internal.Internal smartJoin :: a -> b -> RightOuterJoin a b Source # reifyJoinKind :: RightOuterJoin a b -> JoinKind Source # | |
IsJoinKind LeftOuterJoin Source # | |
Defined in Database.Esqueleto.Internal.Internal smartJoin :: a -> b -> LeftOuterJoin a b Source # reifyJoinKind :: LeftOuterJoin a b -> JoinKind Source # | |
IsJoinKind CrossJoin Source # | |
Defined in Database.Esqueleto.Internal.Internal | |
IsJoinKind InnerJoin Source # | |
Defined in Database.Esqueleto.Internal.Internal |
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
, without needing to go through the BackendCompatible
SqlBackend
SqlReadBackend
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' = withReaderTprojectBackend
asdf
Since: persistent-2.7.1
projectBackend :: sub -> sup #
data PreprocessedFrom a Source #
(Internal) Phantom type used to process from
(see fromStart
).
(Internal) Class that implements the tuple from
magic (see
fromStart
).
from_
Instances
class FromPreprocess a Source #
(Internal) Class that implements the JOIN
from
magic
(see fromStart
).
fromPreprocess
Instances
(PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => FromPreprocess (SqlExpr (Maybe (Entity val))) Source # | |
Defined in Database.Esqueleto.Internal.Internal fromPreprocess :: SqlQuery (SqlExpr (PreprocessedFrom (SqlExpr (Maybe (Entity val))))) | |
(PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => FromPreprocess (SqlExpr (Entity val)) Source # | |
Defined in Database.Esqueleto.Internal.Internal fromPreprocess :: SqlQuery (SqlExpr (PreprocessedFrom (SqlExpr (Entity val)))) | |
(FromPreprocess a, FromPreprocess b, IsJoinKind join) => FromPreprocess (join a b) Source # | |
Defined in Database.Esqueleto.Internal.Internal fromPreprocess :: SqlQuery (SqlExpr (PreprocessedFrom (join a b))) |
when_ :: expr (Value Bool) -> () -> expr a -> (expr (Value Bool), expr a) Source #
Syntax sugar for case_
.
Since: 2.1.2
on :: SqlExpr (Value Bool) -> SqlQuery () Source #
ON
clause: restrict the a JOIN
's result. The ON
clause will be applied to the last JOIN
that does not
have an ON
clause yet. If there are no JOIN
s without
ON
clauses (either because you didn't do any JOIN
, or
because all JOIN
s already have their own ON
clauses), a
runtime exception OnClauseWithoutMatchingJoinException
is
thrown. ON
clauses are optional when doing JOIN
s.
On the simple case of doing just one JOIN
, for example
select $from
$ \(foo `InnerJoin
` bar) -> doon
(foo^.
FooId==.
bar^.
BarFooId) ...
there's no ambiguity and the rules above just mean that
you're allowed to call on
only once (as in SQL). If you
have many joins, then the on
s are applied on the reverse
order that the JOIN
s appear. For example:
select $from
$ \(foo `InnerJoin
` bar `InnerJoin
` baz) -> doon
(baz^.
BazId==.
bar^.
BarBazId)on
(foo^.
FooId==.
bar^.
BarFooId) ...
The order is reversed in order to improve composability.
For example, consider query1
and query2
below:
let query1 =from
$ \(foo `InnerJoin
` bar) -> doon
(foo^.
FooId==.
bar^.
BarFooId) query2 =from
$ \(mbaz `LeftOuterJoin
` quux) -> do return (mbaz?.
BazName, quux) test1 = (,) <$> query1 <*> query2 test2 = flip (,) <$> query2 <*> query1
If the order was not reversed, then test2
would be
broken: query1
's on
would refer to query2
's
LeftOuterJoin
.
groupBy :: ToSomeValues a => a -> SqlQuery () Source #
GROUP BY
clause. You can enclose multiple columns
in a tuple.
select $from
\(foo `InnerJoin
` bar) -> doon
(foo^.
FooBarId==.
bar^.
BarId)groupBy
(bar^.
BarId, bar^.
BarName) return (bar^.
BarId, bar^.
BarName, countRows)
With groupBy you can sort by aggregate functions, like so
(we used let
to restrict the more general countRows
to
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) -> doon
(foo^.
FooBarId==.
bar^.
BarId)groupBy
$ bar^.
BarName let countRows' =countRows
orderBy
[asc
countRows'] return (bar^.
BarName, countRows') forM_ r $ \(Value
name,Value
count) -> do print name print (count :: Int)
orderBy :: [SqlExpr OrderBy] -> SqlQuery () Source #
ORDER BY
clause. See also asc
and desc
.
Multiple calls to orderBy
get concatenated on the final
query, including distinctOnOrderBy
.
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
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.
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] $ doorderBy
[asc foo, desc bar, desc quux] ...
Since: 2.2.4
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 #
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.
(^.) :: 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.
(?.) :: (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.
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.
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 #
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 #
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 #
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
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
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 #
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 newtype
s, or if you want
to apply functions such as like
to strings of different
types.
Safety: This is a slightly unsafe function, especially if
you have defined your own instances of SqlString
. Also,
since Maybe
is an instance of SqlString
, it's possible
to turn a nullable value into a non-nullable one. Avoid
using this function if possible.
subList_select :: PersistField a => 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.
in_ :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool) Source #
IN
operator. For example if you want to select all Person
s by a list
of IDs:
SELECT * FROM Person WHERE Person.id IN (?)
In esqueleto
, we may write the same query above as:
select $from
$ \person -> dowhere_
$ person^.
PersonId `in_
`valList
personIds return person
Where personIds
is of type [Key Person]
.
notIn :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool) Source #
NOT IN
operator.
set :: PersistEntity val => SqlExpr (Entity val) -> [SqlExpr (Update val)] -> SqlQuery () Source #
SET
clause used on UPDATE
s. Note that while it's not
a type error to use this function on a SELECT
, it will
most certainly result in a runtime error.
(=.) :: (PersistEntity val, PersistField typ) => EntityField val typ -> 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 #
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 -> dowhere_
(p^.
PersonName==.
val
"Mike"))then_
(sub_select
$from
$ \v -> do let sub =from
$ \c -> dowhere_
(c^.
PersonName==.
val
"Mike") return (c^.
PersonFavNum)where_
(v^.
PersonFavNum >.sub_select
sub) return $count
(v^.
PersonName) +.val
(1 :: Int)) ] (else_
$val
(-1))
This query is a bit complicated, but basically it checks if a person
named "Mike"
exists, and if that person does, run the subquery to find
out how many people have a ranking (by Fav Num) higher than "Mike"
.
NOTE: There are a few things to be aware about this statement.
- This only implements the full CASE statement, it does not implement the "simple" CASE statement.
- At least one
when_
andthen_
is mandatory otherwise it will emit an error. - The
else_
is also mandatory, unlike the SQL statement in which if theELSE
is omitted it will return aNULL
. You can reproduce this vianothing
.
Since: 2.1.2
toBaseId :: ToBaseId ent => 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 Id BarId fooNum Int
For this example, declare:
instance ToBaseId Foo where type BaseEnt Foo = Bar toBaseIdWitness = FooKey
Now you're able to write queries such as:
select
$from
$ (bar `InnerJoin
` foo) -> doon
(toBaseId
(foo^.
FooId)==.
bar^.
BarId) return (bar, foo)
Note: this function may be unsafe to use in conditions not like the one of the example above.
Since: 2.4.3