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

Safe HaskellNone
LanguageHaskell2010

Database.Esqueleto.Internal.Sql

Contents

Description

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

Synopsis

The pretty face

data SqlQuery a Source #

SQL backend for esqueleto using SqlPersistT.

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 #

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 #

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

Constraint synonym for persistent entities whose backend is SqlPersistT.

select :: (SqlSelect a r, MonadIO m) => SqlQuery a -> SqlReadT m [r] Source #

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

We've seen that from has some magic about which kinds of things you may bring into scope. This select function also has some magic for which kinds of things you may bring back to Haskell-land by using SqlQuery's return:

  • You may return a SqlExpr (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).

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.

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.

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

The guts

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.

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

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

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.

class UnsafeSqlFunctionArgument a 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).

Minimal complete definition

toArgList

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 #

type OrderByClause = SqlExpr OrderBy Source #

A ORDER BY clause.

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.

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.

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

data Mode Source #

(Internal) Mode of query being converted by toRawSql.

Constructors

SELECT 
DELETE 
UPDATE 
INSERT_INTO 

data NeedParens Source #

Constructors

Parens 
Never 

data IdentState Source #

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

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

type IdentInfo = (SqlBackend, IdentState) Source #

Information needed to escape and use identifiers.

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 #

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.

Helper functions

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

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

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

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

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

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 #