Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | eitan@morphism.tech |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
structured query language
Synopsis
- newtype Query (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (row :: RowType) = UnsafeQuery {}
- type family Query_ (db :: SchemasType) (params :: Type) (row :: Type) where ...
- union :: Query lat with db params columns -> Query lat with db params columns -> Query lat with db params columns
- unionAll :: Query lat with db params columns -> Query lat with db params columns -> Query lat with db params columns
- intersect :: Query lat with db params columns -> Query lat with db params columns -> Query lat with db params columns
- intersectAll :: Query lat with db params columns -> Query lat with db params columns -> Query lat with db params columns
- except :: Query lat with db params columns -> Query lat with db params columns -> Query lat with db params columns
- exceptAll :: Query lat with db params columns -> Query lat with db params columns -> Query lat with db params columns
Query
newtype Query (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (row :: RowType) Source #
The process of retrieving or the command to retrieve data from
a database is called a Query
.
The general Query
type is parameterized by
lat :: FromType
- scope forJoinLateral
and subquery expressions,with :: FromType
- scope for allcommon
table expressions,db :: SchemasType
- scope for alltable
s andview
s,params :: [NullType]
- scope for allparameter
s,row :: RowType
- return type of theQuery
.
Let's see some Query
examples.
simple query:
>>>
type Columns = '["col1" ::: 'NoDef :=> 'NotNull 'PGint4, "col2" ::: 'NoDef :=> 'NotNull 'PGint4]
>>>
type Schema = '["tab" ::: 'Table ('[] :=> Columns)]
>>>
:{
let qry :: Query lat with (Public Schema) '[] '["col1" ::: 'NotNull 'PGint4, "col2" ::: 'NotNull 'PGint4] qry = select Star (from (table #tab)) in printSQL qry :} SELECT * FROM "tab" AS "tab"
restricted query:
>>>
:{
let qry :: Query '[] with (Public Schema) params '["col1" ::: 'NotNull 'PGint4, "col2" ::: 'NotNull 'PGint4] qry = select_ ((#col1 + #col2) `as` #col1 :* #col1 `as` #col2) ( from (table #tab) & where_ (#col1 .> #col2) & where_ (#col2 .> 0) ) in printSQL qry :} SELECT ("col1" + "col2") AS "col1", "col1" AS "col2" FROM "tab" AS "tab" WHERE (("col1" > "col2") AND ("col2" > (0 :: int4)))
subquery:
>>>
:{
let qry :: Query lat with (Public Schema) params '["col1" ::: 'NotNull 'PGint4, "col2" ::: 'NotNull 'PGint4] qry = select Star (from (subquery (select Star (from (table #tab)) `as` #sub))) in printSQL qry :} SELECT * FROM (SELECT * FROM "tab" AS "tab") AS "sub"
limits and offsets:
>>>
:{
let qry :: Query lat with (Public Schema) params '["col1" ::: 'NotNull 'PGint4, "col2" ::: 'NotNull 'PGint4] qry = select Star (from (table #tab) & limit 100 & offset 2 & limit 50 & offset 2) in printSQL qry :} SELECT * FROM "tab" AS "tab" LIMIT 50 OFFSET 4
parameterized query:
>>>
:{
let qry :: Query '[] with (Public Schema) '[ 'NotNull 'PGint4] '["col1" ::: 'NotNull 'PGint4, "col2" ::: 'NotNull 'PGint4] qry = select Star (from (table #tab) & where_ (#col1 .> param @1)) in printSQL qry :} SELECT * FROM "tab" AS "tab" WHERE ("col1" > ($1 :: int4))
aggregation query:
>>>
:{
let qry :: Query '[] with (Public Schema) params '["col1" ::: 'NotNull 'PGint8, "col2" ::: 'NotNull 'PGint4] qry = select_ ((fromNull 0 (sum_ (All #col2))) `as` #col1 :* #col1 `as` #col2) ( from (table (#tab `as` #table1)) & groupBy #col1 & having (sum_ (Distinct #col2) .> 1) ) in printSQL qry :} SELECT COALESCE(sum(ALL "col2"), (0 :: int8)) AS "col1", "col1" AS "col2" FROM "tab" AS "table1" GROUP BY "col1" HAVING (sum(DISTINCT "col2") > (1 :: int8))
sorted query:
>>>
:{
let qry :: Query '[] with (Public Schema) params '["col1" ::: 'NotNull 'PGint4, "col2" ::: 'NotNull 'PGint4] qry = select Star (from (table #tab) & orderBy [#col1 & Asc]) in printSQL qry :} SELECT * FROM "tab" AS "tab" ORDER BY "col1" ASC
joins:
>>>
:{
type OrdersColumns = '[ "id" ::: 'NoDef :=> 'NotNull 'PGint4 , "price" ::: 'NoDef :=> 'NotNull 'PGfloat4 , "customer_id" ::: 'NoDef :=> 'NotNull 'PGint4 , "shipper_id" ::: 'NoDef :=> 'NotNull 'PGint4 ] :}
>>>
:{
type OrdersConstraints = '["pk_orders" ::: PrimaryKey '["id"] ,"fk_customers" ::: ForeignKey '["customer_id"] "public" "customers" '["id"] ,"fk_shippers" ::: ForeignKey '["shipper_id"] "public" "shippers" '["id"] ] :}
>>>
type NamesColumns = '["id" ::: 'NoDef :=> 'NotNull 'PGint4, "name" ::: 'NoDef :=> 'NotNull 'PGtext]
>>>
type CustomersConstraints = '["pk_customers" ::: PrimaryKey '["id"]]
>>>
type ShippersConstraints = '["pk_shippers" ::: PrimaryKey '["id"]]
>>>
:{
type OrdersSchema = '[ "orders" ::: 'Table (OrdersConstraints :=> OrdersColumns) , "customers" ::: 'Table (CustomersConstraints :=> NamesColumns) , "shippers" ::: 'Table (ShippersConstraints :=> NamesColumns) ] :}
>>>
:{
type OrderRow = '[ "price" ::: 'NotNull 'PGfloat4 , "customerName" ::: 'NotNull 'PGtext , "shipperName" ::: 'NotNull 'PGtext ] :}
>>>
:{
let qry :: Query lat with (Public OrdersSchema) params OrderRow qry = select_ ( #o ! #price `as` #price :* #c ! #name `as` #customerName :* #s ! #name `as` #shipperName ) ( 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 qry :} SELECT "o"."price" AS "price", "c"."name" AS "customerName", "s"."name" AS "shipperName" 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 qry :: Query lat with (Public Schema) params '["col1" ::: 'NotNull 'PGint4, "col2" ::: 'NotNull 'PGint4] qry = select (#t1 & DotStar) (from (table (#tab `as` #t1) & crossJoin (table (#tab `as` #t2)))) in printSQL qry :} SELECT "t1".* FROM "tab" AS "t1" CROSS JOIN "tab" AS "t2"
value queries:
>>>
:{
let qry :: Query lat with db params '["col1" ::: 'NotNull 'PGtext, "col2" ::: 'NotNull 'PGbool] qry = values ("true" `as` #col1 :* true `as` #col2) ["false" `as` #col1 :* false `as` #col2] in printSQL qry :} SELECT * FROM (VALUES ((E'true' :: text), TRUE), ((E'false' :: text), FALSE)) AS t ("col1", "col2")
set operations:
>>>
:{
let qry :: Query lat with (Public Schema) params '["col1" ::: 'NotNull 'PGint4, "col2" ::: 'NotNull 'PGint4] qry = select Star (from (table #tab)) `unionAll` select Star (from (table #tab)) in printSQL qry :} (SELECT * FROM "tab" AS "tab") UNION ALL (SELECT * FROM "tab" AS "tab")
with query:
>>>
:{
let qry :: Query lat with (Public Schema) params '["col1" ::: 'NotNull 'PGint4, "col2" ::: 'NotNull 'PGint4] qry = with ( select Star (from (table #tab)) `as` #cte1 :>> select Star (from (common #cte1)) `as` #cte2 ) (select Star (from (common #cte2))) in printSQL qry :} WITH "cte1" AS (SELECT * FROM "tab" AS "tab"), "cte2" AS (SELECT * FROM "cte1" AS "cte1") SELECT * FROM "cte2" AS "cte2"
window functions:
>>>
:{
let qry :: Query '[] with (Public Schema) db '["col1" ::: 'NotNull 'PGint4, "col2" ::: 'NotNull 'PGint8] qry = select (#col1 & Also (rank `as` #col2 `Over` (partitionBy #col1 & orderBy [#col2 & Asc]))) (from (table #tab)) in printSQL qry :} SELECT "col1" AS "col1", rank() OVER (PARTITION BY "col1" ORDER BY "col2" ASC) AS "col2" FROM "tab" AS "tab"
correlated subqueries:
>>>
:{
let qry :: Query '[] with (Public Schema) params '["col1" ::: 'NotNull 'PGint4] qry = select #col1 (from (table (#tab `as` #t1)) & where_ (exists ( select Star (from (table (#tab `as` #t2)) & where_ (#t2 ! #col2 .== #t1 ! #col1))))) in printSQL qry :} SELECT "col1" AS "col1" FROM "tab" AS "t1" WHERE EXISTS (SELECT * FROM "tab" AS "t2" WHERE ("t2"."col2" = "t1"."col1"))
Instances
With (Query lat) Source # | |
Defined in Squeal.PostgreSQL.Query.With | |
Eq (Query lat with db params row) Source # | |
Ord (Query lat with db params row) Source # | |
Defined in Squeal.PostgreSQL.Query compare :: Query lat with db params row -> Query lat with db params row -> Ordering # (<) :: Query lat with db params row -> Query lat with db params row -> Bool # (<=) :: Query lat with db params row -> Query lat with db params row -> Bool # (>) :: Query lat with db params row -> Query lat with db params row -> Bool # (>=) :: Query lat with db params row -> Query lat with db params row -> Bool # max :: Query lat with db params row -> Query lat with db params row -> Query lat with db params row # min :: Query lat with db params row -> Query lat with db params row -> Query lat with db params row # | |
Show (Query lat with db params row) Source # | |
Generic (Query lat with db params row) Source # | |
NFData (Query lat with db params row) Source # | |
Defined in Squeal.PostgreSQL.Query | |
RenderSQL (Query lat with db params row) Source # | |
Defined in Squeal.PostgreSQL.Query renderSQL :: Query lat with db params row -> ByteString Source # | |
type Rep (Query lat with db params row) Source # | |
Defined in Squeal.PostgreSQL.Query type Rep (Query lat with db params row) = D1 ('MetaData "Query" "Squeal.PostgreSQL.Query" "squeal-postgresql-0.9.0.0-D17NIjlcsGRAwJTaCTXyvM" 'True) (C1 ('MetaCons "UnsafeQuery" 'PrefixI 'True) (S1 ('MetaSel ('Just "renderQuery") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |
type family Query_ (db :: SchemasType) (params :: Type) (row :: Type) where ... Source #
The Query_
type is parameterized by a db
SchemasType
,
against which the query is type-checked, an input params
Haskell Type
,
and an ouput row Haskell Type
.
A Query_
can be run
using runQueryParams
, or if params = ()
using runQuery
.
Generally, params
will be a Haskell tuple or record whose entries
may be referenced using positional
parameter
s and row
will be a
Haskell record, whose entries will be targeted using overloaded labels.
Query_
is a type family which resolves into a Query
,
so don't be fooled by the input params and output row Haskell Type
s,
which are converted into appropriate
Postgres [
NullType
]
params and RowType
rows.
Use query
to
fix actual Haskell input params and output rows.
>>>
:set -XDeriveAnyClass -XDerivingStrategies
>>>
type Columns = '["col1" ::: 'NoDef :=> 'Null 'PGint8, "col2" ::: 'Def :=> 'NotNull 'PGtext]
>>>
type Schema = '["tab" ::: 'Table ('[] :=> Columns)]
>>>
:{
data Row = Row { col1 :: Maybe Int64, col2 :: String } deriving stock (GHC.Generic) deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo) :}
>>>
:{
let qry :: Query_ (Public Schema) (Int64, Bool) Row qry = select Star (from (table #tab) & where_ (#col1 .> param @1 .&& just_ (param @2))) stmt :: Statement (Public Schema) (Int64, Bool) Row stmt = query qry :}
>>>
:type qry
qry :: Query '[] '[] '["public" ::: '["tab" ::: 'Table ('[] :=> Columns)]] '[ 'NotNull 'PGint8, 'NotNull 'PGbool] '["col1" ::: 'Null 'PGint8, "col2" ::: 'NotNull 'PGtext]>>>
:type stmt
stmt :: Statement '["public" ::: '["tab" ::: 'Table ('[] :=> Columns)]] (Int64, Bool) Row
Set Operations
:: Query lat with db params columns | |
-> Query lat with db params columns | |
-> Query lat with db params columns |
The results of two queries can be combined using the set operation
union
. Duplicate rows are eliminated.
:: Query lat with db params columns | |
-> Query lat with db params columns | |
-> Query lat with db params columns |
The results of two queries can be combined using the set operation
unionAll
, the disjoint union. Duplicate rows are retained.
:: Query lat with db params columns | |
-> Query lat with db params columns | |
-> Query lat with db params columns |
The results of two queries can be combined using the set operation
intersect
, the intersection. Duplicate rows are eliminated.
:: Query lat with db params columns | |
-> Query lat with db params columns | |
-> Query lat with db params columns |
The results of two queries can be combined using the set operation
intersectAll
, the intersection. Duplicate rows are retained.