squeal-postgresql-0.6.0.1: Squeal PostgreSQL Library

Copyright(c) Eitan Chatav 2019
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Squeal.PostgreSQL.Query

Contents

Description

structured query language

Synopsis

Query

type family Query_ (db :: SchemasType) (params :: Type) (row :: Type) where ... Source #

The top level 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.

Query_ is a type family which resolves into a Query, so don't be fooled by the input params and output row Haskell Types, which are converted into appropriate Postgres [NullType] params and RowType rows. Use a top-level Statement to fix actual Haskell input params and output rows.

A top-level 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 parameters and row will be a Haskell record, whose entries will be targeted using overloaded labels.

Let's see some examples of queries.

>>> :set -XDeriveAnyClass -XDerivingStrategies
>>> :{
data Row a b = Row { col1 :: a, col2 :: b }
  deriving stock (GHC.Generic)
  deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo)
:}

simple query:

>>> type Columns = '["col1" ::: 'NoDef :=> 'NotNull 'PGint4, "col2" ::: 'NoDef :=> 'NotNull 'PGint4]
>>> type Schema = '["tab" ::: 'Table ('[] :=> Columns)]
>>> :{
let
  query :: Query_ (Public Schema) () (Row Int32 Int32)
  query = select Star (from (table #tab))
in printSQL query
:}
SELECT * FROM "tab" AS "tab"

restricted query:

>>> :{
let
  query :: Query_ (Public Schema) () (Row Int32 Int32)
  query =
    select_ ((#col1 + #col2) `as` #col1 :* #col1 `as` #col2)
      ( from (table #tab)
        & where_ (#col1 .> #col2)
        & where_ (#col2 .> 0) )
in printSQL query
:}
SELECT ("col1" + "col2") AS "col1", "col1" AS "col2" FROM "tab" AS "tab" WHERE (("col1" > "col2") AND ("col2" > (0 :: int4)))

subquery:

>>> :{
let
  query :: Query_ (Public Schema) () (Row Int32 Int32)
  query = select Star (from (subquery (select Star (from (table #tab)) `as` #sub)))
in printSQL query
:}
SELECT * FROM (SELECT * FROM "tab" AS "tab") AS "sub"

limits and offsets:

>>> :{
let
  query :: Query_ (Public Schema) () (Row Int32 Int32)
  query = select Star (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_ (Public Schema) (Only Int32) (Row Int32 Int32)
  query = select Star (from (table #tab) & where_ (#col1 .> param @1))
in printSQL query
:}
SELECT * FROM "tab" AS "tab" WHERE ("col1" > ($1 :: int4))

aggregation query:

>>> :{
let
  query :: Query_ (Public Schema) () (Row Int64 Int32)
  query =
    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 query
:}
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
  query :: Query_ (Public Schema) () (Row Int32 Int32)
  query = select Star (from (table #tab) & orderBy [#col1 & Asc])
in printSQL query
:}
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"] "customers" '["id"]
  ,"fk_shippers" ::: ForeignKey '["shipper_id"] "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) ]
:}
>>> :{
data Order = Order
  { price :: Float
  , customerName :: Text
  , shipperName :: Text
  } deriving GHC.Generic
instance SOP.Generic Order
instance SOP.HasDatatypeInfo Order
:}
>>> :{
let
  query :: Query_ (Public OrdersSchema) () Order
  query = 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 query
:}
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")
>>> :{
let
  query :: Query_ (Public OrdersSchema) () Order
  query = select_
    ( #o ! #price `as` #price :*
      #c ! #name `as` #customerName :*
      #s ! #name `as` #shipperName )
    ( from (table (#orders `as` #o)
      & (inner.JoinLateral) (select Star (from (table #customers)) `as` #c)
        (#o ! #customer_id .== #c ! #id)
      & (inner.JoinLateral) (select Star (from (table #shippers)) `as` #s)
        (#o ! #shipper_id .== #s ! #id)) )
in printSQL query
:}
SELECT "o"."price" AS "price", "c"."name" AS "customerName", "s"."name" AS "shipperName" FROM "orders" AS "o" INNER JOIN LATERAL (SELECT * FROM "customers" AS "customers") AS "c" ON ("o"."customer_id" = "c"."id") INNER JOIN LATERAL (SELECT * FROM "shippers" AS "shippers") AS "s" ON ("o"."shipper_id" = "s"."id")

self-join:

>>> :{
let
  query :: Query_ (Public Schema) () (Row Int32 Int32)
  query = select
    (#t1 & DotStar)
    (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_ db () (Row String Bool)
  query = values
    ("true" `as` #col1 :* true `as` #col2)
    ["false" `as` #col1 :* false `as` #col2]
in printSQL query
:}
SELECT * FROM (VALUES ((E'true' :: text), TRUE), ((E'false' :: text), FALSE)) AS t ("col1", "col2")

set operations:

>>> :{
let
  query :: Query_ (Public Schema) () (Row Int32 Int32)
  query = select Star (from (table #tab)) `unionAll` select Star (from (table #tab))
in printSQL query
:}
(SELECT * FROM "tab" AS "tab") UNION ALL (SELECT * FROM "tab" AS "tab")

with queries:

>>> :{
let
  query :: Query_ (Public Schema) () (Row Int32 Int32)
  query = with (
    select Star (from (table #tab)) `as` #cte1 :>>
    select Star (from (common #cte1)) `as` #cte2
    ) (select Star (from (common #cte2)))
in printSQL query
:}
WITH "cte1" AS (SELECT * FROM "tab" AS "tab"), "cte2" AS (SELECT * FROM "cte1" AS "cte1") SELECT * FROM "cte2" AS "cte2"

window function queries

>>> :{
let
  query :: Query_ (Public Schema) () (Row Int32 Int64)
  query = select
    (#col1 & Also (rank `as` #col2 `Over` (partitionBy #col1 & orderBy [#col2 & Asc])))
    (from (table #tab))
in printSQL query
:}
SELECT "col1" AS "col1", rank() OVER (PARTITION BY "col1" ORDER BY "col2" ASC) AS "col2" FROM "tab" AS "tab"

correlated subqueries

>>> :{
let
  query :: Query_ (Public Schema) () (Only Int32)
  query =
    select (#col1 `as` #fromOnly) (from (table (#tab `as` #t1))
    & where_ (exists (
      select Star (from (table (#tab `as` #t2))
      & where_ (#t2 ! #col2 .== #t1 ! #col1)))))
in printSQL query
:}
SELECT "col1" AS "fromOnly" FROM "tab" AS "t1" WHERE EXISTS (SELECT * FROM "tab" AS "t2" WHERE ("t2"."col2" = "t1"."col1"))

Equations

Query_ db params row = Query '[] '[] db (TuplePG params) (RowPG row) 

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

  • with :: FromType - scope for all common table expressions,
  • db :: SchemasType - scope for all tables and views,
  • params :: [NullType] - scope for all parameters,
  • row :: RowType - return type of the Query.

Constructors

UnsafeQuery 
Instances
With (Query lat) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.With

Methods

with :: Path (CommonTableExpression (Query lat) db params) with0 with1 -> Query lat with1 db params row -> Query lat with0 db params row Source #

Eq (Query lat with db params row) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

(==) :: 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 #

Ord (Query lat with db params row) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

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 # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

showsPrec :: Int -> Query lat with db params row -> ShowS #

show :: Query lat with db params row -> String #

showList :: [Query lat with db params row] -> ShowS #

Generic (Query lat with db params row) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query

Associated Types

type Rep (Query lat with db params row) :: Type -> Type #

Methods

from :: Query lat with db params row -> Rep (Query lat with db params row) x #

to :: Rep (Query lat with db params row) x -> Query lat with db params row #

NFData (Query lat with db params row) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

rnf :: Query lat with db params row -> () #

RenderSQL (Query lat with db params row) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

renderSQL :: Query lat with db params row -> ByteString Source #

type Rep (Query lat with db params row) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query

type Rep (Query lat with db params row) = D1 (MetaData "Query" "Squeal.PostgreSQL.Query" "squeal-postgresql-0.6.0.1-2mcKKIXTe9UEFlpcl38Onr" True) (C1 (MetaCons "UnsafeQuery" PrefixI True) (S1 (MetaSel (Just "renderQuery") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

Set Operations

union :: Query lat with db params columns -> Query lat with db params columns -> Query lat with db params columns Source #

The results of two queries can be combined using the set operation union. Duplicate rows are eliminated.

unionAll :: Query lat with db params columns -> Query lat with db params columns -> Query lat with db 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 lat with db params columns -> Query lat with db params columns -> Query lat with db params columns Source #

The results of two queries can be combined using the set operation intersect, the intersection. Duplicate rows are eliminated.

intersectAll :: Query lat with db params columns -> Query lat with db params columns -> Query lat with db params columns Source #

The results of two queries can be combined using the set operation intersectAll, the intersection. Duplicate rows are retained.

except :: Query lat with db params columns -> Query lat with db params columns -> Query lat with db 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 lat with db params columns -> Query lat with db params columns -> Query lat with db params columns Source #

The results of two queries can be combined using the set operation exceptAll, the set difference. Duplicate rows are retained.