| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Database.Esqueleto.Internal.Sql
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
- data SqlQuery a
- data SqlExpr a where- 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
- 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
 
- type SqlEntity ent = (PersistEntity ent, PersistEntityBackend ent ~ SqlBackend)
- select :: (SqlSelect a r, MonadIO m) => SqlQuery a -> SqlReadT m [r]
- selectSource :: (SqlSelect a r, BackendCompatible SqlBackend backend, IsPersistBackend backend, PersistQueryRead backend, PersistStoreRead backend, PersistUniqueRead backend, MonadResource m) => SqlQuery a -> ConduitT () r (ReaderT backend m) ()
- delete :: MonadIO m => SqlQuery () -> SqlWriteT m ()
- deleteCount :: MonadIO m => SqlQuery () -> SqlWriteT m Int64
- update :: (MonadIO m, PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => (SqlExpr (Entity val) -> SqlQuery ()) -> SqlWriteT m ()
- updateCount :: (MonadIO m, PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => (SqlExpr (Entity val) -> SqlQuery ()) -> SqlWriteT m Int64
- insertSelect :: (MonadIO m, PersistEntity a) => SqlQuery (SqlExpr (Insertion a)) -> SqlWriteT m ()
- insertSelectCount :: (MonadIO m, PersistEntity a) => SqlQuery (SqlExpr (Insertion a)) -> SqlWriteT m Int64
- unsafeSqlCase :: PersistField a => [(SqlExpr (Value Bool), SqlExpr (Value a))] -> SqlExpr (Value a) -> SqlExpr (Value a)
- unsafeSqlBinOp :: Builder -> SqlExpr (Value a) -> SqlExpr (Value b) -> SqlExpr (Value c)
- unsafeSqlBinOpComposite :: Builder -> Builder -> SqlExpr (Value a) -> SqlExpr (Value b) -> SqlExpr (Value c)
- unsafeSqlValue :: Builder -> SqlExpr (Value a)
- unsafeSqlCastAs :: Text -> SqlExpr (Value a) -> SqlExpr (Value b)
- unsafeSqlFunction :: UnsafeSqlFunctionArgument a => Builder -> a -> SqlExpr (Value b)
- unsafeSqlExtractSubField :: UnsafeSqlFunctionArgument a => Builder -> a -> SqlExpr (Value b)
- class UnsafeSqlFunctionArgument a
- type OrderByClause = SqlExpr OrderBy
- rawSelectSource :: (SqlSelect a r, MonadIO m1, MonadIO m2) => Mode -> SqlQuery a -> SqlReadT m1 (Acquire (ConduitT () r m2 ()))
- runSource :: Monad m => ConduitT () r (ReaderT backend m) () -> ReaderT backend m [r]
- rawEsqueleto :: (MonadIO m, SqlSelect a r, BackendCompatible SqlBackend backend) => Mode -> SqlQuery a -> ReaderT backend m Int64
- toRawSql :: (SqlSelect a r, BackendCompatible SqlBackend backend) => Mode -> (backend, IdentState) -> SqlQuery a -> (Builder, [PersistValue])
- data Mode- = SELECT
- | DELETE
- | UPDATE
- | INSERT_INTO
 
- data NeedParens
- data IdentState
- renderExpr :: SqlBackend -> SqlExpr (Value Bool) -> Text
- initialIdentState :: IdentState
- type IdentInfo = (SqlBackend, IdentState)
- class SqlSelect a r | a -> r, r -> a where- sqlSelectCols :: IdentInfo -> a -> (Builder, [PersistValue])
- sqlSelectColCount :: Proxy a -> Int
- sqlSelectProcessRow :: [PersistValue] -> Either Text r
- sqlInsertInto :: IdentInfo -> a -> (Builder, [PersistValue])
 
- veryUnsafeCoerceSqlExprValue :: SqlExpr (Value a) -> SqlExpr (Value b)
- veryUnsafeCoerceSqlExprValueList :: SqlExpr (ValueList a) -> SqlExpr (Value a)
- renderQueryToText :: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) => Mode -> SqlQuery a -> ReaderT backend m (Text, [PersistValue])
- renderQuerySelect :: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) => SqlQuery a -> ReaderT backend m (Text, [PersistValue])
- renderQueryUpdate :: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) => SqlQuery a -> ReaderT backend m (Text, [PersistValue])
- renderQueryDelete :: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) => SqlQuery a -> ReaderT backend m (Text, [PersistValue])
- renderQueryInsertInto :: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) => SqlQuery a -> ReaderT backend m (Text, [PersistValue])
- makeOrderByNoNewline :: IdentInfo -> [OrderByClause] -> (Builder, [PersistValue])
- uncommas' :: Monoid a => [(Builder, a)] -> (Builder, a)
- parens :: Builder -> Builder
- toArgList :: UnsafeSqlFunctionArgument a => a -> [SqlExpr (Value ())]
- builderToText :: Builder -> Text
- newtype Ident = I Text
The pretty face
SQL backend for esqueleto using SqlPersistT.
An expression on the SQL backend.
There are many comments describing the constructors of this data type. However, Haddock doesn't like GADTs, so you'll have to read them by hitting "Source".
Constructors
Instances
type SqlEntity ent = (PersistEntity ent, PersistEntityBackend ent ~ SqlBackend) Source #
Constraint synonym for persistent entities whose backend
 is SqlPersistT.
select :: (SqlSelect a r, MonadIO m) => SqlQuery a -> SqlReadT m [r] Source #
Execute an esqueleto SELECT query inside persistent's
 SqlPersistT monad and return a list of rows.
We've seen that from has some magic about which kinds of
 things you may bring into scope.  This select function also
 has some magic for which kinds of things you may bring back to
 Haskell-land by using SqlQuery's return:
- You may return a SqlExpr (for an entityEntityv)v(i.e., like the*in SQL), which is then returned to Haskell-land as justEntity v.
- You may return a SqlExpr (Maybe (Entity v))for an entityvthat may beNULL, which is then returned to Haskell-land asMaybe (Entity v). Used forOUTER JOINs.
- You may return a SqlExpr (for a valueValuet)t(i.e., a single column), wheretis any instance ofPersistField, which is then returned to Haskell-land asValue t. You may useValueto return projections of anEntity(see(and^.)() or to return any other value calculated on the query (e.g.,?.)countRowsorsubSelect).
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
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<.valnow)
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(EntityAppointment)) -> 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 -> dosetp [ PersonAge=.just(valthisYear) -. 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 PersistListand 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
Instances
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).
(Internal) Mode of query being converted by toRawSql.
Constructors
| SELECT | |
| DELETE | |
| UPDATE | |
| INSERT_INTO | 
data NeedParens Source #
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.
Minimal complete definition
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
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
Arguments
| :: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) | |
| => Mode | |
| -> 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
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
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
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
makeOrderByNoNewline :: IdentInfo -> [OrderByClause] -> (Builder, [PersistValue]) Source #
builderToText :: Builder -> Text Source #