beam-core-0.6.0.0: Type-safe, feature-complete SQL query and manipulation interface for Haskell

Safe HaskellNone
LanguageHaskell2010

Database.Beam.Query

Contents

Synopsis

Query type

Query expression contexts

A context is a type-level value that signifies where an expression can be used. For example, QExpr corresponds to QGenExprs that result in values. In reality, QExpr is really QGenExpr parameterized over the QValueContext. Similarly, QAgg represents expressions that contain aggregates, but it is just QGenExpr parameterized over QAggregateContext

data QGroupingContext Source #

Instances

Beamable tbl => QGroupable (tbl (QExpr expr s)) (tbl (QGroupExpr expr s)) Source #

group_ for any Beamable type. Adds every field in the type to the grouping key. This is the equivalent of including the grouping expression of each field in the type as part of the aggregate projection

Methods

group_ :: tbl (QExpr expr s) -> tbl (QGroupExpr expr s) Source #

QGroupable (QExpr expr s a) (QGroupExpr expr s a) Source #

group_ for simple value expressions.

Methods

group_ :: QExpr expr s a -> QGroupExpr expr s a Source #

type ContextName QGroupingContext Source # 
type ContextName QGroupingContext = "an aggregate grouping"

data QValueContext Source #

Instances

(IsSql92ExpressionSyntax syntax, HasSqlValueSyntax (Sql92ExpressionValueSyntax syntax) Bool, Beamable t) => SqlDeconstructMaybe syntax (t (Nullable (QExpr syntax s))) (t (QExpr syntax s)) s Source # 

Methods

isJust_ :: t (Nullable (QExpr syntax s)) -> QExpr syntax s Bool Source #

isNothing_ :: t (Nullable (QExpr syntax s)) -> QExpr syntax s Bool Source #

maybe_ :: QExpr syntax s y -> (t (QExpr syntax s) -> QExpr syntax s y) -> t (Nullable (QExpr syntax s)) -> QExpr syntax s y Source #

IsSql92ExpressionSyntax syntax => SqlDeconstructMaybe syntax (QExpr syntax s (Maybe x)) (QExpr syntax s x) s Source # 

Methods

isJust_ :: QExpr syntax s (Maybe x) -> QExpr syntax s Bool Source #

isNothing_ :: QExpr syntax s (Maybe x) -> QExpr syntax s Bool Source #

maybe_ :: QExpr syntax s y -> (QExpr syntax s x -> QExpr syntax s y) -> QExpr syntax s (Maybe x) -> QExpr syntax s y Source #

(Table t, IsSql92ExpressionSyntax syntax, HasSqlValueSyntax (Sql92ExpressionValueSyntax syntax) SqlNull) => SqlJustable (t (QExpr syntax s)) (t (Nullable (QExpr syntax s))) Source # 

Methods

just_ :: t (QExpr syntax s) -> t (Nullable (QExpr syntax s)) Source #

nothing_ :: t (Nullable (QExpr syntax s)) Source #

Beamable tbl => QGroupable (tbl (QExpr expr s)) (tbl (QGroupExpr expr s)) Source #

group_ for any Beamable type. Adds every field in the type to the grouping key. This is the equivalent of including the grouping expression of each field in the type as part of the aggregate projection

Methods

group_ :: tbl (QExpr expr s) -> tbl (QGroupExpr expr s) Source #

(Table t, IsSql92ExpressionSyntax syntax, HasSqlValueSyntax (Sql92ExpressionValueSyntax syntax) SqlNull) => SqlJustable (PrimaryKey t (QExpr syntax s)) (PrimaryKey t (Nullable (QExpr syntax s))) Source # 

Methods

just_ :: PrimaryKey t (QExpr syntax s) -> PrimaryKey t (Nullable (QExpr syntax s)) Source #

nothing_ :: PrimaryKey t (Nullable (QExpr syntax s)) Source #

(IsSql92ExpressionSyntax syntax, HasSqlValueSyntax (Sql92ExpressionValueSyntax syntax) SqlNull) => SqlJustable (QExpr syntax s a) (QExpr syntax s (Maybe a)) Source # 

Methods

just_ :: QExpr syntax s a -> QExpr syntax s (Maybe a) Source #

nothing_ :: QExpr syntax s (Maybe a) Source #

QGroupable (QExpr expr s a) (QGroupExpr expr s a) Source #

group_ for simple value expressions.

Methods

group_ :: QExpr expr s a -> QGroupExpr expr s a Source #

type ContextName QValueContext Source # 
type ContextName QValueContext = "a value"

type QGenExprTable ctxt syntax tbl = forall s. tbl (QGenExpr ctxt syntax s) Source #

A version of the table where each field is a QGenExpr

type QExprTable syntax tbl = QGenExprTable QValueContext syntax tbl Source #

Various SQL functions and constructs

coalesce_ :: IsSql92ExpressionSyntax expr => [QExpr expr s (Maybe a)] -> QExpr expr s a -> QExpr expr s a Source #

SQL COALESCE support

position_ :: (IsSqlExpressionSyntaxStringType syntax text, IsSql92ExpressionSyntax syntax, Integral b) => QExpr syntax s text -> QExpr syntax s text -> QExpr syntax s b Source #

SQL POSITION(.. IN ..) function

charLength_ :: (IsSqlExpressionSyntaxStringType syntax text, IsSql92ExpressionSyntax syntax) => QGenExpr context syntax s text -> QGenExpr context syntax s Int Source #

SQL CHAR_LENGTH function

octetLength_ :: (IsSqlExpressionSyntaxStringType syntax text, IsSql92ExpressionSyntax syntax) => QGenExpr context syntax s text -> QGenExpr context syntax s Int Source #

SQL OCTET_LENGTH function

bitLength_ :: IsSql92ExpressionSyntax syntax => QGenExpr context syntax s SqlBitString -> QGenExpr context syntax s Int Source #

SQL BIT_LENGTH function

currentTimestamp_ :: IsSql92ExpressionSyntax syntax => QGenExpr ctxt syntax s LocalTime Source #

SQL CURRENT_TIMESTAMP function

IF-THEN-ELSE support

if_ :: IsSql92ExpressionSyntax expr => [QIfCond context expr s a] -> QIfElse context expr s a -> QGenExpr context expr s a Source #

then_ :: QGenExpr context expr s Bool -> QGenExpr context expr s a -> QIfCond context expr s a Source #

else_ :: QGenExpr context expr s a -> QIfElse context expr s a Source #

SQL UPDATE assignments

(<-.) :: forall fieldName. (SqlUpdatable expr s lhs rhs, IsSql92FieldNameSyntax fieldName) => lhs -> rhs -> QAssignment fieldName expr s infix 4 Source #

Update a QField or Beamable type containing QFields with the given QExpr or Beamable type containing QExpr

current_ :: IsSql92ExpressionSyntax expr => QField s ty -> QExpr expr s ty Source #

Extract an expression representing the current (non-UPDATEd) value of a QField

Project Haskell values to QGenExprs

type family HaskellLiteralForQExpr x = a Source #

Instances

type HaskellLiteralForQExpr (table (QGenExpr context syntax s)) Source # 
type HaskellLiteralForQExpr (table (QGenExpr context syntax s)) = table Identity
type HaskellLiteralForQExpr (table (Nullable f)) Source # 
type HaskellLiteralForQExpr (QGenExpr context syntax s a) Source # 
type HaskellLiteralForQExpr (QGenExpr context syntax s a) = a

class SqlValable a where Source #

Minimal complete definition

val_

Instances

(Beamable table, IsSql92ExpressionSyntax syntax, FieldsFulfillConstraintNullable (HasSqlValueSyntax (Sql92ExpressionValueSyntax syntax)) table) => SqlValable (table (Nullable (QGenExpr ctxt syntax s))) Source # 

Methods

val_ :: HaskellLiteralForQExpr (table (Nullable (QGenExpr ctxt syntax s))) -> table (Nullable (QGenExpr ctxt syntax s)) Source #

(Beamable table, IsSql92ExpressionSyntax syntax, FieldsFulfillConstraint (HasSqlValueSyntax (Sql92ExpressionValueSyntax syntax)) table) => SqlValable (table (QGenExpr ctxt syntax s)) Source # 

Methods

val_ :: HaskellLiteralForQExpr (table (QGenExpr ctxt syntax s)) -> table (QGenExpr ctxt syntax s) Source #

(HasSqlValueSyntax (Sql92ExpressionValueSyntax syntax) a, IsSql92ExpressionSyntax syntax) => SqlValable (QGenExpr ctxt syntax s a) Source # 

Methods

val_ :: HaskellLiteralForQExpr (QGenExpr ctxt syntax s a) -> QGenExpr ctxt syntax s a Source #

auto_ :: QGenExpr ctxt syntax s a -> QGenExpr ctxt syntax s (Auto a) Source #

General query combinators

guard_ :: forall select db s. IsSql92SelectSyntax select => QExpr (Sql92SelectTableExpressionSyntax (Sql92SelectSelectTableSyntax select)) s Bool -> Q select db s () Source #

Only allow results for which the QExpr yields True

filter_ :: forall r select db s. IsSql92SelectSyntax select => (r -> QExpr (Sql92SelectTableExpressionSyntax (Sql92SelectSelectTableSyntax select)) s Bool) -> Q select db s r -> Q select db s r Source #

Synonym for clause >>= x -> guard_ (mkExpr x)>> pure x

related_ :: forall be db rel select s. (IsSql92SelectSyntax select, HasSqlValueSyntax (Sql92ExpressionValueSyntax (Sql92SelectTableExpressionSyntax (Sql92SelectSelectTableSyntax select))) Bool, Database db, Table rel) => DatabaseEntity be db (TableEntity rel) -> PrimaryKey rel (QExpr (Sql92SelectTableExpressionSyntax (Sql92SelectSelectTableSyntax select)) s) -> Q select db s (rel (QExpr (Sql92SelectTableExpressionSyntax (Sql92SelectSelectTableSyntax select)) s)) Source #

Introduce all entries of the given table which are referenced by the given PrimaryKey

relatedBy_ :: forall be db rel select s. (Database db, Table rel, HasSqlValueSyntax (Sql92ExpressionValueSyntax (Sql92SelectTableExpressionSyntax (Sql92SelectSelectTableSyntax select))) Bool, IsSql92SelectSyntax select) => DatabaseEntity be db (TableEntity rel) -> (rel (QExpr (Sql92SelectTableExpressionSyntax (Sql92SelectSelectTableSyntax select)) s) -> QExpr (Sql92SelectTableExpressionSyntax (Sql92SelectSelectTableSyntax select)) s Bool) -> Q select db s (rel (QExpr (Sql92SelectTableExpressionSyntax (Sql92SelectSelectTableSyntax select)) s)) Source #

Introduce all entries of the given table which for which the expression (which can depend on the queried table returns true)

leftJoin_ :: forall s r select db. (Projectible (Sql92SelectExpressionSyntax select) r, IsSql92SelectSyntax select, ThreadRewritable (QNested s) r, Retaggable (QExpr (Sql92SelectExpressionSyntax select) s) (WithRewrittenThread (QNested s) s r)) => Q select db (QNested s) r -> (WithRewrittenThread (QNested s) s r -> QExpr (Sql92SelectExpressionSyntax select) s Bool) -> Q select db s (Retag Nullable (WithRewrittenThread (QNested s) s r)) Source #

Introduce a table using a left join. The ON clause is required here.Because this is not an inner join, the resulting table is made nullable. This means that each field that would normally have type 'QExpr x' will now have type 'QExpr (Maybe x)'.

perhaps_ :: forall s r select db. (Projectible (Sql92SelectExpressionSyntax select) r, IsSql92SelectSyntax select, ThreadRewritable (QNested s) r, Retaggable (QExpr (Sql92SelectExpressionSyntax select) s) (WithRewrittenThread (QNested s) s r)) => Q select db (QNested s) r -> Q select db s (Retag Nullable (WithRewrittenThread (QNested s) s r)) Source #

Introduce a table using a left join with no ON clause. Because this is not an inner join, the resulting table is made nullable. This means that each field that would normally have type 'QExpr x' will now have type 'QExpr (Maybe x)'.

subselect_ :: forall s r select db. (ThreadRewritable (QNested s) r, ProjectibleInSelectSyntax select r) => Q select db (QNested s) r -> Q select db s (WithRewrittenThread (QNested s) s r) Source #

references_ :: (IsSql92ExpressionSyntax expr, HasSqlValueSyntax (Sql92ExpressionValueSyntax expr) Bool, Table t) => PrimaryKey t (QGenExpr ctxt expr s) -> t (QGenExpr ctxt expr s) -> QGenExpr ctxt expr s Bool Source #

Generate an appropriate boolean QGenExpr comparing the given foreign key to the given table. Useful for creating join conditions.

nub_ :: (IsSql92SelectSyntax select, Projectible (Sql92SelectExpressionSyntax select) r) => Q select db s r -> Q select db s r Source #

Only return distinct values from a query

class SqlJustable a b | b -> a where Source #

Type class for things that can be nullable. This includes 'QExpr (Maybe a)', 'tbl (Nullable QExpr)', and 'PrimaryKey tbl (Nullable QExpr)'

Minimal complete definition

just_, nothing_

Methods

just_ :: a -> b Source #

Given something of type 'QExpr a', 'tbl QExpr', or 'PrimaryKey tbl QExpr', turn it into a 'QExpr (Maybe a)', 'tbl (Nullable QExpr)', or 'PrimaryKey t (Nullable QExpr)' respectively that contains the same values.

nothing_ :: b Source #

Return either a 'QExpr (Maybe x)' representing Nothing or a nullable Table or PrimaryKey filled with Nothing.

class IsSql92ExpressionSyntax syntax => SqlDeconstructMaybe syntax a nonNullA s | a s -> syntax, a -> nonNullA, a -> s, nonNullA -> s where Source #

Type class for anything which can be checked for null-ness. This includes 'QExpr (Maybe a)' as well as Tables or PrimaryKeys over 'Nullable QExpr'.

Minimal complete definition

isJust_, isNothing_, maybe_

Methods

isJust_ :: a -> QExpr syntax s Bool Source #

Returns a QExpr that evaluates to true when the first argument is not null

isNothing_ :: a -> QExpr syntax s Bool Source #

Returns a QExpr that evaluates to true when the first argument is null

maybe_ :: QExpr syntax s y -> (nonNullA -> QExpr syntax s y) -> a -> QExpr syntax s y Source #

Given an object (third argument) which may or may not be null, return the default value if null (first argument), or transform the value that could be null to yield the result of the expression (second argument)

Instances

(IsSql92ExpressionSyntax syntax, HasSqlValueSyntax (Sql92ExpressionValueSyntax syntax) Bool, Beamable t) => SqlDeconstructMaybe syntax (t (Nullable (QExpr syntax s))) (t (QExpr syntax s)) s Source # 

Methods

isJust_ :: t (Nullable (QExpr syntax s)) -> QExpr syntax s Bool Source #

isNothing_ :: t (Nullable (QExpr syntax s)) -> QExpr syntax s Bool Source #

maybe_ :: QExpr syntax s y -> (t (QExpr syntax s) -> QExpr syntax s y) -> t (Nullable (QExpr syntax s)) -> QExpr syntax s y Source #

IsSql92ExpressionSyntax syntax => SqlDeconstructMaybe syntax (QExpr syntax s (Maybe x)) (QExpr syntax s x) s Source # 

Methods

isJust_ :: QExpr syntax s (Maybe x) -> QExpr syntax s Bool Source #

isNothing_ :: QExpr syntax s (Maybe x) -> QExpr syntax s Bool Source #

maybe_ :: QExpr syntax s y -> (QExpr syntax s x -> QExpr syntax s y) -> QExpr syntax s (Maybe x) -> QExpr syntax s y Source #

class SqlOrderable syntax a | a -> syntax Source #

Minimal complete definition

makeSQLOrdering

Instances

SqlOrderable syntax a => SqlOrderable syntax [a] Source # 

Methods

makeSQLOrdering :: [a] -> [WithExprContext syntax]

(SqlOrderable syntax a, SqlOrderable syntax b) => SqlOrderable syntax (a, b) Source # 

Methods

makeSQLOrdering :: (a, b) -> [WithExprContext syntax]

(SqlOrderable syntax a, SqlOrderable syntax b, SqlOrderable syntax c) => SqlOrderable syntax (a, b, c) Source # 

Methods

makeSQLOrdering :: (a, b, c) -> [WithExprContext syntax]

SqlOrderable syntax (QOrd syntax s a) Source # 

Methods

makeSQLOrdering :: QOrd syntax s a -> [WithExprContext syntax]

(SqlOrderable syntax a, SqlOrderable syntax b, SqlOrderable syntax c, SqlOrderable syntax d) => SqlOrderable syntax (a, b, c, d) Source # 

Methods

makeSQLOrdering :: (a, b, c, d) -> [WithExprContext syntax]

(SqlOrderable syntax a, SqlOrderable syntax b, SqlOrderable syntax c, SqlOrderable syntax d, SqlOrderable syntax e) => SqlOrderable syntax (a, b, c, d, e) Source # 

Methods

makeSQLOrdering :: (a, b, c, d, e) -> [WithExprContext syntax]

(SqlOrderable syntax a, SqlOrderable syntax b, SqlOrderable syntax c, SqlOrderable syntax d, SqlOrderable syntax e, SqlOrderable syntax f) => SqlOrderable syntax (a, b, c, d, e, f) Source # 

Methods

makeSQLOrdering :: (a, b, c, d, e, f) -> [WithExprContext syntax]

(SqlOrderable syntax a, SqlOrderable syntax b, SqlOrderable syntax c, SqlOrderable syntax d, SqlOrderable syntax e, SqlOrderable syntax f, SqlOrderable syntax g) => SqlOrderable syntax (a, b, c, d, e, f, g) Source # 

Methods

makeSQLOrdering :: (a, b, c, d, e, f, g) -> [WithExprContext syntax]

(SqlOrderable syntax a, SqlOrderable syntax b, SqlOrderable syntax c, SqlOrderable syntax d, SqlOrderable syntax e, SqlOrderable syntax f, SqlOrderable syntax g, SqlOrderable syntax h) => SqlOrderable syntax (a, b, c, d, e, f, g, h) Source # 

Methods

makeSQLOrdering :: (a, b, c, d, e, f, g, h) -> [WithExprContext syntax]

data QIfCond context expr s a Source #

data QIfElse context expr s a Source #

limit_ :: forall s a select db. (ProjectibleInSelectSyntax select a, ThreadRewritable (QNested s) a) => Integer -> Q select db (QNested s) a -> Q select db s (WithRewrittenThread (QNested s) s a) Source #

Limit the number of results returned by a query.

offset_ :: forall s a select db. (ProjectibleInSelectSyntax select a, ThreadRewritable (QNested s) a) => Integer -> Q select db (QNested s) a -> Q select db s (WithRewrittenThread (QNested s) s a) Source #

Drop the first offset' results.

as_ :: forall a ctxt syntax s. QGenExpr ctxt syntax s a -> QGenExpr ctxt syntax s a Source #

Convenience function that allows you to use type applications to specify the result of a QGenExpr.

Useful to disambiguate the types of QGenExprs without having to provide a complete type signature. As an example, the countAll_ aggregate can return a result of any Integral type. Without further constraints, the type is ambiguous. You can use as_ to disambiguate the return type.

For example, this is ambiguous

aggregate_ (\_ -> countAll_) ..

But this is not

aggregate_ (\_ -> as_ @Int countAll_) ..

Subqueries

exists_ :: (IsSql92SelectSyntax select, HasQBuilder select, ProjectibleInSelectSyntax select a, Sql92ExpressionSelectSyntax (Sql92SelectTableExpressionSyntax (Sql92SelectSelectTableSyntax select)) ~ select) => Q select db s a -> QExpr (Sql92SelectTableExpressionSyntax (Sql92SelectSelectTableSyntax select)) s Bool Source #

Use the SQL EXISTS operator to determine if the given query returns any results

unique_ :: (IsSql92SelectSyntax select, HasQBuilder select, ProjectibleInSelectSyntax select a, Sql92ExpressionSelectSyntax (Sql92SelectTableExpressionSyntax (Sql92SelectSelectTableSyntax select)) ~ select) => Q select db s a -> QExpr (Sql92SelectTableExpressionSyntax (Sql92SelectSelectTableSyntax select)) s Bool Source #

Use the SQL UNIQUE operator to determine if the given query produces a unique result

distinct_ :: (IsSql99ExpressionSyntax (Sql92SelectExpressionSyntax select), HasQBuilder select, ProjectibleInSelectSyntax select a, Sql92ExpressionSelectSyntax (Sql92SelectTableExpressionSyntax (Sql92SelectSelectTableSyntax select)) ~ select) => Q select db s a -> QExpr (Sql92SelectTableExpressionSyntax (Sql92SelectSelectTableSyntax select)) s Bool Source #

Use the SQL99 DISTINCT operator to determine if the given query produces a distinct result

Set operations

Q values can be combined using a variety of set operations. See the manual section.

union_ :: forall select db s a. (IsSql92SelectSyntax select, Projectible (Sql92SelectTableExpressionSyntax (Sql92SelectSelectTableSyntax select)) a, ProjectibleInSelectSyntax select a, ThreadRewritable (QNested s) a) => Q select db (QNested s) a -> Q select db (QNested s) a -> Q select db s (WithRewrittenThread (QNested s) s a) Source #

SQL UNION operator

unionAll_ :: forall select db s a. (IsSql92SelectSyntax select, Projectible (Sql92SelectTableExpressionSyntax (Sql92SelectSelectTableSyntax select)) a, ProjectibleInSelectSyntax select a, ThreadRewritable (QNested s) a) => Q select db (QNested s) a -> Q select db (QNested s) a -> Q select db s (WithRewrittenThread (QNested s) s a) Source #

SQL UNION ALL operator

intersect_ :: forall select db s a. (IsSql92SelectSyntax select, Projectible (Sql92SelectTableExpressionSyntax (Sql92SelectSelectTableSyntax select)) a, ProjectibleInSelectSyntax select a, ThreadRewritable (QNested s) a) => Q select db (QNested s) a -> Q select db (QNested s) a -> Q select db s (WithRewrittenThread (QNested s) s a) Source #

SQL INTERSECT operator

intersectAll_ :: forall select db s a. (IsSql92SelectSyntax select, Projectible (Sql92SelectTableExpressionSyntax (Sql92SelectSelectTableSyntax select)) a, ProjectibleInSelectSyntax select a, ThreadRewritable (QNested s) a) => Q select db (QNested s) a -> Q select db (QNested s) a -> Q select db s (WithRewrittenThread (QNested s) s a) Source #

SQL INTERSECT ALL operator

except_ :: forall select db s a. (IsSql92SelectSyntax select, Projectible (Sql92SelectTableExpressionSyntax (Sql92SelectSelectTableSyntax select)) a, ProjectibleInSelectSyntax select a, ThreadRewritable (QNested s) a) => Q select db (QNested s) a -> Q select db (QNested s) a -> Q select db s (WithRewrittenThread (QNested s) s a) Source #

SQL EXCEPT operator

exceptAll_ :: forall select db s a. (IsSql92SelectSyntax select, Projectible (Sql92SelectTableExpressionSyntax (Sql92SelectSelectTableSyntax select)) a, ProjectibleInSelectSyntax select a, ThreadRewritable (QNested s) a) => Q select db (QNested s) a -> Q select db (QNested s) a -> Q select db s (WithRewrittenThread (QNested s) s a) Source #

SQL EXCEPT ALL operator

Window functions

See the corresponding manual section for more.

over_ :: IsSql2003ExpressionSyntax syntax => QAgg syntax s a -> QWindow (Sql2003ExpressionWindowFrameSyntax syntax) s -> QWindowExpr syntax s a Source #

Produce a window expression given an aggregate function and a window.

frame_ Source #

Specify a window frame with all the options

noOrder_ :: Maybe (QOrd syntax s Int) Source #

partitionBy_ :: partition -> Maybe partition Source #

orderPartitionBy_ :: partition -> Maybe partition Source #

withWindow_ Source #

Arguments

:: (ProjectibleWithPredicate WindowFrameContext (Sql2003ExpressionWindowFrameSyntax (Sql92SelectExpressionSyntax select)) window, Projectible (Sql92SelectExpressionSyntax select) r, Projectible (Sql92SelectExpressionSyntax select) a, ContextRewritable a, ThreadRewritable (QNested s) (WithRewrittenContext a QValueContext), IsSql92SelectSyntax select) 
=> (r -> window)

Window builder function

-> (r -> window -> a)

Projection builder function. Has access to the windows generated above

-> Q select db (QNested s) r

Query to window over

-> Q select db s (WithRewrittenThread (QNested s) s (WithRewrittenContext a QValueContext)) 

Compute a query over windows.

The first function builds window frames using the frame_, partitionBy_, etc functions. The return type can be a single frame, tuples of frame, or any arbitrarily nested tuple of the above. Instances up to 8-tuples are provided.

The second function builds the resulting projection using the result of the subquery as well as the window frames built in the first function. In this function, window expressions can be included in the output using the over_ function.

Ordering primitives

orderBy_ :: forall s a ordering syntax db. (Projectible (Sql92SelectExpressionSyntax syntax) a, SqlOrderable (Sql92SelectOrderingSyntax syntax) ordering, ThreadRewritable (QNested s) a) => (a -> ordering) -> Q syntax db (QNested s) a -> Q syntax db s (WithRewrittenThread (QNested s) s a) Source #

Order by the given expressions. The return type of the ordering key should either be the result of asc_ or desc_ (or another ordering QOrd generated by a backend-specific ordering) or an (possibly nested) tuple of results of the former.

The manual section has more information.

asc_ :: forall syntax s a. IsSql92OrderingSyntax syntax => QExpr (Sql92OrderingExpressionSyntax syntax) s a -> QOrd syntax s a Source #

Produce a QOrd corresponding to a SQL ASC ordering

desc_ :: forall syntax s a. IsSql92OrderingSyntax syntax => QExpr (Sql92OrderingExpressionSyntax syntax) s a -> QOrd syntax s a Source #

Produce a QOrd corresponding to a SQL DESC ordering

Various combinators corresponding to SQL extensions

T614 NTILE function

ntile_ :: (Integral a, IsSql2003NtileExpressionSyntax syntax) => QExpr syntax s Int -> QAgg syntax s a Source #

T615 LEAD and LAG function

lead1_ :: IsSql2003LeadAndLagExpressionSyntax syntax => QExpr syntax s a -> QAgg syntax s a Source #

lag1_ :: IsSql2003LeadAndLagExpressionSyntax syntax => QExpr syntax s a -> QAgg syntax s a Source #

lead_ :: IsSql2003LeadAndLagExpressionSyntax syntax => QExpr syntax s a -> QExpr syntax s Int -> QAgg syntax s a Source #

lag_ :: IsSql2003LeadAndLagExpressionSyntax syntax => QExpr syntax s a -> QExpr syntax s Int -> QAgg syntax s a Source #

leadWithDefault_ :: IsSql2003LeadAndLagExpressionSyntax syntax => QExpr syntax s a -> QExpr syntax s Int -> QExpr syntax s a -> QAgg syntax s a Source #

lagWithDefault_ :: IsSql2003LeadAndLagExpressionSyntax syntax => QExpr syntax s a -> QExpr syntax s Int -> QExpr syntax s a -> QAgg syntax s a Source #

T616 FIRST_VALUE and LAST_VALUE functions

T618 NTH_VALUE function

nthValue_ :: IsSql2003NthValueExpressionSyntax syntax => QExpr syntax s a -> QExpr syntax s Int -> QAgg syntax s a Source #

T621 Enhanced numeric functions

(**.) :: (Floating a, IsSql2003EnhancedNumericFunctionsExpressionSyntax syntax) => QGenExpr ctxt syntax s a -> QGenExpr ctxt syntax s a -> QGenExpr ctxt syntax s a infixr 8 Source #

ln_ :: (Floating a, IsSql2003EnhancedNumericFunctionsExpressionSyntax syntax) => QGenExpr ctxt syntax s a -> QGenExpr ctxt syntax s a Source #

exp_ :: (Floating a, IsSql2003EnhancedNumericFunctionsExpressionSyntax syntax) => QGenExpr ctxt syntax s a -> QGenExpr ctxt syntax s a Source #

sqrt_ :: (Floating a, IsSql2003EnhancedNumericFunctionsExpressionSyntax syntax) => QGenExpr ctxt syntax s a -> QGenExpr ctxt syntax s a Source #

floor_ :: (RealFrac a, Integral b, IsSql2003EnhancedNumericFunctionsExpressionSyntax syntax) => QGenExpr ctxt syntax s a -> QGenExpr ctxt syntax s b Source #

covarPop_ :: (Num a, Floating b, IsSql2003EnhancedNumericFunctionsAggregationExpressionSyntax syntax) => QExpr syntax s a -> QExpr syntax s a -> QExpr syntax s b Source #

corr_ :: (Num a, Floating b, IsSql2003EnhancedNumericFunctionsAggregationExpressionSyntax syntax) => QExpr syntax s a -> QExpr syntax s a -> QExpr syntax s b Source #

regrAvgX_ :: (Num a, Floating b, IsSql2003EnhancedNumericFunctionsAggregationExpressionSyntax syntax) => QExpr syntax s a -> QExpr syntax s a -> QExpr syntax s b Source #

regrAvgY_ :: (Num a, Floating b, IsSql2003EnhancedNumericFunctionsAggregationExpressionSyntax syntax) => QExpr syntax s a -> QExpr syntax s a -> QExpr syntax s b Source #

regrSXX_ :: (Num a, Floating b, IsSql2003EnhancedNumericFunctionsAggregationExpressionSyntax syntax) => QExpr syntax s a -> QExpr syntax s a -> QExpr syntax s b Source #

regrSYY_ :: (Num a, Floating b, IsSql2003EnhancedNumericFunctionsAggregationExpressionSyntax syntax) => QExpr syntax s a -> QExpr syntax s a -> QExpr syntax s b Source #

regrSXY_ :: (Num a, Floating b, IsSql2003EnhancedNumericFunctionsAggregationExpressionSyntax syntax) => QExpr syntax s a -> QExpr syntax s a -> QExpr syntax s b Source #

Relationships

Many-to-many relationships

type ManyToMany db left right = forall syntax s. (Sql92SelectSanityCheck syntax, IsSql92SelectSyntax syntax, SqlEq (QExpr (Sql92SelectExpressionSyntax syntax) s) (PrimaryKey left (QExpr (Sql92SelectExpressionSyntax syntax) s)), SqlEq (QExpr (Sql92SelectExpressionSyntax syntax) s) (PrimaryKey right (QExpr (Sql92SelectExpressionSyntax syntax) s))) => Q syntax db s (left (QExpr (Sql92SelectExpressionSyntax syntax) s)) -> Q syntax db s (right (QExpr (Sql92SelectExpressionSyntax syntax) s)) -> Q syntax db s (left (QExpr (Sql92SelectExpressionSyntax syntax) s), right (QExpr (Sql92SelectExpressionSyntax syntax) s)) Source #

Convenience type to declare many-to-many relationships. See the manual section on relationships for more information

type ManyToManyThrough db through left right = forall syntax s. (Sql92SelectSanityCheck syntax, IsSql92SelectSyntax syntax, SqlEq (QExpr (Sql92SelectExpressionSyntax syntax) s) (PrimaryKey left (QExpr (Sql92SelectExpressionSyntax syntax) s)), SqlEq (QExpr (Sql92SelectExpressionSyntax syntax) s) (PrimaryKey right (QExpr (Sql92SelectExpressionSyntax syntax) s))) => Q syntax db s (left (QExpr (Sql92SelectExpressionSyntax syntax) s)) -> Q syntax db s (right (QExpr (Sql92SelectExpressionSyntax syntax) s)) -> Q syntax db s (through (QExpr (Sql92SelectExpressionSyntax syntax) s), left (QExpr (Sql92SelectExpressionSyntax syntax) s), right (QExpr (Sql92SelectExpressionSyntax syntax) s)) Source #

Convenience type to declare many-to-many relationships with additional data. See the manual section on relationships for more information

manyToMany_ :: (Database db, Table joinThrough, Table left, Table right, Sql92SelectSanityCheck syntax, IsSql92SelectSyntax syntax, SqlEq (QExpr (Sql92SelectExpressionSyntax syntax) s) (PrimaryKey left (QExpr (Sql92SelectExpressionSyntax syntax) s)), SqlEq (QExpr (Sql92SelectExpressionSyntax syntax) s) (PrimaryKey right (QExpr (Sql92SelectExpressionSyntax syntax) s))) => DatabaseEntity be db (TableEntity joinThrough) -> (joinThrough (QExpr (Sql92SelectExpressionSyntax syntax) s) -> PrimaryKey left (QExpr (Sql92SelectExpressionSyntax syntax) s)) -> (joinThrough (QExpr (Sql92SelectExpressionSyntax syntax) s) -> PrimaryKey right (QExpr (Sql92SelectExpressionSyntax syntax) s)) -> Q syntax db s (left (QExpr (Sql92SelectExpressionSyntax syntax) s)) -> Q syntax db s (right (QExpr (Sql92SelectExpressionSyntax syntax) s)) -> Q syntax db s (left (QExpr (Sql92SelectExpressionSyntax syntax) s), right (QExpr (Sql92SelectExpressionSyntax syntax) s)) Source #

Used to define many-to-many relationships without any additional data. Takes the join table and two key extraction functions from that table to the related tables. Also takes two Qs representing the table sources to relate.

See the manual for more indformation.

manyToManyPassthrough_ :: (Database db, Table joinThrough, Table left, Table right, Sql92SelectSanityCheck syntax, IsSql92SelectSyntax syntax, SqlEq (QExpr (Sql92SelectExpressionSyntax syntax) s) (PrimaryKey left (QExpr (Sql92SelectExpressionSyntax syntax) s)), SqlEq (QExpr (Sql92SelectExpressionSyntax syntax) s) (PrimaryKey right (QExpr (Sql92SelectExpressionSyntax syntax) s))) => DatabaseEntity be db (TableEntity joinThrough) -> (joinThrough (QExpr (Sql92SelectExpressionSyntax syntax) s) -> PrimaryKey left (QExpr (Sql92SelectExpressionSyntax syntax) s)) -> (joinThrough (QExpr (Sql92SelectExpressionSyntax syntax) s) -> PrimaryKey right (QExpr (Sql92SelectExpressionSyntax syntax) s)) -> Q syntax db s (left (QExpr (Sql92SelectExpressionSyntax syntax) s)) -> Q syntax db s (right (QExpr (Sql92SelectExpressionSyntax syntax) s)) -> Q syntax db s (joinThrough (QExpr (Sql92SelectExpressionSyntax syntax) s), left (QExpr (Sql92SelectExpressionSyntax syntax) s), right (QExpr (Sql92SelectExpressionSyntax syntax) s)) Source #

Used to define many-to-many relationships with additional data. Takes the join table and two key extraction functions from that table to the related tables. Also takes two Qs representing the table sources to relate.

See the manual for more indformation.

One-to-many relationships

type OneToMany db s one many = forall syntax. (IsSql92SelectSyntax syntax, HasSqlValueSyntax (Sql92ExpressionValueSyntax (Sql92SelectExpressionSyntax syntax)) Bool) => one (QExpr (Sql92SelectExpressionSyntax syntax) s) -> Q syntax db s (many (QExpr (Sql92SelectExpressionSyntax syntax) s)) Source #

Convenience type to declare one-to-many relationships. See the manual section on relationships for more information

type OneToManyOptional db s tbl rel = forall syntax. (IsSql92SelectSyntax syntax, HasSqlValueSyntax (Sql92ExpressionValueSyntax (Sql92SelectExpressionSyntax syntax)) Bool, HasSqlValueSyntax (Sql92ExpressionValueSyntax (Sql92SelectExpressionSyntax syntax)) SqlNull) => tbl (QExpr (Sql92SelectExpressionSyntax syntax) s) -> Q syntax db s (rel (Nullable (QExpr (Sql92SelectExpressionSyntax syntax) s))) Source #

Convenience type to declare one-to-many relationships with a nullable foreign key. See the manual section on relationships for more information

oneToMany_ Source #

Arguments

:: (IsSql92SelectSyntax syntax, HasSqlValueSyntax (Sql92ExpressionValueSyntax (Sql92SelectExpressionSyntax syntax)) Bool, Database db, Table tbl, Table rel) 
=> DatabaseEntity be db (TableEntity rel)

Table to fetch (many)

-> (rel (QExpr (Sql92SelectExpressionSyntax syntax) s) -> PrimaryKey tbl (QExpr (Sql92SelectExpressionSyntax syntax) s))

Foreign key

-> tbl (QExpr (Sql92SelectExpressionSyntax syntax) s) 
-> Q syntax db s (rel (QExpr (Sql92SelectExpressionSyntax syntax) s)) 

Used to define one-to-many (or one-to-one) relationships. Takes the table to fetch, a way to extract the foreign key from that table, and the table to relate to.

oneToManyOptional_ Source #

Used to define one-to-many (or one-to-one) relationships with a nullable foreign key. Takes the table to fetch, a way to extract the foreign key from that table, and the table to relate to.

One-to-one relationshships

type OneToOne db s one many = OneToMany db s one many Source #

Synonym of OneToMany. Useful for giving more meaningful types, when the relationship is meant to be one-to-one.

type OneToMaybe db s tbl rel = OneToManyOptional db s tbl rel Source #

Synonym of OneToManyOptional. Useful for giving more meaningful types, when the relationship is meant to be one-to-one.

oneToOne_ Source #

Arguments

:: (IsSql92SelectSyntax syntax, HasSqlValueSyntax (Sql92ExpressionValueSyntax (Sql92SelectExpressionSyntax syntax)) Bool, Database db, Table tbl, Table rel) 
=> DatabaseEntity be db (TableEntity rel)

Table to fetch (many)

-> (rel (QExpr (Sql92SelectExpressionSyntax syntax) s) -> PrimaryKey tbl (QExpr (Sql92SelectExpressionSyntax syntax) s))

Foreign key

-> tbl (QExpr (Sql92SelectExpressionSyntax syntax) s) 
-> Q syntax db s (rel (QExpr (Sql92SelectExpressionSyntax syntax) s)) 

Used to define one-to-many (or one-to-one) relationships. Takes the table to fetch, a way to extract the foreign key from that table, and the table to relate to.

oneToMaybe_ Source #

Used to define one-to-many (or one-to-one) relationships with a nullable foreign key. Takes the table to fetch, a way to extract the foreign key from that table, and the table to relate to.

Operators

General-purpose operators

(&&.) :: IsSql92ExpressionSyntax syntax => QGenExpr context syntax s Bool -> QGenExpr context syntax s Bool -> QGenExpr context syntax s Bool infixr 3 Source #

SQL AND operator

(||.) :: IsSql92ExpressionSyntax syntax => QGenExpr context syntax s Bool -> QGenExpr context syntax s Bool -> QGenExpr context syntax s Bool infixr 2 Source #

SQL OR operator

not_ :: forall syntax context s. IsSql92ExpressionSyntax syntax => QGenExpr context syntax s Bool -> QGenExpr context syntax s Bool Source #

SQL NOT operator

div_ :: (Integral a, IsSql92ExpressionSyntax syntax) => QGenExpr context syntax s a -> QGenExpr context syntax s a -> QGenExpr context syntax s a Source #

SQL / operator

mod_ :: (Integral a, IsSql92ExpressionSyntax syntax) => QGenExpr context syntax s a -> QGenExpr context syntax s a -> QGenExpr context syntax s a Source #

SQL % operator

like_ :: (IsSqlExpressionSyntaxStringType syntax text, IsSql92ExpressionSyntax syntax) => QExpr syntax s text -> QExpr syntax s text -> QExpr syntax s Bool Source #

SQL LIKE operator

similarTo_ :: (IsSqlExpressionSyntaxStringType syntax text, IsSql99ExpressionSyntax syntax) => QExpr syntax s text -> QExpr syntax s text -> QExpr syntax s text Source #

SQL99 SIMILAR TO operator

isTrue_ :: IsSql92ExpressionSyntax syntax => QGenExpr context syntax s a -> QGenExpr context syntax s Bool Source #

SQL IS TRUE operator

isNotTrue_ :: IsSql92ExpressionSyntax syntax => QGenExpr context syntax s a -> QGenExpr context syntax s Bool Source #

SQL IS NOT TRUE operator

isFalse_ :: IsSql92ExpressionSyntax syntax => QGenExpr context syntax s a -> QGenExpr context syntax s Bool Source #

SQL IS FALSE operator

isNotFalse_ :: IsSql92ExpressionSyntax syntax => QGenExpr context syntax s a -> QGenExpr context syntax s Bool Source #

SQL IS NOT FALSE operator

isUnknown_ :: IsSql92ExpressionSyntax syntax => QGenExpr context syntax s a -> QGenExpr context syntax s Bool Source #

SQL IS UNKNOWN operator

isNotUnknown_ :: IsSql92ExpressionSyntax syntax => QGenExpr context syntax s a -> QGenExpr context syntax s Bool Source #

SQL IS NOT UNKNOWN operator

concat_ :: IsSql99ConcatExpressionSyntax syntax => [QGenExpr context syntax s Text] -> QGenExpr context syntax s Text Source #

SQL CONCAT function

Unquantified comparison operators

class SqlEq expr a | a -> expr where Source #

Class for expression types or expression containers for which there is a notion of equality.

Instances are provided to check the equality of expressions of the same type as well as entire Beamable types parameterized over QGenExpr

Minimal complete definition

(==.), (/=.)

Methods

(==.) :: a -> a -> expr Bool infix 4 Source #

Given two expressions, returns whether they are equal

(/=.) :: a -> a -> expr Bool infix 4 Source #

Given two expressions, returns whether they are not equal

Instances

(IsSql92ExpressionSyntax syntax, HasSqlValueSyntax (Sql92ExpressionValueSyntax syntax) Bool, Beamable tbl) => SqlEq (QGenExpr context syntax s) (tbl (Nullable (QGenExpr context syntax s))) Source # 

Methods

(==.) :: tbl (Nullable (QGenExpr context syntax s)) -> tbl (Nullable (QGenExpr context syntax s)) -> QGenExpr context syntax s Bool Source #

(/=.) :: tbl (Nullable (QGenExpr context syntax s)) -> tbl (Nullable (QGenExpr context syntax s)) -> QGenExpr context syntax s Bool Source #

(IsSql92ExpressionSyntax syntax, HasSqlValueSyntax (Sql92ExpressionValueSyntax syntax) Bool, Beamable tbl) => SqlEq (QGenExpr context syntax s) (tbl (QGenExpr context syntax s)) Source #

Compare two arbitrary Beamable types containing QGenExprs for equality.

Methods

(==.) :: tbl (QGenExpr context syntax s) -> tbl (QGenExpr context syntax s) -> QGenExpr context syntax s Bool Source #

(/=.) :: tbl (QGenExpr context syntax s) -> tbl (QGenExpr context syntax s) -> QGenExpr context syntax s Bool Source #

IsSql92ExpressionSyntax syntax => SqlEq (QGenExpr context syntax s) (QGenExpr context syntax s a) Source #

Compare two arbitrary expressions (of the same type) for equality

Methods

(==.) :: QGenExpr context syntax s a -> QGenExpr context syntax s a -> QGenExpr context syntax s Bool Source #

(/=.) :: QGenExpr context syntax s a -> QGenExpr context syntax s a -> QGenExpr context syntax s Bool Source #

class SqlEq expr e => SqlOrd expr e | e -> expr where Source #

Class for expression types or expression containers for which there is a notion of ordering.

Instances are provided to check the ordering of expressions of the same type. Since there is no universal notion of ordering for an arbitrary number of expressions, no instance is provided for Beamable types.

Minimal complete definition

(<.), (>.), (<=.), (>=.)

Methods

(<.), (>.), (<=.), (>=.) :: e -> e -> expr Bool infix 4 <., >., <=., >=. Source #

Instances

IsSql92ExpressionSyntax syntax => SqlOrd (QGenExpr context syntax s) (QGenExpr context syntax s a) Source # 

Methods

(<.) :: QGenExpr context syntax s a -> QGenExpr context syntax s a -> QGenExpr context syntax s Bool Source #

(>.) :: QGenExpr context syntax s a -> QGenExpr context syntax s a -> QGenExpr context syntax s Bool Source #

(<=.) :: QGenExpr context syntax s a -> QGenExpr context syntax s a -> QGenExpr context syntax s Bool Source #

(>=.) :: QGenExpr context syntax s a -> QGenExpr context syntax s a -> QGenExpr context syntax s Bool Source #

Quantified Comparison Operators

class SqlEq expr a => SqlEqQuantified expr quantified a | a -> expr quantified where Source #

Class for expression types for which there is a notion of quantified equality.

Minimal complete definition

(==*.), (/=*.)

Methods

(==*.), (/=*.) :: a -> quantified -> expr Bool infix 4 ==*., /=*. Source #

Instances

IsSql92ExpressionSyntax syntax => SqlEqQuantified (QGenExpr context syntax s) (QQuantified syntax s a) (QGenExpr context syntax s a) Source #

Two arbitrary expressions can be quantifiably compared for equality.

Methods

(==*.) :: QGenExpr context syntax s a -> QQuantified syntax s a -> QGenExpr context syntax s Bool Source #

(/=*.) :: QGenExpr context syntax s a -> QQuantified syntax s a -> QGenExpr context syntax s Bool Source #

class (SqlOrd expr e, SqlEqQuantified expr quantified e) => SqlOrdQuantified expr quantified e | e -> expr quantified where Source #

Class for things which can be quantifiably compared.

Minimal complete definition

(<*.), (>*.), (<=*.), (>=*.)

Methods

(<*.), (>*.), (<=*.), (>=*.) :: e -> quantified -> expr Bool infix 4 <*., >*., <=*., >=*. Source #

Instances

IsSql92ExpressionSyntax syntax => SqlOrdQuantified (QGenExpr context syntax s) (QQuantified syntax s a) (QGenExpr context syntax s a) Source # 

Methods

(<*.) :: QGenExpr context syntax s a -> QQuantified syntax s a -> QGenExpr context syntax s Bool Source #

(>*.) :: QGenExpr context syntax s a -> QQuantified syntax s a -> QGenExpr context syntax s Bool Source #

(<=*.) :: QGenExpr context syntax s a -> QQuantified syntax s a -> QGenExpr context syntax s Bool Source #

(>=*.) :: QGenExpr context syntax s a -> QQuantified syntax s a -> QGenExpr context syntax s Bool Source #

data QQuantified expr s r Source #

A data structure representing the set to quantify a comparison operator over.

Instances

IsSql92ExpressionSyntax syntax => SqlOrdQuantified (QGenExpr context syntax s) (QQuantified syntax s a) (QGenExpr context syntax s a) Source # 

Methods

(<*.) :: QGenExpr context syntax s a -> QQuantified syntax s a -> QGenExpr context syntax s Bool Source #

(>*.) :: QGenExpr context syntax s a -> QQuantified syntax s a -> QGenExpr context syntax s Bool Source #

(<=*.) :: QGenExpr context syntax s a -> QQuantified syntax s a -> QGenExpr context syntax s Bool Source #

(>=*.) :: QGenExpr context syntax s a -> QQuantified syntax s a -> QGenExpr context syntax s Bool Source #

IsSql92ExpressionSyntax syntax => SqlEqQuantified (QGenExpr context syntax s) (QQuantified syntax s a) (QGenExpr context syntax s a) Source #

Two arbitrary expressions can be quantifiably compared for equality.

Methods

(==*.) :: QGenExpr context syntax s a -> QQuantified syntax s a -> QGenExpr context syntax s Bool Source #

(/=*.) :: QGenExpr context syntax s a -> QQuantified syntax s a -> QGenExpr context syntax s Bool Source #

anyOf_ :: forall s r select expr db. (ThreadRewritable (QNested s) r, ProjectibleInSelectSyntax select r, IsSql92SelectSyntax select, IsSql92ExpressionSyntax expr, HasQBuilder select, Sql92ExpressionSelectSyntax expr ~ select) => Q select db (QNested s) r -> QQuantified expr s (WithRewrittenThread (QNested s) s r) Source #

A QQuantified representing a SQL ANY(..) for use with a quantified comparison operator

Accepts a subquery. Use anyIn_ for an explicit list

allOf_ :: forall s r select expr db. (ThreadRewritable (QNested s) r, ProjectibleInSelectSyntax select r, IsSql92SelectSyntax select, IsSql92ExpressionSyntax expr, HasQBuilder select, Sql92ExpressionSelectSyntax expr ~ select) => Q select db (QNested s) r -> QQuantified expr s (WithRewrittenThread (QNested s) s r) Source #

A QQuantified representing a SQL ALL(..) for use with a quantified comparison operator

Accepts a subquery. Use allIn_ for an explicit list

anyIn_ :: forall s a expr. IsSql92ExpressionSyntax expr => [QExpr expr s a] -> QQuantified expr s a Source #

A QQuantified representing a SQL ANY(..) for use with a quantified comparison operator

Accepts an explicit list of typed expressions. Use anyOf_ for a subquery

allIn_ :: forall s a expr. IsSql92ExpressionSyntax expr => [QExpr expr s a] -> QQuantified expr s a Source #

A QQuantified representing a SQL ALL(..) for use with a quantified comparison operator

Accepts an explicit list of typed expressions. Use allOf_ for a subquery

between_ :: IsSql92ExpressionSyntax syntax => QGenExpr context syntax s a -> QGenExpr context syntax s a -> QGenExpr context syntax s a -> QGenExpr context syntax s Bool Source #

SQL BETWEEN clause

in_ :: (IsSql92ExpressionSyntax syntax, HasSqlValueSyntax (Sql92ExpressionValueSyntax syntax) Bool) => QGenExpr context syntax s a -> [QGenExpr context syntax s a] -> QGenExpr context syntax s Bool Source #

SQL IN predicate

Aggregates

See the corresponding manual section for more detail

aggregate_ Source #

Compute an aggregate over a query.

The supplied aggregate projection should return an aggregate expression (an expression containing an aggregate function such as count_, sum_, countAll_, etc), a grouping key (specified with the group_ function), or a combination of tuples of the above.

Appropriate instances are provided up to 8-tuples.

Semantically, all grouping expressions in the projection will be added to a SQL GROUP BY clause and all aggregate expressions will be computed.

The return value will be the type of the aggregate projection, but transformed to be in the normal value context (i.e., everything will become QExprs).

For usage examples, see the manual.

filterWhere_ :: IsSql2003ExpressionElementaryOLAPOperationsSyntax expr => QAgg expr s a -> QExpr expr s Bool -> QAgg expr s a Source #

Support for FILTER (WHERE ...) syntax for aggregates. Part of SQL2003 Advanced OLAP operations feature (T612)

class QGroupable expr grouped | expr -> grouped, grouped -> expr where Source #

Type class for grouping keys. expr is the type of the grouping key after projection. grouped is the type of the grouping key in the aggregate expression (usually something that contains QGenExprs in the QGroupingContext).

Minimal complete definition

group_

Methods

group_ :: expr -> grouped Source #

Instances

Beamable tbl => QGroupable (tbl (QExpr expr s)) (tbl (QGroupExpr expr s)) Source #

group_ for any Beamable type. Adds every field in the type to the grouping key. This is the equivalent of including the grouping expression of each field in the type as part of the aggregate projection

Methods

group_ :: tbl (QExpr expr s) -> tbl (QGroupExpr expr s) Source #

QGroupable (QExpr expr s a) (QGroupExpr expr s a) Source #

group_ for simple value expressions.

Methods

group_ :: QExpr expr s a -> QGroupExpr expr s a Source #

General-purpose aggregate functions

sum_ :: (IsSql92AggregationExpressionSyntax expr, Num a) => QExpr expr s a -> QAgg expr s a Source #

SQL SUM(ALL ..) function (but without the explicit ALL)

avg_ :: (IsSql92AggregationExpressionSyntax expr, Num a) => QExpr expr s a -> QAgg expr s a Source #

SQL AVG(ALL ..) function (but without the explicit ALL)

min_ :: IsSql92AggregationExpressionSyntax expr => QExpr expr s a -> QAgg expr s a Source #

SQL MIN(ALL ..) function (but without the explicit ALL)

max_ :: IsSql92AggregationExpressionSyntax expr => QExpr expr s a -> QAgg expr s a Source #

SQL MAX(ALL ..) function (but without the explicit ALL)

count_ :: (IsSql92AggregationExpressionSyntax expr, Integral b) => QExpr expr s a -> QAgg expr s b Source #

SQL COUNT(ALL ..) function (but without the explicit ALL)

countAll_ :: IsSql92AggregationExpressionSyntax expr => QAgg expr s Int Source #

SQL COUNT(*) function

rank_ :: IsSql2003ExpressionElementaryOLAPOperationsSyntax expr => QAgg expr s Int Source #

SQL2003 RANK function (Requires T611 Elementary OLAP operations support)

cumeDist_ :: IsSql2003ExpressionAdvancedOLAPOperationsSyntax expr => QAgg expr s Double Source #

SQL2003 CUME_DIST function (Requires T612 Advanced OLAP operations support)

percentRank_ :: IsSql2003ExpressionAdvancedOLAPOperationsSyntax expr => QAgg expr s Double Source #

SQL2003 PERCENT_RANK function (Requires T612 Advanced OLAP operations support)

every_ :: IsSql99AggregationExpressionSyntax expr => QExpr expr s Bool -> QAgg expr s Bool Source #

SQL99 EVERY(ALL ..) function (but without the explicit ALL)

any_ :: IsSql99AggregationExpressionSyntax expr => QExpr expr s Bool -> QAgg expr s Bool Source #

SQL99 ANY(ALL ..) function (but without the explicit ALL)

some_ :: IsSql99AggregationExpressionSyntax expr => QExpr expr s Bool -> QAgg expr s Bool Source #

SQL99 SOME(ALL ..) function (but without the explicit ALL)

Quantified aggregate functions

These functions correspond one-to-one with the <#gp-agg-funcs general-purpose aggregate functions>. However, they each take a mandatory "set quantifier", which is any of the set quantifier values.

Set quantifiers

distinctInGroup_ :: IsSql92AggregationSetQuantifierSyntax s => Maybe s Source #

Compute an aggregate only over distinct values in a group. Corresponds to the AGG(DISTINCT ..) syntax.

allInGroup_ :: IsSql92AggregationSetQuantifierSyntax s => Maybe s Source #

Compute an aggregate over all values in a group. Corresponds semantically to the AGG(ALL ..) syntax, but doesn't produce an explicit ALL. To produce ALL expicitly, see allInGroupExplicitly_.

allInGroupExplicitly_ :: IsSql92AggregationSetQuantifierSyntax s => Maybe s Source #

Compute an aggregate over all values in a group. Corresponds to the AGG(ALL ..) syntax. Note that ALL is the default for most aggregations, so you don't normally explicitly specify ALL. However, if you need to, you can use this function. To be explicit about quantification in the beam query DSL, but not produce an explicit ALL, use allInGroup_. allInGroup_ has the same semantic meaning, but does not produce an explicit ALL.

SQL Command construction and execution

SELECT

newtype SqlSelect select a Source #

Represents a select statement over the syntax select that will return rows of type a.

Constructors

SqlSelect select 

select :: forall syntax db res. (ProjectibleInSelectSyntax syntax res, IsSql92SelectSyntax syntax, HasQBuilder syntax) => Q syntax db QueryInaccessible res -> SqlSelect syntax (QExprToIdentity res) Source #

Build a SqlSelect for the given Q.

lookup :: (HasQBuilder syntax, Sql92SelectSanityCheck syntax, SqlValableTable (PrimaryKey table) (Sql92SelectExpressionSyntax syntax), HasSqlValueSyntax (Sql92ExpressionValueSyntax (Sql92SelectExpressionSyntax syntax)) Bool, Beamable table, Table table, Database db) => DatabaseEntity be db (TableEntity table) -> PrimaryKey table Identity -> SqlSelect syntax (table Identity) Source #

Convenience function to generate a SqlSelect that looks up a table row given a primary key.

runSelectReturningList :: (IsSql92Syntax cmd, MonadBeam cmd be hdl m, FromBackendRow be a) => SqlSelect (Sql92SelectSyntax cmd) a -> m [a] Source #

Run a SqlSelect in a MonadBeam and get the results as a list

runSelectReturningOne :: (IsSql92Syntax cmd, MonadBeam cmd be hdl m, FromBackendRow be a) => SqlSelect (Sql92SelectSyntax cmd) a -> m (Maybe a) Source #

Run a SqlSelect in a MonadBeam and get the unique result, if there is one. Both no results as well as more than one result cause this to return Nothing.

dumpSqlSelect :: ProjectibleInSelectSyntax SqlSyntaxBuilder res => Q SqlSyntaxBuilder db QueryInaccessible res -> IO () Source #

Use a special debug syntax to print out an ANSI Standard SELECT statement that may be generated for a given Q.

INSERT

newtype SqlInsert syntax Source #

Represents a SQL INSERT command that has not yet been run

Constructors

SqlInsert syntax 

insert Source #

Arguments

:: IsSql92InsertSyntax syntax 
=> DatabaseEntity be db (TableEntity table)

Table to insert into

-> SqlInsertValues (Sql92InsertValuesSyntax syntax) table

Values to insert. See insertValues, insertExpressions, and insertFrom for possibilities.

-> SqlInsert syntax 

Generate a SqlInsert given a table and a source of values.

runInsert :: (IsSql92Syntax cmd, MonadBeam cmd be hdl m) => SqlInsert (Sql92InsertSyntax cmd) -> m () Source #

Run a SqlInsert in a MonadBeam

newtype SqlInsertValues insertValues (tbl :: (* -> *) -> *) Source #

Represents a source of values that can be inserted into a table shaped like tbl.

Constructors

SqlInsertValues insertValues 

insertExpressions :: forall syntax table. (Beamable table, IsSql92InsertValuesSyntax syntax) => (forall s. [table (QExpr (Sql92InsertValuesExpressionSyntax syntax) s)]) -> SqlInsertValues syntax table Source #

Build a SqlInsertValues from series of expressions

insertValues :: forall table syntax. (Beamable table, IsSql92InsertValuesSyntax syntax, FieldsFulfillConstraint (HasSqlValueSyntax (Sql92ExpressionValueSyntax (Sql92InsertValuesExpressionSyntax syntax))) table) => [table Identity] -> SqlInsertValues syntax table Source #

Build a SqlInsertValues from concrete table values

insertFrom :: IsSql92InsertValuesSyntax syntax => SqlSelect (Sql92InsertValuesSelectSyntax syntax) (table Identity) -> SqlInsertValues syntax table Source #

Build a SqlInsertValues from a SqlSelect that returns the same table

UPDATE

newtype SqlUpdate syntax (table :: (* -> *) -> *) Source #

Represents a SQL UPDATE statement for the given table.

Constructors

SqlUpdate syntax 

update Source #

Arguments

:: (Beamable table, IsSql92UpdateSyntax syntax) 
=> DatabaseEntity be db (TableEntity table)

The table to insert into

-> (forall s. table (QField s) -> [QAssignment (Sql92UpdateFieldNameSyntax syntax) (Sql92UpdateExpressionSyntax syntax) s])

A sequence of assignments to make.

-> (forall s. table (QExpr (Sql92UpdateExpressionSyntax syntax) s) -> QExpr (Sql92UpdateExpressionSyntax syntax) s Bool)

Build a WHERE clause given a table containing expressions

-> SqlUpdate syntax table 

Build a SqlUpdate given a table, a list of assignments, and a way to build a WHERE clause.

See the '(<-.)' operator for ways to build assignments. The argument to the second argument is a the table parameterized over QField, which represents the left hand side of assignments. Sometimes, you'd like to also get the current value of a particular column. You can use the current_ function to convert a QField to a QExpr.

save Source #

Arguments

:: (Table table, IsSql92UpdateSyntax syntax, SqlValableTable (PrimaryKey table) (Sql92UpdateExpressionSyntax syntax), SqlValableTable table (Sql92UpdateExpressionSyntax syntax), HasSqlValueSyntax (Sql92ExpressionValueSyntax (Sql92UpdateExpressionSyntax syntax)) Bool) 
=> DatabaseEntity be db (TableEntity table)

Table to update

-> table Identity

Value to set to

-> SqlUpdate syntax table 

Generate a SqlUpdate that will update the given table with the given value.

The SQL UPDATE that is generated will set every non-primary key field for the row where each primary key field is exactly what is given.

Note: This is a pure SQL UPDATE command. This does not upsert or merge values.

runUpdate :: (IsSql92Syntax cmd, MonadBeam cmd be hdl m) => SqlUpdate (Sql92UpdateSyntax cmd) tbl -> m () Source #

Run a SqlUpdate in a MonadBeam.

DELETE

newtype SqlDelete syntax (table :: (* -> *) -> *) Source #

Represents a SQL DELETE statement for the given table

Constructors

SqlDelete syntax 

delete Source #

Arguments

:: IsSql92DeleteSyntax delete 
=> DatabaseEntity be db (TableEntity table)

Table to delete from

-> (forall s. table (QExpr (Sql92DeleteExpressionSyntax delete) s) -> QExpr (Sql92DeleteExpressionSyntax delete) s Bool)

Build a WHERE clause given a table containing expressions

-> SqlDelete delete table 

Build a SqlDelete from a table and a way to build a WHERE clause

runDelete :: (IsSql92Syntax cmd, MonadBeam cmd be hdl m) => SqlDelete (Sql92DeleteSyntax cmd) table -> m () Source #

Run a SqlDelete in a MonadBeam