hpqtypes-extras-1.2.4: Extra utilities for hpqtypes library

Safe HaskellNone
LanguageHaskell2010

Database.PostgreSQL.PQTypes.SQL.Builder

Description

Module SQL2 offers some nice monadic function that build SQL commands on the fly. Some examples:

kRun_ $ sqlSelect "documents" $ do
  sqlResult "id"
  sqlResult "title"
  sqlResult "mtime"
  sqlOrderBy "documents.mtime DESC"
  sqlWhereILike "documents.title" pattern

SQL2 supports SELECT as sqlSelect and data manipulation using sqlInsert, sqlInsertSelect, sqlDelete and sqlUpdate.

kRun_ $ sqlInsert "documents" $ do
  sqlSet "title" title
  sqlSet "ctime" now
  sqlResult "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.

kRun_ $ sqlInsert "documents" $ do
  sqlSet "ctime" now
  sqlSetList "title" [title1, title2, title3]
  sqlResult "id"

The above will insert 3 new documents.

SQL2 provides quite a lot of SQL magic, including ORDER BY as sqlOrderBy, GROUP BY as sqlGroupBy.

kRun_ $ 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 $ SQL "documents.title ILIKE ?" [toSql pattern]

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.

kRun_ $ sqlDelete "mails" $ do
  sqlWhere "id > 67"
kRun_ $ sqlUpdate "document_tags" $ do
  sqlSet "value" (123 :: Int)
  sqlWhere "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

In 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 are we 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.

Synopsis

Documentation

sqlWhere :: (MonadState v m, SqlWhere v) => SQL -> m () Source #

sqlWhereE :: (MonadState v m, SqlWhere v, DBExtraException e) => e -> SQL -> m () Source #

sqlWhereEV :: (MonadState v m, SqlWhere v, DBExtraException e, FromSQL a) => (a -> e, SQL) -> SQL -> m () Source #

sqlWhereEVV :: (MonadState v m, SqlWhere v, DBExtraException e, FromSQL a, FromSQL b) => (a -> b -> e, SQL, SQL) -> SQL -> m () Source #

sqlWhereEVVV :: (MonadState v m, SqlWhere v, DBExtraException e, FromSQL a, FromSQL b, FromSQL c) => (a -> b -> c -> e, SQL, SQL, SQL) -> SQL -> m () Source #

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 #

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 turn 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 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 #

data SqlInsertSelect Source #

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

class SqlSet a Source #

Minimal complete definition

sqlSet1

class SqlOrderBy a Source #

Minimal complete definition

sqlOrderBy1

class SqlDistinct a Source #

Minimal complete definition

sqlDistinct1

data SqlCondition Source #

SqlCondition are clauses that are in SQL statements in the WHERE block. Each statement has a list of conditions, all of them must be fullfilled. 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 recepie how to query the database for current values in there and construct proper exception object using that information. For SqlWhyNot mkException queries the mkException should take as input same lenth 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] 

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.

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 # 

Methods

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

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

Show a => Show (AscDesc a) Source # 

Methods

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

show :: AscDesc a -> String #

showList :: [AscDesc a] -> ShowS #