esqueleto-1.4: Bare bones, type-safe EDSL for SQL queries on persistent backends.

Safe HaskellNone

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 SqlExpr a Source

An expression on the SQL backend.

Instances

Esqueleto SqlQuery SqlExpr SqlBackend 
ToSomeValues SqlExpr (SqlExpr (Value a)) 
~ * a (Value b) => UnsafeSqlFunctionArgument (SqlExpr a) 
PersistEntity a => SqlSelect (SqlExpr (Maybe (Entity a))) (Maybe (Entity a))

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

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

You may return an Entity from a select query.

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

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

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

Constraint synonym for persistent entities whose backend is SqlPersistT.

select :: (SqlSelect a r, MonadResource m, MonadSqlPersist m) => SqlQuery a -> 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 sub_select).

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, MonadResource m, MonadSqlPersist m) => SqlQuery a -> m (Source m r)Source

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

selectDistinct :: (SqlSelect a r, MonadResource m, MonadSqlPersist m) => SqlQuery a -> m [r]Source

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

selectDistinctSource :: (SqlSelect a r, MonadResource m, MonadSqlPersist m) => SqlQuery a -> m (Source m r)Source

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

delete :: (MonadResource m, MonadSqlPersist m) => SqlQuery () -> 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 :: (MonadResource m, MonadSqlPersist m) => SqlQuery () -> m Int64Source

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

update :: (MonadResource m, MonadSqlPersist m, SqlEntity val) => (SqlExpr (Entity val) -> SqlQuery ()) -> 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_ $ isNull (p ^. PersonAge)

updateCount :: (MonadResource m, MonadSqlPersist m, SqlEntity val) => (SqlExpr (Entity val) -> SqlQuery ()) -> m Int64Source

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

insertSelectDistinct :: (MonadResource m, MonadSqlPersist m, PersistEntity a) => SqlQuery (SqlExpr (Insertion a)) -> m ()Source

Insert a PersistField for every unique selected value.

insertSelect :: (MonadResource m, MonadSqlPersist m, PersistEntity a) => SqlQuery (SqlExpr (Insertion a)) -> m ()Source

Insert a PersistField for every selected value.

The guts

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.

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.

rawSelectSource :: (SqlSelect a r, MonadResource m, MonadSqlPersist m) => Mode -> SqlQuery a -> m (Source m r)Source

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

runSource :: MonadResource m => Source m r -> m [r]Source

(Internal) Run a Source of rows.

rawEsqueleto :: (MonadResource m, MonadSqlPersist m, SqlSelect a r) => Mode -> SqlQuery a -> m Int64Source

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

toRawSql :: SqlSelect a r => Mode -> IdentInfo -> 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), you may just turn on query logging of persistent.

data Mode Source

(Internal) Mode of query being converted by toRawSql.

data IdentState Source

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

type IdentInfo = (Connection, IdentState)Source

Information needed to escape and use identifiers.

class SqlSelect a r | a -> r, r -> a whereSource

(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 -> IntSource

Number of columns that will be consumed.

sqlSelectProcessRow :: [PersistValue] -> Either Text rSource

Transform a row of the result into the data type.

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

Create INSERT INTO clause instead.

Instances

SqlSelect () ()

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

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

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

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

You may return an Entity from a select query.

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

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

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

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

(SqlSelect a ra, SqlSelect b rb, SqlSelect c rc) => SqlSelect (a, b, c) (ra, rb, rc) 
(SqlSelect a ra, SqlSelect b rb, SqlSelect c rc, SqlSelect d rd) => SqlSelect (a, b, c, d) (ra, rb, rc, rd) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 

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.