Copyright | (c) Eitan Chatav 2017 |
---|---|
Maintainer | [email protected] |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Squeal.PostgreSQL.Query
Description
Squeal queries.
- newtype Query (schema :: TablesType) (params :: [ColumnType]) (columns :: ColumnsType) = UnsafeQuery {}
- 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
- select :: SListI columns => NP (Aliased (Expression tables grouping params)) (column ': columns) -> TableExpression schema params tables grouping -> Query schema params (column ': columns)
- selectDistinct :: SListI columns => NP (Aliased (Expression tables Ungrouped params)) (column ': columns) -> TableExpression schema params tables Ungrouped -> Query schema params (column ': columns)
- selectStar :: HasUnique table tables columns => TableExpression schema params tables Ungrouped -> Query schema params columns
- selectDistinctStar :: HasUnique table tables columns => TableExpression schema params tables Ungrouped -> Query schema params columns
- selectDotStar :: HasTable table tables columns => Alias table -> TableExpression schema params tables Ungrouped -> Query schema params columns
- selectDistinctDotStar :: HasTable table tables columns => Alias table -> TableExpression schema params tables Ungrouped -> Query schema params columns
- data TableExpression (schema :: TablesType) (params :: [ColumnType]) (tables :: TablesType) (grouping :: Grouping) = TableExpression {
- fromClause :: FromClause schema params tables
- whereClause :: [Condition tables Ungrouped params]
- groupByClause :: GroupByClause tables grouping
- havingClause :: HavingClause tables grouping params
- orderByClause :: [SortExpression tables grouping params]
- limitClause :: [Word64]
- offsetClause :: [Word64]
- renderTableExpression :: TableExpression schema params tables grouping -> ByteString
- from :: FromClause schema params tables -> TableExpression schema params tables Ungrouped
- where_ :: Condition tables Ungrouped params -> TableExpression schema params tables grouping -> TableExpression schema params tables grouping
- group :: SListI bys => NP (By tables) bys -> TableExpression schema params tables Ungrouped -> TableExpression schema params tables (Grouped bys)
- having :: Condition tables (Grouped bys) params -> TableExpression schema params tables (Grouped bys) -> TableExpression schema params tables (Grouped bys)
- orderBy :: [SortExpression tables grouping params] -> TableExpression schema params tables grouping -> TableExpression schema params tables grouping
- limit :: Word64 -> TableExpression schema params tables grouping -> TableExpression schema params tables grouping
- offset :: Word64 -> TableExpression schema params tables grouping -> TableExpression schema params tables grouping
- data FromClause schema params tables where
- Table :: Aliased (Table schema) table -> FromClause schema params '[table]
- Subquery :: Aliased (Query schema params) table -> FromClause schema params '[table]
- CrossJoin :: FromClause schema params right -> FromClause schema params left -> FromClause schema params (Join left right)
- InnerJoin :: FromClause schema params right -> Condition (Join left right) Ungrouped params -> FromClause schema params left -> FromClause schema params (Join left right)
- LeftOuterJoin :: FromClause schema params right -> Condition (Join left right) Ungrouped params -> FromClause schema params left -> FromClause schema params (Join left (NullifyTables right))
- RightOuterJoin :: FromClause schema params right -> Condition (Join left right) Ungrouped params -> FromClause schema params left -> FromClause schema params (Join (NullifyTables left) right)
- FullOuterJoin :: FromClause schema params right -> Condition (Join left right) Ungrouped params -> FromClause schema params left -> FromClause schema params (Join (NullifyTables left) (NullifyTables right))
- renderFromClause :: FromClause schema params tables -> ByteString
- data By (tables :: TablesType) (by :: (Symbol, Symbol)) where
- renderBy :: By tables tabcolty -> ByteString
- data GroupByClause tables grouping where
- NoGroups :: GroupByClause tables Ungrouped
- Group :: SListI bys => NP (By tables) bys -> GroupByClause tables (Grouped bys)
- renderGroupByClause :: GroupByClause tables grouping -> ByteString
- data HavingClause tables grouping params where
- NoHaving :: HavingClause tables Ungrouped params
- Having :: [Condition tables (Grouped bys) params] -> HavingClause tables (Grouped bys) params
- renderHavingClause :: HavingClause tables grouping params -> ByteString
- data SortExpression tables grouping params where
- Asc :: Expression tables grouping params (Required (NotNull ty)) -> SortExpression tables grouping params
- Desc :: Expression tables grouping params (Required (NotNull ty)) -> SortExpression tables grouping params
- AscNullsFirst :: Expression tables grouping params (Required (Null ty)) -> SortExpression tables grouping params
- AscNullsLast :: Expression tables grouping params (Required (Null ty)) -> SortExpression tables grouping params
- DescNullsFirst :: Expression tables grouping params (Required (Null ty)) -> SortExpression tables grouping params
- DescNullsLast :: Expression tables grouping params (Required (Null ty)) -> SortExpression tables grouping params
- renderSortExpression :: SortExpression tables grouping params -> ByteString
Queries
newtype Query (schema :: TablesType) (params :: [ColumnType]) (columns :: ColumnsType) Source #
The process of retrieving or the command to retrieve data from a database
is called a Query
. The select
, selectStar
, selectDotStar
,
selectDistinct
, selectDistinctStar
and selectDistinctDotStar
commands
are used to specify queries.
simple query:
>>>
:{
let query :: Query '["tab" ::: '["col" ::: 'Required ('Null 'PGint4)]] '[] '["col" ::: 'Required ('Null 'PGint4)] query = selectStar (from (Table (#tab `As` #t))) in renderQuery query :} "SELECT * FROM tab AS t"
restricted query:
>>>
:{
let query :: Query '[ "tab" ::: '[ "col1" ::: 'Required ('NotNull 'PGint4) , "col2" ::: 'Required ('NotNull 'PGint4) ]] '[] '[ "sum" ::: 'Required ('NotNull 'PGint4) , "col1" ::: 'Required ('NotNull 'PGint4) ] query = select ((#col1 + #col2) `As` #sum :* #col1 `As` #col1 :* Nil) ( from (Table (#tab `As` #t)) & where_ (#col1 .> #col2) & where_ (#col2 .> 0) ) in renderQuery query :} "SELECT (col1 + col2) AS sum, col1 AS col1 FROM tab AS t WHERE ((col1 > col2) AND (col2 > 0))"
subquery:
>>>
:{
let query :: Query '["tab" ::: '["col" ::: 'Required ('Null 'PGint4)]] '[] '["col" ::: 'Required ('Null 'PGint4)] query = selectStar (from (Subquery (selectStar (from (Table (#tab `As` #t))) `As` #sub))) in renderQuery query :} "SELECT * FROM (SELECT * FROM tab AS t) AS sub"
limits and offsets:
>>>
:{
let query :: Query '["tab" ::: '["col" ::: 'Required ('Null 'PGint4)]] '[] '["col" ::: 'Required ('Null 'PGint4)] query = selectStar (from (Table (#tab `As` #t)) & limit 100 & offset 2 & limit 50 & offset 2) in renderQuery query :} "SELECT * FROM tab AS t LIMIT 50 OFFSET 4"
parameterized query:
>>>
:{
let query :: Query '["tab" ::: '["col" ::: 'Required ('NotNull 'PGfloat8)]] '[ 'Required ('NotNull 'PGfloat8)] '["col" ::: 'Required ('NotNull 'PGfloat8)] query = selectStar (from (Table (#tab `As` #t)) & where_ (#col .> param @1)) in renderQuery query :} "SELECT * FROM tab AS t WHERE (col > ($1 :: float8))"
aggregation query:
>>>
:{
let query :: Query '[ "tab" ::: '[ "col1" ::: 'Required ('NotNull 'PGint4) , "col2" ::: 'Required ('NotNull 'PGint4) ]] '[] '[ "sum" ::: 'Required ('NotNull 'PGint4) , "col1" ::: 'Required ('NotNull 'PGint4) ] query = select (sum_ #col2 `As` #sum :* #col1 `As` #col1 :* Nil) ( from (Table (#tab `As` #table1)) & group (By #col1 :* Nil) & having (#col1 + sum_ #col2 .> 1) ) in renderQuery 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" ::: '["col" ::: 'Required ('Null 'PGint4)]] '[] '["col" ::: 'Required ('Null 'PGint4)] query = selectStar (from (Table (#tab `As` #t)) & orderBy [#col & AscNullsFirst]) in renderQuery query :} "SELECT * FROM tab AS t ORDER BY col ASC NULLS FIRST"
joins:
>>>
:set -XFlexibleContexts
>>>
:{
let query :: Query '[ "orders" ::: '[ "id" ::: 'Required ('NotNull 'PGint4) , "price" ::: 'Required ('NotNull 'PGfloat4) , "customer_id" ::: 'Required ('NotNull 'PGint4) , "shipper_id" ::: 'Required ('NotNull 'PGint4) ] , "customers" ::: '[ "id" ::: 'Required ('NotNull 'PGint4) , "name" ::: 'Required ('NotNull 'PGtext) ] , "shippers" ::: '[ "id" ::: 'Required ('NotNull 'PGint4) , "name" ::: 'Required ('NotNull 'PGtext) ] ] '[] '[ "order_price" ::: 'Required ('NotNull 'PGfloat4) , "customer_name" ::: 'Required ('NotNull 'PGtext) , "shipper_name" ::: 'Required ('NotNull 'PGtext) ] query = select ( #o ! #price `As` #order_price :* #c ! #name `As` #customer_name :* #s ! #name `As` #shipper_name :* Nil ) ( 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 renderQuery 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" ::: '["col" ::: 'Required ('Null 'PGint4)]] '[] '["col" ::: 'Required ('Null 'PGint4)] query = selectDotStar #t1 (from (Table (#tab `As` #t1) & CrossJoin (Table (#tab `As` #t2)))) in renderQuery query :} "SELECT t1.* FROM tab AS t1 CROSS JOIN tab AS t2"
set operations:
>>>
:{
let query :: Query '["tab" ::: '["col" ::: 'Required ('Null 'PGint4)]] '[] '["col" ::: 'Required ('Null 'PGint4)] query = selectStar (from (Table (#tab `As` #t))) `unionAll` selectStar (from (Table (#tab `As` #t))) in renderQuery query :} "(SELECT * FROM tab AS t) UNION ALL (SELECT * FROM tab AS t)"
Constructors
UnsafeQuery | |
Fields |
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.
Select
Arguments
:: SListI columns | |
=> NP (Aliased (Expression tables grouping params)) (column ': columns) | select list |
-> TableExpression schema params tables 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 tables Ungrouped params)) (column ': columns) | select list |
-> TableExpression schema params tables 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 tables columns | |
=> TableExpression schema params tables 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 tables columns | |
=> TableExpression schema params tables Ungrouped | intermediate virtual table |
-> Query schema params columns |
A selectDistinctStar
emits all columns that the table expression
produces and eliminates duplicate rows.
Arguments
:: HasTable table tables columns | |
=> Alias table | particular virtual subtable |
-> TableExpression schema params tables 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
:: HasTable table tables columns | |
=> Alias table | particular virtual subtable |
-> TableExpression schema params tables Ungrouped | intermediate virtual table |
-> Query schema params columns |
A selectDistinctDotStar
asks for all the columns of a particular table,
and eliminates duplicate rows.
Table Expressions
data TableExpression (schema :: TablesType) (params :: [ColumnType]) (tables :: TablesType) (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 offsetClause
s. 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 tables grouping -> ByteString Source #
Render a TableExpression
Arguments
:: FromClause schema params tables | table reference |
-> TableExpression schema params tables 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.
where_ :: Condition tables Ungrouped params -> TableExpression schema params tables grouping -> TableExpression schema params tables grouping Source #
A where_
is an endomorphism of TableExpression
s which adds a
search condition to the whereClause
.
group :: SListI bys => NP (By tables) bys -> TableExpression schema params tables Ungrouped -> TableExpression schema params tables (Grouped bys) Source #
A group
is a transformation of TableExpression
s which switches
its Grouping
from Ungrouped
to Grouped
. Use group Nil
to perform
a "grand total" aggregation query.
having :: Condition tables (Grouped bys) params -> TableExpression schema params tables (Grouped bys) -> TableExpression schema params tables (Grouped bys) Source #
A having
is an endomorphism of TableExpression
s which adds a
search condition to the havingClause
.
orderBy :: [SortExpression tables grouping params] -> TableExpression schema params tables grouping -> TableExpression schema params tables grouping Source #
An orderBy
is an endomorphism of TableExpression
s which appends an
ordering to the right of the orderByClause
.
limit :: Word64 -> TableExpression schema params tables grouping -> TableExpression schema params tables grouping Source #
A limit
is an endomorphism of TableExpression
s which adds to the
limitClause
.
offset :: Word64 -> TableExpression schema params tables grouping -> TableExpression schema params tables grouping Source #
An offset
is an endomorphism of TableExpression
s which adds to the
offsetClause
.
From
data FromClause schema params tables where Source #
A FromClause
can be a table name, or a derived table such
as a subquery, a JOIN
construct, or complex combinations of these.
- A real
Table
is a table from the schema. Subquery
derives a table from aQuery
.A joined table is a table derived from two other (real or derived) tables according to the rules of the particular join type.
CrossJoin
,InnerJoin
,LeftOuterJoin
,RightOuterJoin
andFullOuterJoin
are available and can be nested using the&
operator to match the left-to-right sequencing of their placement in SQL.t1 & CrossJoin t2
. For every possible combination of rows fromt1
andt2
(i.e., a Cartesian product), the joined table will contain a row consisting of all columns int1
followed by all columns int2
. If the tables haven
andm
rows respectively, the joined table will haven * m
rows.t1 & InnerJoin t2 on
. For each rowr1
oft1
, the joined table has a row for each row int2
that satisfies theon
condition withr1
t1 & LeftOuterJoin t2 on
. First, an inner join is performed. Then, for each row int1
that does not satisfy theon
condition with any row int2
, a joined row is added with null values in columns oft2
. Thus, the joined table always has at least one row for each row int1
.t1 & RightOuterJoin t2 on
. First, an inner join is performed. Then, for each row int2
that does not satisfy theon
condition with any row int1
, a joined row is added with null values in columns oft1
. This is the converse of a left join: the result table will always have a row for each row int2
.t1 & FullOuterJoin t2 on
. First, an inner join is performed. Then, for each row int1
that does not satisfy theon
condition with any row int2
, a joined row is added with null values in columns oft2
. Also, for each row oft2
that does not satisfy the join condition with any row int1
, a joined row with null values in the columns oft1
is added.
Constructors
Table :: Aliased (Table schema) table -> FromClause schema params '[table] | |
Subquery :: Aliased (Query schema params) table -> FromClause schema params '[table] | |
CrossJoin :: FromClause schema params right -> FromClause schema params left -> FromClause schema params (Join left right) | |
InnerJoin :: FromClause schema params right -> Condition (Join left right) Ungrouped params -> FromClause schema params left -> FromClause schema params (Join left right) | |
LeftOuterJoin :: FromClause schema params right -> Condition (Join left right) Ungrouped params -> FromClause schema params left -> FromClause schema params (Join left (NullifyTables right)) | |
RightOuterJoin :: FromClause schema params right -> Condition (Join left right) Ungrouped params -> FromClause schema params left -> FromClause schema params (Join (NullifyTables left) right) | |
FullOuterJoin :: FromClause schema params right -> Condition (Join left right) Ungrouped params -> FromClause schema params left -> FromClause schema params (Join (NullifyTables left) (NullifyTables right)) |
renderFromClause :: FromClause schema params tables -> ByteString Source #
Renders a FromClause
.
Grouping
data By (tables :: TablesType) (by :: (Symbol, Symbol)) where Source #
By
s 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
.
data GroupByClause tables 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 Expression
s must be aggregated
in Group Nil
.
Constructors
NoGroups :: GroupByClause tables Ungrouped | |
Group :: SListI bys => NP (By tables) bys -> GroupByClause tables (Grouped bys) |
renderGroupByClause :: GroupByClause tables grouping -> ByteString Source #
Renders a GroupByClause
.
data HavingClause tables 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 tables Ungrouped params | |
Having :: [Condition tables (Grouped bys) params] -> HavingClause tables (Grouped bys) params |
Instances
Eq (HavingClause tables grouping params) Source # | |
Ord (HavingClause tables grouping params) Source # | |
Show (HavingClause tables grouping params) Source # | |
renderHavingClause :: HavingClause tables grouping params -> ByteString Source #
Render a HavingClause
.
Sorting
data SortExpression tables grouping params where Source #
SortExpression
s 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 tables grouping params (Required (NotNull ty)) -> SortExpression tables grouping params | |
Desc :: Expression tables grouping params (Required (NotNull ty)) -> SortExpression tables grouping params | |
AscNullsFirst :: Expression tables grouping params (Required (Null ty)) -> SortExpression tables grouping params | |
AscNullsLast :: Expression tables grouping params (Required (Null ty)) -> SortExpression tables grouping params | |
DescNullsFirst :: Expression tables grouping params (Required (Null ty)) -> SortExpression tables grouping params | |
DescNullsLast :: Expression tables grouping params (Required (Null ty)) -> SortExpression tables grouping params |
Instances
Show (SortExpression tables grouping params) Source # | |
renderSortExpression :: SortExpression tables grouping params -> ByteString Source #
Render a SortExpression
.