Safe Haskell | None |
---|---|
Language | Haskell2010 |
Module Database.PostgreSQL.PQTypes.SQL.Builder offers a nice monadic DSL for building SQL statements on the fly. Some examples:
>>>
:{
>>>
| sqlSelect "documents" $ do
>>>
| sqlResult "id"
>>>
| sqlResult "title"
>>>
| sqlResult "mtime"
>>>
| sqlOrderBy "documents.mtime DESC"
>>>
| sqlWhereILike "documents.title" "%pattern%"
>>>
:}
SQL " SELECT id, title, mtime FROM documents WHERE (documents.title ILIKE <\"%pattern%\">) ORDER BY documents.mtime DESC "
SQL.Builder
supports SELECT as sqlSelect
and data manipulation using
sqlInsert
, sqlInsertSelect
, sqlDelete
and sqlUpdate
.
>>>
import Data.Time.Clock
>>>
now <- getCurrentTime
>>>
:{
>>>
| sqlInsert "documents" $ do
>>>
| sqlSet "title" title
>>>
| sqlSet "ctime" now
>>>
| sqlResult "id"
>>>
:}
SQL " INSERT INTO documents (title, ctime) VALUES (<\"title\">, <\"2017-02-01 17:56:20.324894547 UTC\">) RETURNING id"
The sqlInsertSelect
is particulary interesting as it supports INSERT
of values taken from a SELECT clause from same or even different
tables.
There is a possibility to do multiple inserts at once. Data given by
sqlSetList
will be inserted multiple times, data given by sqlSet
will be multiplied as many times as needed to cover all inserted rows
(it is common to all rows). If you use multiple sqlSetList
then
lists will be made equal in length by appending DEFAULT
as fill
element.
>>>
:{
>>>
| sqlInsert "documents" $ do
>>>
| sqlSet "ctime" now
>>>
| sqlSetList "title" ["title1", "title2", "title3"]
>>>
| sqlResult "id"
>>>
:}
SQL " INSERT INTO documents (ctime, title) VALUES (<\"2017-02-01 17:56:20.324894547 UTC\">, <\"title1\">) , (<\"2017-02-01 17:56:20.324894547 UTC\">, <\"title2\">) , (<\"2017-02-01 17:56:20.324894547 UTC\">, <\"title3\">) RETURNING id"
The above will insert 3 new documents.
SQL.Builder
provides quite a lot of SQL magic, including ORDER BY
as
sqlOrderBy
, GROUP BY
as sqlGroupBy
.
>>>
:{
>>>
| sqlSelect "documents" $ do
>>>
| sqlResult "id"
>>>
| sqlResult "title"
>>>
| sqlResult "mtime"
>>>
| sqlOrderBy "documents.mtime DESC"
>>>
| sqlOrderBy "documents.title"
>>>
| sqlGroupBy "documents.status"
>>>
| sqlJoinOn "users" "documents.user_id = users.id"
>>>
| sqlWhere $ mkSQL "documents.title ILIKE" <?> "%pattern%"
>>>
:}
SQL " SELECT id, title, mtime FROM documents JOIN users ON documents.user_id = users.id WHERE (documents.title ILIKE <\"%pattern%\">) GROUP BY documents.status ORDER BY documents.mtime DESC, documents.title "
Joins are done by sqlJoinOn
, sqlLeftJoinOn
, sqlRightJoinOn
,
sqlJoinOn
, sqlFullJoinOn
. If everything fails use sqlJoin
and
sqlFrom
to set join clause as string. Support for a join grammars as
some kind of abstract syntax data type is lacking.
>>>
:{
>>>
| sqlDelete "mails" $ do
>>>
| sqlWhere "id > 67"
>>>
:}
SQL " DELETE FROM mails WHERE (id > 67) "
>>>
:{
>>>
| sqlUpdate "document_tags" $ do
>>>
| sqlSet "value" (123 :: Int)
>>>
| sqlWhere "name = 'abc'"
>>>
:}
SQL " UPDATE document_tags SET value=<123> WHERE (name = 'abc') "
Exception returning and kWhyNot
are a subsystem for querying why a
query did not provide expected results. For example:
let query = sqlUpdate "documents" $ do sqlSet "deleted" True sqlWhereEq "documents.id" 12345 sqlWhereEqE DocumentDeleteFlagMustBe "documents.deleted" False sqlWhereILikeE DocumentTitleMustContain "documents.title" "%important%" result <- kRun query
If the result is zero then no document was updated. We would like to
know what happened. In query we have three filtering clauses. One is a
baseline: the one mentioning documents.id
. Baseline clauses define
what objects we are talking about. Other clauses are correctness
checks and may fail if status of on object is unexpected. Using
kWhyNot
we can see what is wrong with an object:
problems <- kWhyNot query
Now problems
should contain a list of issues with rows that could be
possibly be affected by weren't due to correctness clauses. For
example it may state:
problems = [[ DocumentDeleteFlagMustBe { documentDeleteFlagMustBe = False , documentDeleteFlagReallyIs = True } , DocumentTitleMustContain { documentTitleMustContain = "%important%" , documentTitleReallyIs = "Some contract v2" } ]]
Note: problems is a nested array, for each object we get a list of issues pertaining to that object. If that list is empty, then it means that baseline conditions failed or there is no such object that fullfills all conditions at the same time although there are some that fullfill each one separatelly.
Note: kWhyNot
is currently disabled. Use kWhyNot1
instead, which
returns a single exception.
Synopsis
- sqlWhere :: (MonadState v m, SqlWhere v) => SQL -> m ()
- sqlWhereE :: (MonadState v m, SqlWhere v, DBExtraException e) => e -> SQL -> m ()
- sqlWhereEV :: (MonadState v m, SqlWhere v, DBExtraException e, FromSQL a) => (a -> e, SQL) -> SQL -> m ()
- sqlWhereEVV :: (MonadState v m, SqlWhere v, DBExtraException e, FromSQL a, FromSQL b) => (a -> b -> e, SQL, SQL) -> SQL -> m ()
- sqlWhereEVVV :: (MonadState v m, SqlWhere v, DBExtraException e, FromSQL a, FromSQL b, FromSQL c) => (a -> b -> c -> e, SQL, SQL, SQL) -> SQL -> m ()
- sqlWhereEVVVV :: (MonadState v m, SqlWhere v, DBExtraException e, FromSQL a, FromSQL b, FromSQL c, FromSQL d) => (a -> b -> c -> d -> e, SQL, SQL, SQL, SQL) -> SQL -> m ()
- sqlWhereEq :: (MonadState v m, SqlWhere v, Show a, ToSQL a) => SQL -> a -> m ()
- sqlWhereEqE :: (MonadState v m, SqlWhere v, DBExtraException e, Show a, FromSQL a, ToSQL a) => (a -> a -> e) -> SQL -> a -> m ()
- sqlWhereEqSql :: (MonadState v m, SqlWhere v, Sqlable sql) => SQL -> sql -> m ()
- sqlWhereNotEq :: (MonadState v m, SqlWhere v, Show a, ToSQL a) => SQL -> a -> m ()
- sqlWhereNotEqE :: (MonadState v m, SqlWhere v, DBExtraException e, Show a, ToSQL a, FromSQL a) => (a -> a -> e) -> SQL -> a -> m ()
- sqlWhereIn :: (MonadState v m, SqlWhere v, Show a, ToSQL a) => SQL -> [a] -> m ()
- sqlWhereInSql :: (MonadState v m, Sqlable a, SqlWhere v) => SQL -> a -> m ()
- sqlWhereInE :: (MonadState v m, SqlWhere v, DBExtraException e, Show a, ToSQL a, FromSQL a) => ([a] -> a -> e) -> SQL -> [a] -> m ()
- sqlWhereNotIn :: (MonadState v m, SqlWhere v, Show a, ToSQL a) => SQL -> [a] -> m ()
- sqlWhereNotInSql :: (MonadState v m, Sqlable a, SqlWhere v) => SQL -> a -> m ()
- sqlWhereNotInE :: (MonadState v m, SqlWhere v, DBExtraException e, Show a, ToSQL a, FromSQL a) => ([a] -> a -> e) -> SQL -> [a] -> m ()
- sqlWhereExists :: (MonadState v m, SqlWhere v) => SqlSelect -> m ()
- sqlWhereNotExists :: (MonadState v m, SqlWhere v) => SqlSelect -> m ()
- sqlWhereLike :: (MonadState v m, SqlWhere v, Show a, ToSQL a) => SQL -> a -> m ()
- sqlWhereLikeE :: (MonadState v m, SqlWhere v, DBExtraException e, Show a, ToSQL a, FromSQL a) => (a -> a -> e) -> SQL -> a -> m ()
- sqlWhereILike :: (MonadState v m, SqlWhere v, Show a, ToSQL a) => SQL -> a -> m ()
- sqlWhereILikeE :: (MonadState v m, SqlWhere v, DBExtraException e, Show a, ToSQL a, FromSQL a) => (a -> a -> e) -> SQL -> a -> m ()
- sqlWhereIsNULL :: (MonadState v m, SqlWhere v) => SQL -> m ()
- sqlWhereIsNotNULL :: (MonadState v m, SqlWhere v) => SQL -> m ()
- sqlWhereIsNULLE :: (MonadState v m, SqlWhere v, DBExtraException e, FromSQL a) => (a -> e) -> SQL -> m ()
- sqlIgnore :: MonadState s m => State (SqlWhereIgnore s) a -> m ()
- sqlFrom :: (MonadState v m, SqlFrom v) => SQL -> m ()
- sqlJoin :: (MonadState v m, SqlFrom v) => SQL -> m ()
- sqlJoinOn :: (MonadState v m, SqlFrom v) => SQL -> SQL -> m ()
- sqlLeftJoinOn :: (MonadState v m, SqlFrom v) => SQL -> SQL -> m ()
- sqlRightJoinOn :: (MonadState v m, SqlFrom v) => SQL -> SQL -> m ()
- sqlFullJoinOn :: (MonadState v m, SqlFrom v) => SQL -> SQL -> m ()
- sqlSet :: (MonadState v m, SqlSet v, Show a, ToSQL a) => SQL -> a -> m ()
- sqlSetInc :: (MonadState v m, SqlSet v) => SQL -> m ()
- sqlSetList :: (MonadState SqlInsert m, Show a, ToSQL a) => SQL -> [a] -> m ()
- sqlSetListWithDefaults :: (MonadState SqlInsert m, Show a, ToSQL a) => SQL -> [Maybe a] -> m ()
- sqlSetCmd :: (MonadState v m, SqlSet v) => SQL -> SQL -> m ()
- sqlSetCmdList :: MonadState SqlInsert m => SQL -> [SQL] -> m ()
- sqlCopyColumn :: (MonadState v m, SqlSet v) => SQL -> m ()
- sqlResult :: (MonadState v m, SqlResult v) => SQL -> m ()
- sqlOrderBy :: (MonadState v m, SqlOrderBy v) => SQL -> m ()
- sqlGroupBy :: (MonadState v m, SqlGroupByHaving v) => SQL -> m ()
- sqlHaving :: (MonadState v m, SqlGroupByHaving v) => SQL -> m ()
- sqlOffset :: (MonadState v m, SqlOffsetLimit v, Integral int) => int -> m ()
- sqlLimit :: (MonadState v m, SqlOffsetLimit v, Integral int) => int -> m ()
- sqlDistinct :: (MonadState v m, SqlDistinct v) => m ()
- sqlWith :: (MonadState v m, SqlWith v, Sqlable s) => SQL -> s -> m ()
- class (SqlWhere a, Sqlable a) => SqlTurnIntoSelect a
- sqlTurnIntoSelect :: SqlTurnIntoSelect a => a -> SqlSelect
- sqlTurnIntoWhyNotSelect :: SqlTurnIntoSelect a => a -> SqlSelect
- sqlSelect :: SQL -> State SqlSelect () -> SqlSelect
- sqlSelect2 :: SQL -> State SqlSelect () -> SqlSelect
- data SqlSelect = SqlSelect {
- sqlSelectFrom :: SQL
- sqlSelectDistinct :: Bool
- sqlSelectResult :: [SQL]
- sqlSelectWhere :: [SqlCondition]
- sqlSelectOrderBy :: [SQL]
- sqlSelectGroupBy :: [SQL]
- sqlSelectHaving :: [SQL]
- sqlSelectOffset :: Integer
- sqlSelectLimit :: Integer
- sqlSelectWith :: [(SQL, SQL)]
- sqlInsert :: SQL -> State SqlInsert () -> SqlInsert
- data SqlInsert = SqlInsert {
- sqlInsertWhat :: SQL
- sqlInsertSet :: [(SQL, Multiplicity SQL)]
- sqlInsertResult :: [SQL]
- sqlInsertWith :: [(SQL, SQL)]
- sqlInsertSelect :: SQL -> SQL -> State SqlInsertSelect () -> SqlInsertSelect
- data SqlInsertSelect = SqlInsertSelect {
- sqlInsertSelectWhat :: SQL
- sqlInsertSelectDistinct :: Bool
- sqlInsertSelectSet :: [(SQL, SQL)]
- sqlInsertSelectResult :: [SQL]
- sqlInsertSelectFrom :: SQL
- sqlInsertSelectWhere :: [SqlCondition]
- sqlInsertSelectOrderBy :: [SQL]
- sqlInsertSelectGroupBy :: [SQL]
- sqlInsertSelectHaving :: [SQL]
- sqlInsertSelectOffset :: Integer
- sqlInsertSelectLimit :: Integer
- sqlInsertSelectWith :: [(SQL, SQL)]
- sqlUpdate :: SQL -> State SqlUpdate () -> SqlUpdate
- data SqlUpdate = SqlUpdate {
- sqlUpdateWhat :: SQL
- sqlUpdateFrom :: SQL
- sqlUpdateWhere :: [SqlCondition]
- sqlUpdateSet :: [(SQL, SQL)]
- sqlUpdateResult :: [SQL]
- sqlUpdateWith :: [(SQL, SQL)]
- sqlDelete :: SQL -> State SqlDelete () -> SqlDelete
- data SqlDelete = SqlDelete {
- sqlDeleteFrom :: SQL
- sqlDeleteUsing :: SQL
- sqlDeleteWhere :: [SqlCondition]
- sqlDeleteResult :: [SQL]
- sqlDeleteWith :: [(SQL, SQL)]
- sqlWhereAny :: (MonadState v m, SqlWhere v) => [State SqlAll ()] -> m ()
- class SqlResult a
- class SqlSet a
- class SqlFrom a
- class SqlWhere a
- class SqlOrderBy a
- class SqlGroupByHaving a
- class SqlOffsetLimit a
- class SqlDistinct a
- data SqlCondition
- sqlGetWhereConditions :: SqlWhere a => a -> [SqlCondition]
- data SqlWhyNot = (FromRow row, DBExtraException e) => SqlWhyNot Bool (row -> e) [SQL]
- kWhyNot1 :: (SqlTurnIntoSelect s, MonadDB m, MonadThrow m) => s -> m SomeDBExtraException
- kRun1OrThrowWhyNot :: (SqlTurnIntoSelect s, MonadDB m, MonadThrow m) => s -> m ()
- kRun1OrThrowWhyNotAllowIgnore :: (SqlTurnIntoSelect s, MonadDB m, MonadThrow m) => s -> m ()
- kRunManyOrThrowWhyNot :: (SqlTurnIntoSelect s, MonadDB m, MonadThrow m) => s -> m ()
- kRunAndFetch1OrThrowWhyNot :: (IsSQL s, FromRow row, MonadDB m, MonadThrow m, SqlTurnIntoSelect s) => (row -> a) -> s -> m a
- class (Show e, Typeable e, ToJSValue e) => DBExtraException e where
- data SomeDBExtraException = (Show e, DBExtraException e) => SomeDBExtraException e
- catchDBExtraException :: (MonadBaseControl IO m, DBExtraException e) => m a -> (e -> m a) -> m a
- data DBBaseLineConditionIsFalse = DBBaseLineConditionIsFalse SQL
- class Sqlable a where
- sqlOR :: SQL -> SQL -> SQL
- sqlConcatComma :: [SQL] -> SQL
- sqlConcatAND :: [SQL] -> SQL
- sqlConcatOR :: [SQL] -> SQL
- parenthesize :: SQL -> SQL
- data AscDesc a
Documentation
sqlWhere :: (MonadState v m, SqlWhere v) => SQL -> m () Source #
The WHERE
part of an SQL query. See above for a usage
example. See also SqlCondition
.
sqlWhereE :: (MonadState v m, SqlWhere v, DBExtraException e) => e -> SQL -> m () Source #
Like sqlWhere
, but also takes an exception value that is thrown
in case of error. See SqlCondition
and SqlWhyNot
.
sqlWhereEV :: (MonadState v m, SqlWhere v, DBExtraException e, FromSQL a) => (a -> e, SQL) -> SQL -> m () Source #
Like sqlWhereE
, but takes a one-argument function that
constructs an exception value plus an SQL fragment for querying the
database for the argument that is fed into the exception
constructor function. See SqlCondition
and SqlWhyNot
.
The SQL fragment should be of form TABLENAME.COLUMNAME
, as it is
executed as part of a SELECT
query involving all referenced
tables.
sqlWhereEVV :: (MonadState v m, SqlWhere v, DBExtraException e, FromSQL a, FromSQL b) => (a -> b -> e, SQL, SQL) -> SQL -> m () Source #
Like sqlWhereEV
, but the exception constructor function takes
two arguments.
sqlWhereEVVV :: (MonadState v m, SqlWhere v, DBExtraException e, FromSQL a, FromSQL b, FromSQL c) => (a -> b -> c -> e, SQL, SQL, SQL) -> SQL -> m () Source #
Like sqlWhereEV
, but the exception constructor function takes
three arguments.
sqlWhereEVVVV :: (MonadState v m, SqlWhere v, DBExtraException e, FromSQL a, FromSQL b, FromSQL c, FromSQL d) => (a -> b -> c -> d -> e, SQL, SQL, SQL, SQL) -> SQL -> m () Source #
Like sqlWhereEV
, but the exception constructor function takes
four arguments.
sqlWhereEq :: (MonadState v m, SqlWhere v, Show a, ToSQL a) => SQL -> a -> m () Source #
sqlWhereEqE :: (MonadState v m, SqlWhere v, DBExtraException e, Show a, FromSQL a, ToSQL a) => (a -> a -> e) -> SQL -> a -> m () Source #
sqlWhereEqSql :: (MonadState v m, SqlWhere v, Sqlable sql) => SQL -> sql -> m () Source #
sqlWhereNotEq :: (MonadState v m, SqlWhere v, Show a, ToSQL a) => SQL -> a -> m () Source #
sqlWhereNotEqE :: (MonadState v m, SqlWhere v, DBExtraException e, Show a, ToSQL a, FromSQL a) => (a -> a -> e) -> SQL -> a -> m () Source #
sqlWhereIn :: (MonadState v m, SqlWhere v, Show a, ToSQL a) => SQL -> [a] -> m () Source #
sqlWhereInSql :: (MonadState v m, Sqlable a, SqlWhere v) => SQL -> a -> m () Source #
sqlWhereInE :: (MonadState v m, SqlWhere v, DBExtraException e, Show a, ToSQL a, FromSQL a) => ([a] -> a -> e) -> SQL -> [a] -> m () Source #
sqlWhereNotIn :: (MonadState v m, SqlWhere v, Show a, ToSQL a) => SQL -> [a] -> m () Source #
sqlWhereNotInSql :: (MonadState v m, Sqlable a, SqlWhere v) => SQL -> a -> m () Source #
sqlWhereNotInE :: (MonadState v m, SqlWhere v, DBExtraException e, Show a, ToSQL a, FromSQL a) => ([a] -> a -> e) -> SQL -> [a] -> m () Source #
sqlWhereExists :: (MonadState v m, SqlWhere v) => SqlSelect -> m () Source #
sqlWhereNotExists :: (MonadState v m, SqlWhere v) => SqlSelect -> m () Source #
sqlWhereLike :: (MonadState v m, SqlWhere v, Show a, ToSQL a) => SQL -> a -> m () Source #
sqlWhereLikeE :: (MonadState v m, SqlWhere v, DBExtraException e, Show a, ToSQL a, FromSQL a) => (a -> a -> e) -> SQL -> a -> m () Source #
sqlWhereILike :: (MonadState v m, SqlWhere v, Show a, ToSQL a) => SQL -> a -> m () Source #
sqlWhereILikeE :: (MonadState v m, SqlWhere v, DBExtraException e, Show a, ToSQL a, FromSQL a) => (a -> a -> e) -> SQL -> a -> m () Source #
sqlWhereIsNULL :: (MonadState v m, SqlWhere v) => SQL -> m () Source #
sqlWhereIsNotNULL :: (MonadState v m, SqlWhere v) => SQL -> m () Source #
sqlWhereIsNULLE :: (MonadState v m, SqlWhere v, DBExtraException e, FromSQL a) => (a -> e) -> SQL -> m () Source #
sqlIgnore :: MonadState s m => State (SqlWhereIgnore s) a -> m () Source #
sqlLeftJoinOn :: (MonadState v m, SqlFrom v) => SQL -> SQL -> m () Source #
sqlRightJoinOn :: (MonadState v m, SqlFrom v) => SQL -> SQL -> m () Source #
sqlFullJoinOn :: (MonadState v m, SqlFrom v) => SQL -> SQL -> m () Source #
sqlSetList :: (MonadState SqlInsert m, Show a, ToSQL a) => SQL -> [a] -> m () Source #
sqlSetListWithDefaults :: (MonadState SqlInsert m, Show a, ToSQL a) => SQL -> [Maybe a] -> m () Source #
sqlSetCmdList :: MonadState SqlInsert m => SQL -> [SQL] -> m () Source #
sqlCopyColumn :: (MonadState v m, SqlSet v) => SQL -> m () Source #
sqlOrderBy :: (MonadState v m, SqlOrderBy v) => SQL -> m () Source #
sqlGroupBy :: (MonadState v m, SqlGroupByHaving v) => SQL -> m () Source #
sqlHaving :: (MonadState v m, SqlGroupByHaving v) => SQL -> m () Source #
sqlOffset :: (MonadState v m, SqlOffsetLimit v, Integral int) => int -> m () Source #
sqlLimit :: (MonadState v m, SqlOffsetLimit v, Integral int) => int -> m () Source #
sqlDistinct :: (MonadState v m, SqlDistinct v) => m () Source #
class (SqlWhere a, Sqlable a) => SqlTurnIntoSelect a Source #
Instances
sqlTurnIntoSelect :: SqlTurnIntoSelect a => a -> SqlSelect Source #
sqlTurnIntoWhyNotSelect :: SqlTurnIntoSelect a => a -> SqlSelect Source #
The sqlTurnIntoWhyNotSelect
turns a failed query into a
why-not-query that can explain why query altered zero rows or
returned zero results.
Lets consider an example of explanation:
UPDATE t1 SET a = 1 WHERE cond1 AND cond2 -- with value2 AND EXISTS (SELECT TRUE FROM t2 WHERE cond3 -- with value3a and value3b AND EXISTS (SELECT TRUE FROM t3 WHERE cond4))
sqlTurnIntoWhyNotSelect
will produce a SELECT
of the form:
SELECT EXISTS (SELECT TRUE ... WHERE cond1), EXISTS (SELECT TRUE ... WHERE cond1 AND cond2), EXISTS (SELECT TRUE ... WHERE cond1 AND cond2 AND cond3), EXISTS (SELECT TRUE ... WHERE cond1 AND cond2 AND cond3 AND cond4);
Now, after this statement is executed we see which of these
returned FALSE
as the first one. This is the condition that failed
the whole query.
We can get more information at this point. If failed condition was
cond2
, then value2
can be extracted by this statement:
SELECT value2 ... WHERE cond1;
If failed condition was cond3
, then statement executed can be:
SELECT value3a, value3b ... WHERE cond1 AND cond2;
Rationale: EXISTS
clauses should pinpoint which condX
was the first
one to produce zero rows. SELECT
clauses after EXISTS
should
explain why condX filtered out all rows.
kWhyNot1
looks for first EXISTS
clause that is FALSE
and then tries to construct an Exception
object with values that come
after. If values that comes after cannot be sensibly parsed
(usually they are NULL
when a value is expected), this exception is
skipped and next one is tried.
If first EXISTS
clause is TRUE
but no other exception was properly
generated then DBExceptionCouldNotParseValues
is thrown with pair
of typeRef
of first exception that could not be parsed and with
list of SqlValues that it could not parse.
The kRun1OrThrowWhyNot
throws first exception on the
list.
We have a theorem to use in this transformation:
EXISTS (SELECT t1 WHERE cond1 AND EXISTS (SELECT t2 WHERE cond2))
is equivalent to
EXISTS (SELECT t1, t2 WHERE cond1 AND cond2)
and it can be used recursivelly.
SqlSelect | |
|
Instances
SqlInsert | |
|
Instances
Show SqlInsert Source # | |
IsSQL SqlInsert Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder | |
SqlResult SqlInsert Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder sqlResult1 :: SqlInsert -> SQL -> SqlInsert | |
SqlSet SqlInsert Source # | |
Sqlable SqlInsert Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder toSQLCommand :: SqlInsert -> SQL Source # |
sqlInsertSelect :: SQL -> SQL -> State SqlInsertSelect () -> SqlInsertSelect Source #
data SqlInsertSelect Source #
SqlInsertSelect | |
|
Instances
SqlUpdate | |
|
Instances
Show SqlUpdate Source # | |
IsSQL SqlUpdate Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder | |
SqlTurnIntoSelect SqlUpdate Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder | |
SqlResult SqlUpdate Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder sqlResult1 :: SqlUpdate -> SQL -> SqlUpdate | |
SqlSet SqlUpdate Source # | |
SqlFrom SqlUpdate Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder | |
SqlWhere SqlUpdate Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder sqlWhere1 :: SqlUpdate -> SqlCondition -> SqlUpdate sqlGetWhereConditions :: SqlUpdate -> [SqlCondition] Source # | |
Sqlable SqlUpdate Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder toSQLCommand :: SqlUpdate -> SQL Source # |
SqlDelete | |
|
Instances
Show SqlDelete Source # | |
IsSQL SqlDelete Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder | |
SqlTurnIntoSelect SqlDelete Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder | |
SqlFrom SqlDelete Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder | |
SqlWhere SqlDelete Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder sqlWhere1 :: SqlDelete -> SqlCondition -> SqlDelete sqlGetWhereConditions :: SqlDelete -> [SqlCondition] Source # | |
Sqlable SqlDelete Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder toSQLCommand :: SqlDelete -> SQL Source # |
sqlWhereAny :: (MonadState v m, SqlWhere v) => [State SqlAll ()] -> m () Source #
sqlResult1
Instances
SqlResult SqlInsertSelect Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder sqlResult1 :: SqlInsertSelect -> SQL -> SqlInsertSelect | |
SqlResult SqlInsert Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder sqlResult1 :: SqlInsert -> SQL -> SqlInsert | |
SqlResult SqlUpdate Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder sqlResult1 :: SqlUpdate -> SQL -> SqlUpdate | |
SqlResult SqlSelect Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder sqlResult1 :: SqlSelect -> SQL -> SqlSelect |
sqlSet1
Instances
SqlSet SqlInsertSelect Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder sqlSet1 :: SqlInsertSelect -> SQL -> SQL -> SqlInsertSelect | |
SqlSet SqlInsert Source # | |
SqlSet SqlUpdate Source # | |
sqlFrom1
Instances
SqlFrom SqlDelete Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder | |
SqlFrom SqlInsertSelect Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder sqlFrom1 :: SqlInsertSelect -> SQL -> SqlInsertSelect | |
SqlFrom SqlUpdate Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder | |
SqlFrom SqlSelect Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder |
sqlWhere1, sqlGetWhereConditions
Instances
SqlWhere SqlDelete Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder sqlWhere1 :: SqlDelete -> SqlCondition -> SqlDelete sqlGetWhereConditions :: SqlDelete -> [SqlCondition] Source # | |
SqlWhere SqlInsertSelect Source # | |
SqlWhere SqlUpdate Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder sqlWhere1 :: SqlUpdate -> SqlCondition -> SqlUpdate sqlGetWhereConditions :: SqlUpdate -> [SqlCondition] Source # | |
SqlWhere SqlSelect Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder sqlWhere1 :: SqlSelect -> SqlCondition -> SqlSelect sqlGetWhereConditions :: SqlSelect -> [SqlCondition] Source # |
class SqlOrderBy a Source #
sqlOrderBy1
Instances
SqlOrderBy SqlInsertSelect Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder sqlOrderBy1 :: SqlInsertSelect -> SQL -> SqlInsertSelect | |
SqlOrderBy SqlSelect Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder sqlOrderBy1 :: SqlSelect -> SQL -> SqlSelect |
class SqlGroupByHaving a Source #
sqlGroupBy1, sqlHaving1
Instances
SqlGroupByHaving SqlInsertSelect Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder sqlGroupBy1 :: SqlInsertSelect -> SQL -> SqlInsertSelect sqlHaving1 :: SqlInsertSelect -> SQL -> SqlInsertSelect | |
SqlGroupByHaving SqlSelect Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder sqlGroupBy1 :: SqlSelect -> SQL -> SqlSelect sqlHaving1 :: SqlSelect -> SQL -> SqlSelect |
class SqlOffsetLimit a Source #
sqlOffset1, sqlLimit1
Instances
class SqlDistinct a Source #
sqlDistinct1
Instances
SqlDistinct SqlInsertSelect Source # | |
SqlDistinct SqlSelect Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder sqlDistinct1 :: SqlSelect -> SqlSelect |
data SqlCondition Source #
SqlCondition
are clauses that are part of the WHERE block in
SQL statements. Each statement has a list of conditions, all of
them must be fulfilled. Sometimes we need to inspect internal
structure of a condition. For now it seems that the only
interesting case is EXISTS (SELECT ...), because that internal
SELECT can have explainable clauses.
Instances
Show SqlCondition Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder showsPrec :: Int -> SqlCondition -> ShowS # show :: SqlCondition -> String # showList :: [SqlCondition] -> ShowS # | |
Sqlable SqlCondition Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder toSQLCommand :: SqlCondition -> SQL Source # |
sqlGetWhereConditions :: SqlWhere a => a -> [SqlCondition] Source #
SqlWhyNot
contains a recipe for how to query the database for
some values we're interested in and construct a proper exception
object using that information. For SqlWhyNot mkException queries
the mkException
should take as input a list of the same length
list as there are queries. Each query will be run in a JOIN context
with all referenced tables, so it can extract values from there.
(FromRow row, DBExtraException e) => SqlWhyNot Bool (row -> e) [SQL] |
kWhyNot1 :: (SqlTurnIntoSelect s, MonadDB m, MonadThrow m) => s -> m SomeDBExtraException Source #
kRun1OrThrowWhyNot :: (SqlTurnIntoSelect s, MonadDB m, MonadThrow m) => s -> m () Source #
kRun1OrThrowWhyNotAllowIgnore :: (SqlTurnIntoSelect s, MonadDB m, MonadThrow m) => s -> m () Source #
kRunManyOrThrowWhyNot :: (SqlTurnIntoSelect s, MonadDB m, MonadThrow m) => s -> m () Source #
kRunAndFetch1OrThrowWhyNot :: (IsSQL s, FromRow row, MonadDB m, MonadThrow m, SqlTurnIntoSelect s) => (row -> a) -> s -> m a Source #
class (Show e, Typeable e, ToJSValue e) => DBExtraException e where Source #
DBExtraException
and SomeDBExtraException
mimic Exception
and
SomeException
, but we need our own class and data type to limit its
use to only those which describe semantic exceptions.
Our data types also feature conversion to JSON type so that external representation is known in place where exception is defined.
data SomeDBExtraException Source #
(Show e, DBExtraException e) => SomeDBExtraException e |
Instances
Show SomeDBExtraException Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder showsPrec :: Int -> SomeDBExtraException -> ShowS # show :: SomeDBExtraException -> String # showList :: [SomeDBExtraException] -> ShowS # | |
Exception SomeDBExtraException Source # | |
catchDBExtraException :: (MonadBaseControl IO m, DBExtraException e) => m a -> (e -> m a) -> m a Source #
data DBBaseLineConditionIsFalse Source #
Instances
class Sqlable a where Source #
toSQLCommand :: a -> SQL Source #
Instances
Sqlable SQL Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder toSQLCommand :: SQL -> SQL Source # | |
Sqlable SqlDelete Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder toSQLCommand :: SqlDelete -> SQL Source # | |
Sqlable SqlInsertSelect Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder toSQLCommand :: SqlInsertSelect -> SQL Source # | |
Sqlable SqlInsert Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder toSQLCommand :: SqlInsert -> SQL Source # | |
Sqlable SqlUpdate Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder toSQLCommand :: SqlUpdate -> SQL Source # | |
Sqlable SqlSelect Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder toSQLCommand :: SqlSelect -> SQL Source # | |
Sqlable SqlCondition Source # | |
Defined in Database.PostgreSQL.PQTypes.SQL.Builder toSQLCommand :: SqlCondition -> SQL Source # |
sqlConcatComma :: [SQL] -> SQL Source #
sqlConcatAND :: [SQL] -> SQL Source #
sqlConcatOR :: [SQL] -> SQL Source #
parenthesize :: SQL -> SQL Source #