hpqtypes-extras-1.9.0.1: Extra utilities for hpqtypes library

Safe HaskellNone
LanguageHaskell2010

Database.PostgreSQL.PQTypes.SQL.Builder

Description

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

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 #

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 #

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 #

sqlFrom :: (MonadState v m, SqlFrom v) => SQL -> m () Source #

sqlJoin :: (MonadState v m, SqlFrom v) => SQL -> m () Source #

sqlJoinOn :: (MonadState v m, SqlFrom v) => SQL -> SQL -> 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 #

sqlSet :: (MonadState v m, SqlSet v, Show a, ToSQL a) => SQL -> a -> m () Source #

sqlSetInc :: (MonadState v m, SqlSet v) => SQL -> m () Source #

sqlSetList :: (MonadState SqlInsert m, Show a, ToSQL a) => SQL -> [a] -> m () Source #

sqlSetCmd :: (MonadState v m, SqlSet v) => SQL -> SQL -> m () Source #

sqlCopyColumn :: (MonadState v m, SqlSet v) => SQL -> m () Source #

sqlResult :: (MonadState v m, SqlResult v) => SQL -> m () Source #

sqlOrderBy :: (MonadState v m, SqlOrderBy 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 #

sqlWith :: (MonadState v m, SqlWith v, Sqlable s) => SQL -> s -> m () 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.

data SqlSelect Source #

Instances
Show SqlSelect Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

IsSQL SqlSelect Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

Methods

withSQL :: SqlSelect -> ParamAllocator -> (Ptr PGparam -> CString -> IO r) -> IO r #

SqlTurnIntoSelect SqlSelect Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

SqlDistinct SqlSelect Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

SqlOffsetLimit SqlSelect Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

SqlGroupByHaving SqlSelect Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

SqlOrderBy SqlSelect Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

SqlResult SqlSelect Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

SqlFrom SqlSelect Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

SqlWhere SqlSelect Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

Sqlable SqlSelect Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

data SqlInsertSelect Source #

Instances
Show SqlInsertSelect Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

IsSQL SqlInsertSelect Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

Methods

withSQL :: SqlInsertSelect -> ParamAllocator -> (Ptr PGparam -> CString -> IO r) -> IO r #

SqlTurnIntoSelect SqlInsertSelect Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

SqlDistinct SqlInsertSelect Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

SqlOffsetLimit SqlInsertSelect Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

SqlGroupByHaving SqlInsertSelect Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

SqlOrderBy SqlInsertSelect Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

SqlResult SqlInsertSelect Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

SqlSet SqlInsertSelect Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

SqlFrom SqlInsertSelect Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

SqlWhere SqlInsertSelect Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

Sqlable SqlInsertSelect Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

data SqlUpdate Source #

sqlWhereAny :: (MonadState v m, SqlWhere v) => [State SqlAll ()] -> m () Source #

Add a condition in the WHERE statement that holds if any of the given condition holds.

sqlWhereAnyE :: (DBExtraException e, MonadState v m, SqlWhere v) => e -> [State SqlAll ()] -> m () Source #

Add a condition just like sqlWhereAny but throw the given exception if none of the given conditions hold.

class SqlSet a Source #

Minimal complete definition

sqlSet1

class SqlFrom a Source #

Minimal complete definition

sqlFrom1

class SqlOrderBy a Source #

Minimal complete definition

sqlOrderBy1

class SqlDistinct a Source #

Minimal complete definition

sqlDistinct1

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.

data SqlWhyNot 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.

Constructors

(FromRow row, DBExtraException e) => SqlWhyNot Bool (row -> e) [SQL] 

kWhyNot1 :: (SqlTurnIntoSelect s, MonadDB m, MonadThrow m) => s -> m SomeDBExtraException Source #

Function kWhyNot1 is a workhorse for explainable SQL failures. SQL fails if it did not affect any rows or did not return any rows. When that happens kWhyNot1 should be called. kWhyNot1 returns an exception describing why a row could not be returned or affected by a query.

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.

Minimal complete definition

Nothing

catchDBExtraException :: (MonadBaseControl IO m, DBExtraException e) => m a -> (e -> m a) -> m a Source #

sqlOR :: SQL -> SQL -> SQL Source #

data AscDesc a Source #

AscDesc marks ORDER BY order as ascending or descending. Conversion to SQL adds DESC marker to descending and no marker to ascending order.

Constructors

Asc a 
Desc a 
Instances
Eq a => Eq (AscDesc a) Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

Methods

(==) :: AscDesc a -> AscDesc a -> Bool #

(/=) :: AscDesc a -> AscDesc a -> Bool #

Show a => Show (AscDesc a) Source # 
Instance details

Defined in Database.PostgreSQL.PQTypes.SQL.Builder

Methods

showsPrec :: Int -> AscDesc a -> ShowS #

show :: AscDesc a -> String #

showList :: [AscDesc a] -> ShowS #