| Copyright | (c) Eitan Chatav 2017 |
|---|---|
| Maintainer | eitan@morphism.tech |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
Squeal.PostgreSQL.Query
Contents
Description
Squeal queries.
Synopsis
- newtype Query (schema :: SchemaType) (params :: [NullityType]) (columns :: RowType) = UnsafeQuery {}
- select :: SListI columns => NP (Aliased (Expression schema from grouping params)) (column ': columns) -> TableExpression schema params from grouping -> Query schema params (column ': columns)
- selectDistinct :: SListI columns => NP (Aliased (Expression schema from Ungrouped params)) (column ': columns) -> TableExpression schema params from Ungrouped -> Query schema params (column ': columns)
- selectStar :: HasUnique table from columns => TableExpression schema params from Ungrouped -> Query schema params columns
- selectDistinctStar :: HasUnique table from columns => TableExpression schema params from Ungrouped -> Query schema params columns
- selectDotStar :: Has table from columns => Alias table -> TableExpression schema params from Ungrouped -> Query schema params columns
- selectDistinctDotStar :: Has table from columns => Alias table -> TableExpression schema params from Ungrouped -> Query schema params columns
- values :: SListI cols => NP (Aliased (Expression schema '[] Ungrouped params)) cols -> [NP (Aliased (Expression schema '[] Ungrouped params)) cols] -> Query schema params cols
- values_ :: SListI cols => NP (Aliased (Expression schema '[] Ungrouped params)) cols -> Query schema params cols
- union :: Query schema params columns -> Query schema params columns -> Query schema params columns
- unionAll :: Query schema params columns -> Query schema params columns -> Query schema params columns
- intersect :: Query schema params columns -> Query schema params columns -> Query schema params columns
- intersectAll :: Query schema params columns -> Query schema params columns -> Query schema params columns
- except :: Query schema params columns -> Query schema params columns -> Query schema params columns
- exceptAll :: Query schema params columns -> Query schema params columns -> Query schema params columns
- class With statement where
- data CommonTableExpression statement (params :: [NullityType]) (schema0 :: SchemaType) (schema1 :: SchemaType) where
- CommonTableExpression :: Aliased (statement schema params) (alias ::: cte) -> CommonTableExpression statement params schema ((alias ::: View cte) ': schema)
- renderCommonTableExpression :: (forall sch ps row. statement ps sch row -> ByteString) -> CommonTableExpression statement params schema0 schema1 -> ByteString
- renderCommonTableExpressions :: (forall sch ps row. statement ps sch row -> ByteString) -> CommonTableExpression statement params schema0 schema1 -> AlignedList (CommonTableExpression statement params) schema1 schema2 -> ByteString
- jsonEach :: Expression schema '[] Ungrouped params (nullity PGjson) -> Query schema params '["key" ::: NotNull PGtext, "value" ::: NotNull PGjson]
- jsonbEach :: Expression schema '[] Ungrouped params (nullity PGjsonb) -> Query schema params '["key" ::: NotNull PGtext, "value" ::: NotNull PGjsonb]
- jsonEachAsText :: Expression schema '[] Ungrouped params (nullity PGjson) -> Query schema params '["key" ::: NotNull PGtext, "value" ::: NotNull PGtext]
- jsonbEachAsText :: Expression schema '[] Ungrouped params (nullity PGjsonb) -> Query schema params '["key" ::: NotNull PGtext, "value" ::: NotNull PGtext]
- jsonObjectKeys :: Expression schema '[] Ungrouped params (nullity PGjson) -> Query schema params '["json_object_keys" ::: NotNull PGtext]
- jsonbObjectKeys :: Expression schema '[] Ungrouped params (nullity PGjsonb) -> Query schema params '["jsonb_object_keys" ::: NotNull PGtext]
- jsonPopulateRecord :: TypeExpression schema (nullity (PGcomposite row)) -> Expression schema '[] Ungrouped params (nullity PGjson) -> Query schema params row
- jsonbPopulateRecord :: TypeExpression schema (nullity (PGcomposite row)) -> Expression schema '[] Ungrouped params (nullity PGjsonb) -> Query schema params row
- jsonPopulateRecordSet :: TypeExpression schema (nullity (PGcomposite row)) -> Expression schema '[] Ungrouped params (nullity PGjson) -> Query schema params row
- jsonbPopulateRecordSet :: TypeExpression schema (nullity (PGcomposite row)) -> Expression schema '[] Ungrouped params (nullity PGjsonb) -> Query schema params row
- jsonToRecord :: SListI record => Expression schema '[] Ungrouped params (nullity PGjson) -> NP (Aliased (TypeExpression schema)) record -> Query schema params record
- jsonbToRecord :: SListI record => Expression schema '[] Ungrouped params (nullity PGjsonb) -> NP (Aliased (TypeExpression schema)) record -> Query schema params record
- jsonToRecordSet :: SListI record => Expression schema '[] Ungrouped params (nullity PGjson) -> NP (Aliased (TypeExpression schema)) record -> Query schema params record
- jsonbToRecordSet :: SListI record => Expression schema '[] Ungrouped params (nullity PGjsonb) -> NP (Aliased (TypeExpression schema)) record -> Query schema params record
- data TableExpression (schema :: SchemaType) (params :: [NullityType]) (from :: FromType) (grouping :: Grouping) = TableExpression {
- fromClause :: FromClause schema params from
- whereClause :: [Condition schema from Ungrouped params]
- groupByClause :: GroupByClause from grouping
- havingClause :: HavingClause schema from grouping params
- orderByClause :: [SortExpression schema from grouping params]
- limitClause :: [Word64]
- offsetClause :: [Word64]
- renderTableExpression :: TableExpression schema params from grouping -> ByteString
- from :: FromClause schema params from -> TableExpression schema params from Ungrouped
- where_ :: Condition schema from Ungrouped params -> TableExpression schema params from grouping -> TableExpression schema params from grouping
- groupBy :: SListI bys => NP (By from) bys -> TableExpression schema params from Ungrouped -> TableExpression schema params from (Grouped bys)
- having :: Condition schema from (Grouped bys) params -> TableExpression schema params from (Grouped bys) -> TableExpression schema params from (Grouped bys)
- orderBy :: [SortExpression schema from grouping params] -> TableExpression schema params from grouping -> TableExpression schema params from grouping
- limit :: Word64 -> TableExpression schema params from grouping -> TableExpression schema params from grouping
- offset :: Word64 -> TableExpression schema params from grouping -> TableExpression schema params from grouping
- newtype FromClause schema params from = UnsafeFromClause {}
- table :: Has tab schema (Table table) => Aliased Alias (alias ::: tab) -> FromClause schema params '[alias ::: TableToRow table]
- subquery :: Aliased (Query schema params) rel -> FromClause schema params '[rel]
- view :: Has view schema (View row) => Aliased Alias (alias ::: view) -> FromClause schema params '[alias ::: row]
- crossJoin :: FromClause schema params right -> FromClause schema params left -> FromClause schema params (Join left right)
- innerJoin :: FromClause schema params right -> Condition schema (Join left right) Ungrouped params -> FromClause schema params left -> FromClause schema params (Join left right)
- leftOuterJoin :: FromClause schema params right -> Condition schema (Join left right) Ungrouped params -> FromClause schema params left -> FromClause schema params (Join left (NullifyFrom right))
- rightOuterJoin :: FromClause schema params right -> Condition schema (Join left right) Ungrouped params -> FromClause schema params left -> FromClause schema params (Join (NullifyFrom left) right)
- fullOuterJoin :: FromClause schema params right -> Condition schema (Join left right) Ungrouped params -> FromClause schema params left -> FromClause schema params (Join (NullifyFrom left) (NullifyFrom right))
- data By (from :: FromType) (by :: (Symbol, Symbol)) where
- renderBy :: By from by -> ByteString
- data GroupByClause from grouping where
- NoGroups :: GroupByClause from Ungrouped
- Group :: SListI bys => NP (By from) bys -> GroupByClause from (Grouped bys)
- renderGroupByClause :: GroupByClause from grouping -> ByteString
- data HavingClause schema from grouping params where
- NoHaving :: HavingClause schema from Ungrouped params
- Having :: [Condition schema from (Grouped bys) params] -> HavingClause schema from (Grouped bys) params
- renderHavingClause :: HavingClause schema from grouping params -> ByteString
- data SortExpression schema from grouping params where
- Asc :: Expression schema from grouping params (NotNull ty) -> SortExpression schema from grouping params
- Desc :: Expression schema from grouping params (NotNull ty) -> SortExpression schema from grouping params
- AscNullsFirst :: Expression schema from grouping params (Null ty) -> SortExpression schema from grouping params
- AscNullsLast :: Expression schema from grouping params (Null ty) -> SortExpression schema from grouping params
- DescNullsFirst :: Expression schema from grouping params (Null ty) -> SortExpression schema from grouping params
- DescNullsLast :: Expression schema from grouping params (Null ty) -> SortExpression schema from grouping params
- renderSortExpression :: SortExpression schema from grouping params -> ByteString
- in_ :: Expression schema from grp params ty -> Query schema params '[alias ::: ty] -> Expression schema from grp params (nullity PGbool)
- rowIn :: SListI row => NP (Aliased (Expression schema from grp params)) row -> Query schema params row -> Expression schema from grp params (nullity PGbool)
- eqAll :: Expression schema from grp params ty -> Query schema params '[alias ::: ty] -> Expression schema from grp params (nullity PGbool)
- rowEqAll :: SListI row => NP (Aliased (Expression schema from grp params)) row -> Query schema params row -> Expression schema from grp params (nullity PGbool)
- eqAny :: Expression schema from grp params ty -> Query schema params '[alias ::: ty] -> Expression schema from grp params (nullity PGbool)
- rowEqAny :: SListI row => NP (Aliased (Expression schema from grp params)) row -> Query schema params row -> Expression schema from grp params (nullity PGbool)
- neqAll :: Expression schema from grp params ty -> Query schema params '[alias ::: ty] -> Expression schema from grp params (nullity PGbool)
- rowNeqAll :: SListI row => NP (Aliased (Expression schema from grp params)) row -> Query schema params row -> Expression schema from grp params (nullity PGbool)
- neqAny :: Expression schema from grp params ty -> Query schema params '[alias ::: ty] -> Expression schema from grp params (nullity PGbool)
- rowNeqAny :: SListI row => NP (Aliased (Expression schema from grp params)) row -> Query schema params row -> Expression schema from grp params (nullity PGbool)
- allLt :: Expression schema from grp params ty -> Query schema params '[alias ::: ty] -> Expression schema from grp params (nullity PGbool)
- rowLtAll :: SListI row => NP (Aliased (Expression schema from grp params)) row -> Query schema params row -> Expression schema from grp params (nullity PGbool)
- ltAny :: Expression schema from grp params ty -> Query schema params '[alias ::: ty] -> Expression schema from grp params (nullity PGbool)
- rowLtAny :: SListI row => NP (Aliased (Expression schema from grp params)) row -> Query schema params row -> Expression schema from grp params (nullity PGbool)
- lteAll :: Expression schema from grp params ty -> Query schema params '[alias ::: ty] -> Expression schema from grp params (nullity PGbool)
- rowLteAll :: SListI row => NP (Aliased (Expression schema from grp params)) row -> Query schema params row -> Expression schema from grp params (nullity PGbool)
- lteAny :: Expression schema from grp params ty -> Query schema params '[alias ::: ty] -> Expression schema from grp params (nullity PGbool)
- rowLteAny :: SListI row => NP (Aliased (Expression schema from grp params)) row -> Query schema params row -> Expression schema from grp params (nullity PGbool)
- gtAll :: Expression schema from grp params ty -> Query schema params '[alias ::: ty] -> Expression schema from grp params (nullity PGbool)
- rowGtAll :: SListI row => NP (Aliased (Expression schema from grp params)) row -> Query schema params row -> Expression schema from grp params (nullity PGbool)
- gtAny :: Expression schema from grp params ty -> Query schema params '[alias ::: ty] -> Expression schema from grp params (nullity PGbool)
- rowGtAny :: SListI row => NP (Aliased (Expression schema from grp params)) row -> Query schema params row -> Expression schema from grp params (nullity PGbool)
- gteAll :: Expression schema from grp params ty -> Query schema params '[alias ::: ty] -> Expression schema from grp params (nullity PGbool)
- rowGteAll :: SListI row => NP (Aliased (Expression schema from grp params)) row -> Query schema params row -> Expression schema from grp params (nullity PGbool)
- gteAny :: Expression schema from grp params ty -> Query schema params '[alias ::: ty] -> Expression schema from grp params (nullity PGbool)
- rowGteAny :: SListI row => NP (Aliased (Expression schema from grp params)) row -> Query schema params row -> Expression schema from grp params (nullity PGbool)
Queries
newtype Query (schema :: SchemaType) (params :: [NullityType]) (columns :: RowType) Source #
The process of retrieving or the command to retrieve data from a database
is called a Query. Let's see some examples of queries.
simple query:
>>>:{let query :: Query '["tab" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'Null 'PGint4])] '[] '["col" ::: 'Null 'PGint4] query = selectStar (from (table #tab)) in printSQL query :} SELECT * FROM "tab" AS "tab"
restricted query:
>>>:{let query :: Query '[ "tab" ::: 'Table ('[] :=> '[ "col1" ::: 'NoDef :=> 'NotNull 'PGint4 , "col2" ::: 'NoDef :=> 'NotNull 'PGint4 ])] '[] '[ "sum" ::: 'NotNull 'PGint4 , "col1" ::: 'NotNull 'PGint4 ] query = select ((#col1 + #col2) `as` #sum :* #col1) ( from (table #tab) & where_ (#col1 .> #col2) & where_ (#col2 .> 0) ) in printSQL query :} SELECT ("col1" + "col2") AS "sum", "col1" AS "col1" FROM "tab" AS "tab" WHERE (("col1" > "col2") AND ("col2" > 0))
subquery:
>>>:{let query :: Query '["tab" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'Null 'PGint4])] '[] '["col" ::: 'Null 'PGint4] query = selectStar (from (subquery (selectStar (from (table #tab)) `as` #sub))) in printSQL query :} SELECT * FROM (SELECT * FROM "tab" AS "tab") AS "sub"
limits and offsets:
>>>:{let query :: Query '["tab" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'Null 'PGint4])] '[] '["col" ::: 'Null 'PGint4] query = selectStar (from (table #tab) & limit 100 & offset 2 & limit 50 & offset 2) in printSQL query :} SELECT * FROM "tab" AS "tab" LIMIT 50 OFFSET 4
parameterized query:
>>>:{let query :: Query '["tab" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'NotNull 'PGfloat8])] '[ 'NotNull 'PGfloat8] '["col" ::: 'NotNull 'PGfloat8] query = selectStar (from (table #tab) & where_ (#col .> param @1)) in printSQL query :} SELECT * FROM "tab" AS "tab" WHERE ("col" > ($1 :: float8))
aggregation query:
>>>:{let query :: Query '[ "tab" ::: 'Table ('[] :=> '[ "col1" ::: 'NoDef :=> 'NotNull 'PGint4 , "col2" ::: 'NoDef :=> 'NotNull 'PGint4 ])] '[] '[ "sum" ::: 'NotNull 'PGint4 , "col1" ::: 'NotNull 'PGint4 ] query = select (sum_ #col2 `as` #sum :* #col1) ( from (table (#tab `as` #table1)) & groupBy #col1 & having (#col1 + sum_ #col2 .> 1) ) in printSQL query :} SELECT sum("col2") AS "sum", "col1" AS "col1" FROM "tab" AS "table1" GROUP BY "col1" HAVING (("col1" + sum("col2")) > 1)
sorted query:
>>>:{let query :: Query '["tab" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'Null 'PGint4])] '[] '["col" ::: 'Null 'PGint4] query = selectStar (from (table #tab) & orderBy [#col & AscNullsFirst]) in printSQL query :} SELECT * FROM "tab" AS "tab" ORDER BY "col" ASC NULLS FIRST
joins:
>>>:set -XFlexibleContexts>>>:{let query :: Query '[ "orders" ::: 'Table ( '["pk_orders" ::: PrimaryKey '["id"] ,"fk_customers" ::: ForeignKey '["customer_id"] "customers" '["id"] ,"fk_shippers" ::: ForeignKey '["shipper_id"] "shippers" '["id"]] :=> '[ "id" ::: 'NoDef :=> 'NotNull 'PGint4 , "price" ::: 'NoDef :=> 'NotNull 'PGfloat4 , "customer_id" ::: 'NoDef :=> 'NotNull 'PGint4 , "shipper_id" ::: 'NoDef :=> 'NotNull 'PGint4 ]) , "customers" ::: 'Table ( '["pk_customers" ::: PrimaryKey '["id"]] :=> '[ "id" ::: 'NoDef :=> 'NotNull 'PGint4 , "name" ::: 'NoDef :=> 'NotNull 'PGtext ]) , "shippers" ::: 'Table ( '["pk_shippers" ::: PrimaryKey '["id"]] :=> '[ "id" ::: 'NoDef :=> 'NotNull 'PGint4 , "name" ::: 'NoDef :=> 'NotNull 'PGtext ]) ] '[] '[ "order_price" ::: 'NotNull 'PGfloat4 , "customer_name" ::: 'NotNull 'PGtext , "shipper_name" ::: 'NotNull 'PGtext ] query = select ( #o ! #price `as` #order_price :* #c ! #name `as` #customer_name :* #s ! #name `as` #shipper_name ) ( from (table (#orders `as` #o) & innerJoin (table (#customers `as` #c)) (#o ! #customer_id .== #c ! #id) & innerJoin (table (#shippers `as` #s)) (#o ! #shipper_id .== #s ! #id)) ) in printSQL query :} SELECT "o"."price" AS "order_price", "c"."name" AS "customer_name", "s"."name" AS "shipper_name" FROM "orders" AS "o" INNER JOIN "customers" AS "c" ON ("o"."customer_id" = "c"."id") INNER JOIN "shippers" AS "s" ON ("o"."shipper_id" = "s"."id")
self-join:
>>>:{let query :: Query '["tab" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'Null 'PGint4])] '[] '["col" ::: 'Null 'PGint4] query = selectDotStar #t1 (from (table (#tab `as` #t1) & crossJoin (table (#tab `as` #t2)))) in printSQL query :} SELECT "t1".* FROM "tab" AS "t1" CROSS JOIN "tab" AS "t2"
value queries:
>>>:{let query :: Query '[] '[] '["foo" ::: 'NotNull 'PGint2, "bar" ::: 'NotNull 'PGbool] query = values (1 `as` #foo :* true `as` #bar) [2 `as` #foo :* false `as` #bar] in printSQL query :} SELECT * FROM (VALUES (1, TRUE), (2, FALSE)) AS t ("foo", "bar")
set operations:
>>>:{let query :: Query '["tab" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'Null 'PGint4])] '[] '["col" ::: 'Null 'PGint4] query = selectStar (from (table #tab)) `unionAll` selectStar (from (table #tab)) in printSQL query :} (SELECT * FROM "tab" AS "tab") UNION ALL (SELECT * FROM "tab" AS "tab")
with queries:
>>>:{let query :: Query '[ "t1" ::: 'View '[ "c1" ::: 'NotNull 'PGtext , "c2" ::: 'NotNull 'PGtext] ] '[] '[ "c1" ::: 'NotNull 'PGtext , "c2" ::: 'NotNull 'PGtext ] query = with ( selectStar (from (view #t1)) `as` #t2 :>> selectStar (from (view #t2)) `as` #t3 ) (selectStar (from (view #t3))) in printSQL query :} WITH "t2" AS (SELECT * FROM "t1" AS "t1"), "t3" AS (SELECT * FROM "t2" AS "t2") SELECT * FROM "t3" AS "t3"
Constructors
| UnsafeQuery | |
Fields | |
Instances
| With Query Source # | |
Defined in Squeal.PostgreSQL.Query Methods with :: AlignedList (CommonTableExpression Query params) schema0 schema1 -> Query schema1 params row -> Query schema0 params row Source # | |
| Eq (Query schema params columns) Source # | |
| Ord (Query schema params columns) Source # | |
Defined in Squeal.PostgreSQL.Query Methods compare :: Query schema params columns -> Query schema params columns -> Ordering # (<) :: Query schema params columns -> Query schema params columns -> Bool # (<=) :: Query schema params columns -> Query schema params columns -> Bool # (>) :: Query schema params columns -> Query schema params columns -> Bool # (>=) :: Query schema params columns -> Query schema params columns -> Bool # max :: Query schema params columns -> Query schema params columns -> Query schema params columns # min :: Query schema params columns -> Query schema params columns -> Query schema params columns # | |
| Show (Query schema params columns) Source # | |
| Generic (Query schema params columns) Source # | |
| NFData (Query schema params columns) Source # | |
Defined in Squeal.PostgreSQL.Query | |
| RenderSQL (Query schema params columns) Source # | |
Defined in Squeal.PostgreSQL.Query Methods renderSQL :: Query schema params columns -> ByteString Source # | |
| type Rep (Query schema params columns) Source # | |
Defined in Squeal.PostgreSQL.Query type Rep (Query schema params columns) = D1 (MetaData "Query" "Squeal.PostgreSQL.Query" "squeal-postgresql-0.4.0.0-GuxxUOwtUmZB6qL3MLEXvb" True) (C1 (MetaCons "UnsafeQuery" PrefixI True) (S1 (MetaSel (Just "renderQuery") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))) | |
Select
Arguments
| :: SListI columns | |
| => NP (Aliased (Expression schema from grouping params)) (column ': columns) | select list |
| -> TableExpression schema params from grouping | intermediate virtual table |
| -> Query schema params (column ': columns) |
the TableExpression in the select command constructs an intermediate
virtual table by possibly combining tables, views, eliminating rows,
grouping, etc. This table is finally passed on to processing by
the select list. The select list determines which columns of
the intermediate table are actually output.
Arguments
| :: SListI columns | |
| => NP (Aliased (Expression schema from Ungrouped params)) (column ': columns) | select list |
| -> TableExpression schema params from Ungrouped | intermediate virtual table |
| -> Query schema params (column ': columns) |
After the select list has been processed, the result table can
be subject to the elimination of duplicate rows using selectDistinct.
Arguments
| :: HasUnique table from columns | |
| => TableExpression schema params from Ungrouped | intermediate virtual table |
| -> Query schema params columns |
The simplest kind of query is selectStar which emits all columns
that the table expression produces.
Arguments
| :: HasUnique table from columns | |
| => TableExpression schema params from Ungrouped | intermediate virtual table |
| -> Query schema params columns |
A selectDistinctStar emits all columns that the table expression
produces and eliminates duplicate rows.
Arguments
| :: Has table from columns | |
| => Alias table | particular virtual subtable |
| -> TableExpression schema params from Ungrouped | intermediate virtual table |
| -> Query schema params columns |
When working with multiple tables, it can also be useful to ask
for all the columns of a particular table, using selectDotStar.
selectDistinctDotStar Source #
Arguments
| :: Has table from columns | |
| => Alias table | particular virtual table |
| -> TableExpression schema params from Ungrouped | intermediate virtual table |
| -> Query schema params columns |
A selectDistinctDotStar asks for all the columns of a particular table,
and eliminates duplicate rows.
Values
Arguments
| :: SListI cols | |
| => NP (Aliased (Expression schema '[] Ungrouped params)) cols | |
| -> [NP (Aliased (Expression schema '[] Ungrouped params)) cols] | When more than one row is specified, all the rows must must have the same number of elements |
| -> Query schema params cols |
values computes a row value or set of row values
specified by value expressions. It is most commonly used
to generate a “constant table” within a larger command,
but it can be used on its own.
>>>type Row = '["a" ::: 'NotNull 'PGint4, "b" ::: 'NotNull 'PGtext]>>>let query = values (1 `as` #a :* "one" `as` #b) [] :: Query '[] '[] Row>>>printSQL querySELECT * FROM (VALUES (1, E'one')) AS t ("a", "b")
Arguments
| :: SListI cols | |
| => NP (Aliased (Expression schema '[] Ungrouped params)) cols | one row of values |
| -> Query schema params cols |
values_ computes a row value or set of row values
specified by value expressions.
Set Operations
union :: Query schema params columns -> Query schema params columns -> Query schema params columns Source #
The results of two queries can be combined using the set operation
union. Duplicate rows are eliminated.
unionAll :: Query schema params columns -> Query schema params columns -> Query schema params columns Source #
The results of two queries can be combined using the set operation
unionAll, the disjoint union. Duplicate rows are retained.
intersect :: Query schema params columns -> Query schema params columns -> Query schema params columns Source #
The results of two queries can be combined using the set operation
intersect, the intersection. Duplicate rows are eliminated.
intersectAll :: Query schema params columns -> Query schema params columns -> Query schema params columns Source #
The results of two queries can be combined using the set operation
intersectAll, the intersection. Duplicate rows are retained.
except :: Query schema params columns -> Query schema params columns -> Query schema params columns Source #
The results of two queries can be combined using the set operation
except, the set difference. Duplicate rows are eliminated.
exceptAll :: Query schema params columns -> Query schema params columns -> Query schema params columns Source #
The results of two queries can be combined using the set operation
exceptAll, the set difference. Duplicate rows are retained.
With
class With statement where Source #
with provides a way to write auxiliary statements for use in a larger query.
These statements, referred to as CommonTableExpressions, can be thought of as
defining temporary tables that exist just for one query.
Minimal complete definition
Methods
Arguments
| :: AlignedList (CommonTableExpression statement params) schema0 schema1 | common table expressions |
| -> statement schema1 params row | larger query |
| -> statement schema0 params row |
Instances
| With Query Source # | |
Defined in Squeal.PostgreSQL.Query Methods with :: AlignedList (CommonTableExpression Query params) schema0 schema1 -> Query schema1 params row -> Query schema0 params row Source # | |
| With Manipulation Source # | |
Defined in Squeal.PostgreSQL.Manipulation Methods with :: AlignedList (CommonTableExpression Manipulation params) schema0 schema1 -> Manipulation schema1 params row -> Manipulation schema0 params row Source # | |
data CommonTableExpression statement (params :: [NullityType]) (schema0 :: SchemaType) (schema1 :: SchemaType) where Source #
A CommonTableExpression is an auxiliary statement in a with clause.
Constructors
| CommonTableExpression :: Aliased (statement schema params) (alias ::: cte) -> CommonTableExpression statement params schema ((alias ::: View cte) ': schema) |
Instances
| (KnownSymbol alias, schema1 ~ ((alias ::: View cte) ': schema)) => Aliasable alias (statement schema params cte) (AlignedList (CommonTableExpression statement params) schema schema1) Source # | |
Defined in Squeal.PostgreSQL.Query Methods as :: statement schema params cte -> Alias alias -> AlignedList (CommonTableExpression statement params) schema schema1 Source # | |
| (KnownSymbol alias, schema1 ~ ((alias ::: View cte) ': schema)) => Aliasable alias (statement schema params cte) (CommonTableExpression statement params schema schema1) Source # | |
Defined in Squeal.PostgreSQL.Query Methods as :: statement schema params cte -> Alias alias -> CommonTableExpression statement params schema schema1 Source # | |
renderCommonTableExpression Source #
Arguments
| :: (forall sch ps row. statement ps sch row -> ByteString) | render statement |
| -> CommonTableExpression statement params schema0 schema1 | |
| -> ByteString |
render a CommonTableExpression.
renderCommonTableExpressions Source #
Arguments
| :: (forall sch ps row. statement ps sch row -> ByteString) | render statement |
| -> CommonTableExpression statement params schema0 schema1 | |
| -> AlignedList (CommonTableExpression statement params) schema1 schema2 | |
| -> ByteString |
render a non-empty AlignedList of CommonTableExpressions.
Json
Arguments
| :: Expression schema '[] Ungrouped params (nullity PGjson) | json object |
| -> Query schema params '["key" ::: NotNull PGtext, "value" ::: NotNull PGjson] |
Expands the outermost JSON object into a set of key/value pairs.
Arguments
| :: Expression schema '[] Ungrouped params (nullity PGjsonb) | jsonb object |
| -> Query schema params '["key" ::: NotNull PGtext, "value" ::: NotNull PGjsonb] |
Expands the outermost binary JSON object into a set of key/value pairs.
Arguments
| :: Expression schema '[] Ungrouped params (nullity PGjson) | json object |
| -> Query schema params '["key" ::: NotNull PGtext, "value" ::: NotNull PGtext] |
Expands the outermost JSON object into a set of key/value pairs.
Arguments
| :: Expression schema '[] Ungrouped params (nullity PGjsonb) | jsonb object |
| -> Query schema params '["key" ::: NotNull PGtext, "value" ::: NotNull PGtext] |
Expands the outermost binary JSON object into a set of key/value pairs.
Arguments
| :: Expression schema '[] Ungrouped params (nullity PGjson) | json object |
| -> Query schema params '["json_object_keys" ::: NotNull PGtext] |
Returns set of keys in the outermost JSON object.
Arguments
| :: Expression schema '[] Ungrouped params (nullity PGjsonb) | jsonb object |
| -> Query schema params '["jsonb_object_keys" ::: NotNull PGtext] |
Returns set of keys in the outermost JSON object.
Arguments
| :: TypeExpression schema (nullity (PGcomposite row)) | row type |
| -> Expression schema '[] Ungrouped params (nullity PGjson) | json object |
| -> Query schema params row |
Expands the JSON expression to a row whose columns match the record type defined by the given table.
Arguments
| :: TypeExpression schema (nullity (PGcomposite row)) | row type |
| -> Expression schema '[] Ungrouped params (nullity PGjsonb) | jsonb object |
| -> Query schema params row |
Expands the binary JSON expression to a row whose columns match the record type defined by the given table.
jsonPopulateRecordSet Source #
Arguments
| :: TypeExpression schema (nullity (PGcomposite row)) | row type |
| -> Expression schema '[] Ungrouped params (nullity PGjson) | json array |
| -> Query schema params row |
Expands the outermost array of objects in the given JSON expression to a set of rows whose columns match the record type defined by the given table.
jsonbPopulateRecordSet Source #
Arguments
| :: TypeExpression schema (nullity (PGcomposite row)) | row type |
| -> Expression schema '[] Ungrouped params (nullity PGjsonb) | jsonb array |
| -> Query schema params row |
Expands the outermost array of objects in the given binary JSON expression to a set of rows whose columns match the record type defined by the given table.
Arguments
| :: SListI record | |
| => Expression schema '[] Ungrouped params (nullity PGjson) | json object |
| -> NP (Aliased (TypeExpression schema)) record | record types |
| -> Query schema params record |
Builds an arbitrary record from a JSON object.
Arguments
| :: SListI record | |
| => Expression schema '[] Ungrouped params (nullity PGjsonb) | jsonb object |
| -> NP (Aliased (TypeExpression schema)) record | record types |
| -> Query schema params record |
Builds an arbitrary record from a binary JSON object.
Arguments
| :: SListI record | |
| => Expression schema '[] Ungrouped params (nullity PGjson) | json array |
| -> NP (Aliased (TypeExpression schema)) record | record types |
| -> Query schema params record |
Builds an arbitrary set of records from a JSON array of objects.
Arguments
| :: SListI record | |
| => Expression schema '[] Ungrouped params (nullity PGjsonb) | jsonb array |
| -> NP (Aliased (TypeExpression schema)) record | record types |
| -> Query schema params record |
Builds an arbitrary set of records from a binary JSON array of objects.
Table Expressions
data TableExpression (schema :: SchemaType) (params :: [NullityType]) (from :: FromType) (grouping :: Grouping) Source #
A TableExpression computes a table. The table expression contains
a fromClause that is optionally followed by a whereClause,
groupByClause, havingClause, orderByClause, limitClause
and offsetClauses. Trivial table expressions simply refer
to a table on disk, a so-called base table, but more complex expressions
can be used to modify or combine base tables in various ways.
Constructors
| TableExpression | |
Fields
| |
renderTableExpression :: TableExpression schema params from grouping -> ByteString Source #
Render a TableExpression
Arguments
| :: FromClause schema params from | table reference |
| -> TableExpression schema params from Ungrouped |
A from generates a TableExpression from a table reference that can be
a table name, or a derived table such as a subquery, a JOIN construct,
or complex combinations of these. A from may be transformed by where_,
group, having, orderBy, limit and offset, using the & operator
to match the left-to-right sequencing of their placement in SQL.
Arguments
| :: Condition schema from Ungrouped params | filtering condition |
| -> TableExpression schema params from grouping | |
| -> TableExpression schema params from grouping |
A where_ is an endomorphism of TableExpressions which adds a
search condition to the whereClause.
Arguments
| :: SListI bys | |
| => NP (By from) bys | grouped columns |
| -> TableExpression schema params from Ungrouped | |
| -> TableExpression schema params from (Grouped bys) |
A groupBy is a transformation of TableExpressions which switches
its Grouping from Ungrouped to Grouped. Use group Nil to perform
a "grand total" aggregation query.
Arguments
| :: Condition schema from (Grouped bys) params | having condition |
| -> TableExpression schema params from (Grouped bys) | |
| -> TableExpression schema params from (Grouped bys) |
A having is an endomorphism of TableExpressions which adds a
search condition to the havingClause.
Arguments
| :: [SortExpression schema from grouping params] | sort expressions |
| -> TableExpression schema params from grouping | |
| -> TableExpression schema params from grouping |
An orderBy is an endomorphism of TableExpressions which appends an
ordering to the right of the orderByClause.
Arguments
| :: Word64 | limit parameter |
| -> TableExpression schema params from grouping | |
| -> TableExpression schema params from grouping |
A limit is an endomorphism of TableExpressions which adds to the
limitClause.
Arguments
| :: Word64 | offset parameter |
| -> TableExpression schema params from grouping | |
| -> TableExpression schema params from grouping |
An offset is an endomorphism of TableExpressions which adds to the
offsetClause.
From Clauses
newtype FromClause schema params from Source #
A FromClause can be a table name, or a derived table such
as a subquery, a JOIN construct, or complex combinations of these.
Constructors
| UnsafeFromClause | |
Fields | |
Instances
| Eq (FromClause schema params from) Source # | |
Defined in Squeal.PostgreSQL.Query Methods (==) :: FromClause schema params from -> FromClause schema params from -> Bool # (/=) :: FromClause schema params from -> FromClause schema params from -> Bool # | |
| Ord (FromClause schema params from) Source # | |
Defined in Squeal.PostgreSQL.Query Methods compare :: FromClause schema params from -> FromClause schema params from -> Ordering # (<) :: FromClause schema params from -> FromClause schema params from -> Bool # (<=) :: FromClause schema params from -> FromClause schema params from -> Bool # (>) :: FromClause schema params from -> FromClause schema params from -> Bool # (>=) :: FromClause schema params from -> FromClause schema params from -> Bool # max :: FromClause schema params from -> FromClause schema params from -> FromClause schema params from # min :: FromClause schema params from -> FromClause schema params from -> FromClause schema params from # | |
| Show (FromClause schema params from) Source # | |
Defined in Squeal.PostgreSQL.Query Methods showsPrec :: Int -> FromClause schema params from -> ShowS # show :: FromClause schema params from -> String # showList :: [FromClause schema params from] -> ShowS # | |
| Generic (FromClause schema params from) Source # | |
Defined in Squeal.PostgreSQL.Query Associated Types type Rep (FromClause schema params from) :: * -> * # Methods from :: FromClause schema params from -> Rep (FromClause schema params from) x # to :: Rep (FromClause schema params from) x -> FromClause schema params from # | |
| NFData (FromClause schema params from) Source # | |
Defined in Squeal.PostgreSQL.Query Methods rnf :: FromClause schema params from -> () # | |
| type Rep (FromClause schema params from) Source # | |
Defined in Squeal.PostgreSQL.Query type Rep (FromClause schema params from) = D1 (MetaData "FromClause" "Squeal.PostgreSQL.Query" "squeal-postgresql-0.4.0.0-GuxxUOwtUmZB6qL3MLEXvb" True) (C1 (MetaCons "UnsafeFromClause" PrefixI True) (S1 (MetaSel (Just "renderFromClause") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))) | |
table :: Has tab schema (Table table) => Aliased Alias (alias ::: tab) -> FromClause schema params '[alias ::: TableToRow table] Source #
A real table is a table from the schema.
view :: Has view schema (View row) => Aliased Alias (alias ::: view) -> FromClause schema params '[alias ::: row] Source #
Arguments
| :: FromClause schema params right | right |
| -> FromClause schema params left | left |
| -> FromClause schema params (Join left right) |
left & crossJoin right. For every possible combination of rows from
left and right (i.e., a Cartesian product), the joined table will contain
a row consisting of all columns in left followed by all columns in right.
If the tables have n and m rows respectively, the joined table will
have n * m rows.
Arguments
| :: FromClause schema params right | right |
| -> Condition schema (Join left right) Ungrouped params |
|
| -> FromClause schema params left | left |
| -> FromClause schema params (Join left right) |
left & innerJoin right on. The joined table is filtered by
the on condition.
Arguments
| :: FromClause schema params right | right |
| -> Condition schema (Join left right) Ungrouped params |
|
| -> FromClause schema params left | left |
| -> FromClause schema params (Join left (NullifyFrom right)) |
left & leftOuterJoin right on. First, an inner join is performed.
Then, for each row in left that does not satisfy the on condition with
any row in right, a joined row is added with null values in columns of right.
Thus, the joined table always has at least one row for each row in left.
Arguments
| :: FromClause schema params right | right |
| -> Condition schema (Join left right) Ungrouped params |
|
| -> FromClause schema params left | left |
| -> FromClause schema params (Join (NullifyFrom left) right) |
left & rightOuterJoin right on. First, an inner join is performed.
Then, for each row in right that does not satisfy the on condition with
any row in left, a joined row is added with null values in columns of left.
This is the converse of a left join: the result table will always
have a row for each row in right.
Arguments
| :: FromClause schema params right | right |
| -> Condition schema (Join left right) Ungrouped params |
|
| -> FromClause schema params left | left |
| -> FromClause schema params (Join (NullifyFrom left) (NullifyFrom right)) |
left & fullOuterJoin right on. First, an inner join is performed.
Then, for each row in left that does not satisfy the on condition with
any row in right, a joined row is added with null values in columns of right.
Also, for each row of right that does not satisfy the join condition
with any row in left, a joined row with null values in the columns of left
is added.
Grouping
data By (from :: FromType) (by :: (Symbol, Symbol)) where Source #
Bys are used in group to reference a list of columns which are then
used to group together those rows in a table that have the same values
in all the columns listed. By #col will reference an unambiguous
column col; otherwise By2 (#tab ! #col) will reference a table
qualified column tab.col.
Constructors
| By1 :: (HasUnique table from columns, Has column columns ty) => Alias column -> By from '(table, column) | |
| By2 :: (Has table from columns, Has column columns ty) => Alias table -> Alias column -> By from '(table, column) |
Instances
| (Has rel rels cols, Has col cols ty, by ~ (,) rel col) => IsQualified rel col (By rels by) Source # | |
| (Has rel rels cols, Has col cols ty, bys ~ ((,) rel col ': ([] :: [(Symbol, Symbol)]))) => IsQualified rel col (NP (By rels) bys) Source # | |
| (HasUnique rel rels cols, Has col cols ty, by ~ (,) rel col) => IsLabel col (By rels by) Source # | |
Defined in Squeal.PostgreSQL.Query | |
| (HasUnique rel rels cols, Has col cols ty, bys ~ ((,) rel col ': ([] :: [(Symbol, Symbol)]))) => IsLabel col (NP (By rels) bys) Source # | |
Defined in Squeal.PostgreSQL.Query | |
| Eq (By from by) Source # | |
| Ord (By from by) Source # | |
Defined in Squeal.PostgreSQL.Query | |
| Show (By from by) Source # | |
data GroupByClause from grouping where Source #
A GroupByClause indicates the Grouping of a TableExpression.
A NoGroups indicates Ungrouped while a Group indicates Grouped.
NoGroups is distinguised from Group Nil since no aggregation can be
done on NoGroups while all output Expressions must be aggregated
in Group Nil. In general, all output Expressions in the
complement of bys must be aggregated in Group bys.
Constructors
| NoGroups :: GroupByClause from Ungrouped | |
| Group :: SListI bys => NP (By from) bys -> GroupByClause from (Grouped bys) |
renderGroupByClause :: GroupByClause from grouping -> ByteString Source #
Renders a GroupByClause.
data HavingClause schema from grouping params where Source #
A HavingClause is used to eliminate groups that are not of interest.
An Ungrouped TableExpression may only use NoHaving while a Grouped
TableExpression must use Having whose conditions are combined with
.&&.
Constructors
| NoHaving :: HavingClause schema from Ungrouped params | |
| Having :: [Condition schema from (Grouped bys) params] -> HavingClause schema from (Grouped bys) params |
Instances
| Eq (HavingClause schema from grouping params) Source # | |
Defined in Squeal.PostgreSQL.Query Methods (==) :: HavingClause schema from grouping params -> HavingClause schema from grouping params -> Bool # (/=) :: HavingClause schema from grouping params -> HavingClause schema from grouping params -> Bool # | |
| Ord (HavingClause schema from grouping params) Source # | |
Defined in Squeal.PostgreSQL.Query Methods compare :: HavingClause schema from grouping params -> HavingClause schema from grouping params -> Ordering # (<) :: HavingClause schema from grouping params -> HavingClause schema from grouping params -> Bool # (<=) :: HavingClause schema from grouping params -> HavingClause schema from grouping params -> Bool # (>) :: HavingClause schema from grouping params -> HavingClause schema from grouping params -> Bool # (>=) :: HavingClause schema from grouping params -> HavingClause schema from grouping params -> Bool # max :: HavingClause schema from grouping params -> HavingClause schema from grouping params -> HavingClause schema from grouping params # min :: HavingClause schema from grouping params -> HavingClause schema from grouping params -> HavingClause schema from grouping params # | |
| Show (HavingClause schema from grouping params) Source # | |
Defined in Squeal.PostgreSQL.Query Methods showsPrec :: Int -> HavingClause schema from grouping params -> ShowS # show :: HavingClause schema from grouping params -> String # showList :: [HavingClause schema from grouping params] -> ShowS # | |
renderHavingClause :: HavingClause schema from grouping params -> ByteString Source #
Render a HavingClause.
Sorting
data SortExpression schema from grouping params where Source #
SortExpressions are used by sortBy to optionally sort the results
of a Query. Asc or Desc set the sort direction of a NotNull result
column to ascending or descending. Ascending order puts smaller values
first, where "smaller" is defined in terms of the .< operator. Similarly,
descending order is determined with the .> operator. AscNullsFirst,
AscNullsLast, DescNullsFirst and DescNullsLast options are used to
determine whether nulls appear before or after non-null values in the sort
ordering of a Null result column.
Constructors
| Asc :: Expression schema from grouping params (NotNull ty) -> SortExpression schema from grouping params | |
| Desc :: Expression schema from grouping params (NotNull ty) -> SortExpression schema from grouping params | |
| AscNullsFirst :: Expression schema from grouping params (Null ty) -> SortExpression schema from grouping params | |
| AscNullsLast :: Expression schema from grouping params (Null ty) -> SortExpression schema from grouping params | |
| DescNullsFirst :: Expression schema from grouping params (Null ty) -> SortExpression schema from grouping params | |
| DescNullsLast :: Expression schema from grouping params (Null ty) -> SortExpression schema from grouping params |
Instances
| Show (SortExpression schema from grouping params) Source # | |
Defined in Squeal.PostgreSQL.Query Methods showsPrec :: Int -> SortExpression schema from grouping params -> ShowS # show :: SortExpression schema from grouping params -> String # showList :: [SortExpression schema from grouping params] -> ShowS # | |
renderSortExpression :: SortExpression schema from grouping params -> ByteString Source #
Render a SortExpression.
Subquery Expressions
Arguments
| :: Expression schema from grp params ty | expression |
| -> Query schema params '[alias ::: ty] | subquery |
| -> Expression schema from grp params (nullity PGbool) |
The right-hand side is a subQuery, which must return exactly one column.
The left-hand expression is evaluated and compared to each row of the
subQuery result. The result of in_ is true if any equal subquery row is found.
The result is false if no equal row is found
(including the case where the subquery returns no rows).
>>>printSQL $ true `in_` values_ (true `as` #foo)TRUE IN (SELECT * FROM (VALUES (TRUE)) AS t ("foo"))
Arguments
| :: SListI row | |
| => NP (Aliased (Expression schema from grp params)) row | row constructor |
| -> Query schema params row | subquery |
| -> Expression schema from grp params (nullity PGbool) |
The left-hand side of this form of rowIn is a row constructor.
The right-hand side is a subQuery,
which must return exactly as many columns as
there are expressions in the left-hand row.
The left-hand expressions are evaluated and compared row-wise to each row
of the subquery result. The result of rowIn
is true if any equal subquery row is found.
The result is false if no equal row is found
(including the case where the subquery returns no rows).
>>>let myRow = 1 `as` #foo :* false `as` #bar :: NP (Aliased (Expression '[] '[] 'Ungrouped '[])) '["foo" ::: 'NotNull 'PGint2, "bar" ::: 'NotNull 'PGbool]>>>printSQL $ myRow `rowIn` values_ myRowROW(1, FALSE) IN (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))
Arguments
| :: Expression schema from grp params ty | expression |
| -> Query schema params '[alias ::: ty] | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>printSQL $ true `eqAll` values_ (true `as` #foo)TRUE = ALL (SELECT * FROM (VALUES (TRUE)) AS t ("foo"))
Arguments
| :: SListI row | |
| => NP (Aliased (Expression schema from grp params)) row | row constructor |
| -> Query schema params row | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>let myRow = 1 `as` #foo :* false `as` #bar :: NP (Aliased (Expression '[] '[] 'Ungrouped '[])) '["foo" ::: 'NotNull 'PGint2, "bar" ::: 'NotNull 'PGbool]>>>printSQL $ myRow `rowEqAll` values_ myRowROW(1, FALSE) = ALL (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))
Arguments
| :: Expression schema from grp params ty | expression |
| -> Query schema params '[alias ::: ty] | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>printSQL $ true `eqAny` values_ (true `as` #foo)TRUE = ANY (SELECT * FROM (VALUES (TRUE)) AS t ("foo"))
Arguments
| :: SListI row | |
| => NP (Aliased (Expression schema from grp params)) row | row constructor |
| -> Query schema params row | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>let myRow = 1 `as` #foo :* false `as` #bar :: NP (Aliased (Expression '[] '[] 'Ungrouped '[])) '["foo" ::: 'NotNull 'PGint2, "bar" ::: 'NotNull 'PGbool]>>>printSQL $ myRow `rowEqAny` values_ myRowROW(1, FALSE) = ANY (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))
Arguments
| :: Expression schema from grp params ty | expression |
| -> Query schema params '[alias ::: ty] | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>printSQL $ true `neqAll` values_ (true `as` #foo)TRUE <> ALL (SELECT * FROM (VALUES (TRUE)) AS t ("foo"))
Arguments
| :: SListI row | |
| => NP (Aliased (Expression schema from grp params)) row | row constructor |
| -> Query schema params row | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>let myRow = 1 `as` #foo :* false `as` #bar :: NP (Aliased (Expression '[] '[] 'Ungrouped '[])) '["foo" ::: 'NotNull 'PGint2, "bar" ::: 'NotNull 'PGbool]>>>printSQL $ myRow `rowNeqAll` values_ myRowROW(1, FALSE) <> ALL (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))
Arguments
| :: Expression schema from grp params ty | expression |
| -> Query schema params '[alias ::: ty] | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>printSQL $ true `neqAny` values_ (true `as` #foo)TRUE <> ANY (SELECT * FROM (VALUES (TRUE)) AS t ("foo"))
Arguments
| :: SListI row | |
| => NP (Aliased (Expression schema from grp params)) row | row constructor |
| -> Query schema params row | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>let myRow = 1 `as` #foo :* false `as` #bar :: NP (Aliased (Expression '[] '[] 'Ungrouped '[])) '["foo" ::: 'NotNull 'PGint2, "bar" ::: 'NotNull 'PGbool]>>>printSQL $ myRow `rowNeqAny` values_ myRowROW(1, FALSE) <> ANY (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))
Arguments
| :: Expression schema from grp params ty | expression |
| -> Query schema params '[alias ::: ty] | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>printSQL $ true `allLt` values_ (true `as` #foo)TRUE ALL < (SELECT * FROM (VALUES (TRUE)) AS t ("foo"))
Arguments
| :: SListI row | |
| => NP (Aliased (Expression schema from grp params)) row | row constructor |
| -> Query schema params row | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>let myRow = 1 `as` #foo :* false `as` #bar :: NP (Aliased (Expression '[] '[] 'Ungrouped '[])) '["foo" ::: 'NotNull 'PGint2, "bar" ::: 'NotNull 'PGbool]>>>printSQL $ myRow `rowLtAll` values_ myRowROW(1, FALSE) ALL < (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))
Arguments
| :: Expression schema from grp params ty | expression |
| -> Query schema params '[alias ::: ty] | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>printSQL $ true `ltAny` values_ (true `as` #foo)TRUE ANY < (SELECT * FROM (VALUES (TRUE)) AS t ("foo"))
Arguments
| :: SListI row | |
| => NP (Aliased (Expression schema from grp params)) row | row constructor |
| -> Query schema params row | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>let myRow = 1 `as` #foo :* false `as` #bar :: NP (Aliased (Expression '[] '[] 'Ungrouped '[])) '["foo" ::: 'NotNull 'PGint2, "bar" ::: 'NotNull 'PGbool]>>>printSQL $ myRow `rowLtAll` values_ myRowROW(1, FALSE) ALL < (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))
Arguments
| :: Expression schema from grp params ty | expression |
| -> Query schema params '[alias ::: ty] | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>printSQL $ true `lteAll` values_ (true `as` #foo)TRUE <= ALL (SELECT * FROM (VALUES (TRUE)) AS t ("foo"))
Arguments
| :: SListI row | |
| => NP (Aliased (Expression schema from grp params)) row | row constructor |
| -> Query schema params row | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>let myRow = 1 `as` #foo :* false `as` #bar :: NP (Aliased (Expression '[] '[] 'Ungrouped '[])) '["foo" ::: 'NotNull 'PGint2, "bar" ::: 'NotNull 'PGbool]>>>printSQL $ myRow `rowLteAll` values_ myRowROW(1, FALSE) <= ALL (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))
Arguments
| :: Expression schema from grp params ty | expression |
| -> Query schema params '[alias ::: ty] | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>printSQL $ true `lteAny` values_ (true `as` #foo)TRUE <= ANY (SELECT * FROM (VALUES (TRUE)) AS t ("foo"))
Arguments
| :: SListI row | |
| => NP (Aliased (Expression schema from grp params)) row | row constructor |
| -> Query schema params row | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>let myRow = 1 `as` #foo :* false `as` #bar :: NP (Aliased (Expression '[] '[] 'Ungrouped '[])) '["foo" ::: 'NotNull 'PGint2, "bar" ::: 'NotNull 'PGbool]>>>printSQL $ myRow `rowLteAny` values_ myRowROW(1, FALSE) <= ANY (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))
Arguments
| :: Expression schema from grp params ty | expression |
| -> Query schema params '[alias ::: ty] | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>printSQL $ true `gtAll` values_ (true `as` #foo)TRUE > ALL (SELECT * FROM (VALUES (TRUE)) AS t ("foo"))
Arguments
| :: SListI row | |
| => NP (Aliased (Expression schema from grp params)) row | row constructor |
| -> Query schema params row | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>let myRow = 1 `as` #foo :* false `as` #bar :: NP (Aliased (Expression '[] '[] 'Ungrouped '[])) '["foo" ::: 'NotNull 'PGint2, "bar" ::: 'NotNull 'PGbool]>>>printSQL $ myRow `rowGtAll` values_ myRowROW(1, FALSE) > ALL (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))
Arguments
| :: Expression schema from grp params ty | expression |
| -> Query schema params '[alias ::: ty] | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>printSQL $ true `gtAny` values_ (true `as` #foo)TRUE > ANY (SELECT * FROM (VALUES (TRUE)) AS t ("foo"))
Arguments
| :: SListI row | |
| => NP (Aliased (Expression schema from grp params)) row | row constructor |
| -> Query schema params row | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>let myRow = 1 `as` #foo :* false `as` #bar :: NP (Aliased (Expression '[] '[] 'Ungrouped '[])) '["foo" ::: 'NotNull 'PGint2, "bar" ::: 'NotNull 'PGbool]>>>printSQL $ myRow `rowGtAny` values_ myRowROW(1, FALSE) > ANY (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))
Arguments
| :: Expression schema from grp params ty | expression |
| -> Query schema params '[alias ::: ty] | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>printSQL $ true `gteAll` values_ (true `as` #foo)TRUE >= ALL (SELECT * FROM (VALUES (TRUE)) AS t ("foo"))
Arguments
| :: SListI row | |
| => NP (Aliased (Expression schema from grp params)) row | row constructor |
| -> Query schema params row | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>let myRow = 1 `as` #foo :* false `as` #bar :: NP (Aliased (Expression '[] '[] 'Ungrouped '[])) '["foo" ::: 'NotNull 'PGint2, "bar" ::: 'NotNull 'PGbool]>>>printSQL $ myRow `rowGteAll` values_ myRowROW(1, FALSE) >= ALL (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))
Arguments
| :: Expression schema from grp params ty | expression |
| -> Query schema params '[alias ::: ty] | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>printSQL $ true `gteAny` values_ (true `as` #foo)TRUE >= ANY (SELECT * FROM (VALUES (TRUE)) AS t ("foo"))
Arguments
| :: SListI row | |
| => NP (Aliased (Expression schema from grp params)) row | row constructor |
| -> Query schema params row | subquery |
| -> Expression schema from grp params (nullity PGbool) |
>>>let myRow = 1 `as` #foo :* false `as` #bar :: NP (Aliased (Expression '[] '[] 'Ungrouped '[])) '["foo" ::: 'NotNull 'PGint2, "bar" ::: 'NotNull 'PGbool]>>>printSQL $ myRow `rowGteAny` values_ myRowROW(1, FALSE) >= ANY (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))