squeal-postgresql-0.4.0.0: Squeal PostgreSQL Library

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

Squeal.PostgreSQL.Query

Contents

Description

Squeal queries.

Synopsis

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 
Instances
With Query Source # 
Instance details

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

Defined in Squeal.PostgreSQL.Query

Methods

(==) :: Query schema params columns -> Query schema params columns -> Bool #

(/=) :: Query schema params columns -> Query schema params columns -> Bool #

Ord (Query schema params columns) Source # 
Instance details

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

Defined in Squeal.PostgreSQL.Query

Methods

showsPrec :: Int -> Query schema params columns -> ShowS #

show :: Query schema params columns -> String #

showList :: [Query schema params columns] -> ShowS #

Generic (Query schema params columns) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query

Associated Types

type Rep (Query schema params columns) :: * -> * #

Methods

from :: Query schema params columns -> Rep (Query schema params columns) x #

to :: Rep (Query schema params columns) x -> Query schema params columns #

NFData (Query schema params columns) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

rnf :: Query schema params columns -> () #

RenderSQL (Query schema params columns) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

renderSQL :: Query schema params columns -> ByteString Source #

type Rep (Query schema params columns) Source # 
Instance details

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

select Source #

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.

selectDistinct Source #

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.

selectStar Source #

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.

selectDistinctStar Source #

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.

selectDotStar Source #

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

values Source #

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 query
SELECT * FROM (VALUES (1, E'one')) AS t ("a", "b")

values_ Source #

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

with

Methods

with Source #

Arguments

:: AlignedList (CommonTableExpression statement params) schema0 schema1

common table expressions

-> statement schema1 params row

larger query

-> statement schema0 params row 
Instances
With Query Source # 
Instance details

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

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

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

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 

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

jsonEach Source #

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.

jsonbEach Source #

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.

jsonEachAsText Source #

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.

jsonbEachAsText Source #

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.

jsonObjectKeys Source #

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.

jsonbObjectKeys Source #

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.

jsonPopulateRecord Source #

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.

jsonbPopulateRecord Source #

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.

jsonToRecord Source #

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.

jsonbToRecord Source #

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.

jsonToRecordSet Source #

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.

jsonbToRecordSet Source #

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

  • fromClause :: FromClause schema params 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.

  • whereClause :: [Condition schema from Ungrouped params]

    optional search coditions, combined with .&&. After the processing of the fromClause is done, each row of the derived virtual table is checked against the search condition. If the result of the condition is true, the row is kept in the output table, otherwise it is discarded. The search condition typically references at least one column of the table generated in the fromClause; this is not required, but otherwise the WHERE clause will be fairly useless.

  • groupByClause :: GroupByClause from grouping

    The groupByClause is used to group together those rows in a table that have the same values in all the columns listed. The order in which the columns are listed does not matter. The effect is to combine each set of rows having common values into one group row that represents all rows in the group. This is done to eliminate redundancy in the output and/or compute aggregates that apply to these groups.

  • havingClause :: HavingClause schema from grouping params

    If a table has been grouped using groupBy, but only certain groups are of interest, the havingClause can be used, much like a whereClause, to eliminate groups from the result. Expressions in the havingClause can refer both to grouped expressions and to ungrouped expressions (which necessarily involve an aggregate function).

  • orderByClause :: [SortExpression schema from grouping params]

    The orderByClause is for optional sorting. When more than one SortExpression is specified, the later (right) values are used to sort rows that are equal according to the earlier (left) values.

  • limitClause :: [Word64]

    The limitClause is combined with min to give a limit count if nonempty. If a limit count is given, no more than that many rows will be returned (but possibly fewer, if the query itself yields fewer rows).

  • offsetClause :: [Word64]

    The offsetClause is combined with + to give an offset count if nonempty. The offset count says to skip that many rows before beginning to return rows. The rows are skipped before the limit count is applied.

renderTableExpression :: TableExpression schema params from grouping -> ByteString Source #

from Source #

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.

where_ Source #

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.

groupBy Source #

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.

having Source #

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.

orderBy Source #

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.

limit Source #

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.

offset Source #

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.

Instances
Eq (FromClause schema params from) Source # 
Instance details

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

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

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

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

Defined in Squeal.PostgreSQL.Query

Methods

rnf :: FromClause schema params from -> () #

type Rep (FromClause schema params from) Source # 
Instance details

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.

subquery :: Aliased (Query schema params) rel -> FromClause schema params '[rel] Source #

subquery derives a table from a Query.

view :: Has view schema (View row) => Aliased Alias (alias ::: view) -> FromClause schema params '[alias ::: row] Source #

view derives a table from a View.

crossJoin 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.

innerJoin Source #

Arguments

:: FromClause schema params right

right

-> Condition schema (Join left right) Ungrouped params

on condition

-> FromClause schema params left

left

-> FromClause schema params (Join left right) 

left & innerJoin right on. The joined table is filtered by the on condition.

leftOuterJoin Source #

Arguments

:: FromClause schema params right

right

-> Condition schema (Join left right) Ungrouped params

on condition

-> 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.

rightOuterJoin Source #

Arguments

:: FromClause schema params right

right

-> Condition schema (Join left right) Ungrouped params

on condition

-> 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.

fullOuterJoin Source #

Arguments

:: FromClause schema params right

right

-> Condition schema (Join left right) Ungrouped params

on condition

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

Defined in Squeal.PostgreSQL.Query

Methods

(!) :: Alias rel -> Alias 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 # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

(!) :: Alias rel -> Alias col -> NP (By rels) bys Source #

(HasUnique rel rels cols, Has col cols ty, by ~ (,) rel col) => IsLabel col (By rels by) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

fromLabel :: By rels by #

(HasUnique rel rels cols, Has col cols ty, bys ~ ((,) rel col ': ([] :: [(Symbol, Symbol)]))) => IsLabel col (NP (By rels) bys) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

fromLabel :: NP (By rels) bys #

Eq (By from by) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

(==) :: By from by -> By from by -> Bool #

(/=) :: By from by -> By from by -> Bool #

Ord (By from by) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

compare :: By from by -> By from by -> Ordering #

(<) :: By from by -> By from by -> Bool #

(<=) :: By from by -> By from by -> Bool #

(>) :: By from by -> By from by -> Bool #

(>=) :: By from by -> By from by -> Bool #

max :: By from by -> By from by -> By from by #

min :: By from by -> By from by -> By from by #

Show (By from by) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

showsPrec :: Int -> By from by -> ShowS #

show :: By from by -> String #

showList :: [By from by] -> ShowS #

renderBy :: By from by -> ByteString Source #

Renders a By.

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) 

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

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

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

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

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

in_ Source #

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"))

rowIn Source #

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_ myRow
ROW(1, FALSE) IN (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))

eqAll Source #

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"))

rowEqAll Source #

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_ myRow
ROW(1, FALSE) = ALL (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))

eqAny Source #

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"))

rowEqAny Source #

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_ myRow
ROW(1, FALSE) = ANY (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))

neqAll Source #

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"))

rowNeqAll Source #

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_ myRow
ROW(1, FALSE) <> ALL (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))

neqAny Source #

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"))

rowNeqAny Source #

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_ myRow
ROW(1, FALSE) <> ANY (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))

allLt Source #

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"))

rowLtAll Source #

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_ myRow
ROW(1, FALSE) ALL < (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))

ltAny Source #

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"))

rowLtAny Source #

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_ myRow
ROW(1, FALSE) ALL < (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))

lteAll Source #

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"))

rowLteAll Source #

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_ myRow
ROW(1, FALSE) <= ALL (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))

lteAny Source #

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"))

rowLteAny Source #

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_ myRow
ROW(1, FALSE) <= ANY (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))

gtAll Source #

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"))

rowGtAll Source #

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_ myRow
ROW(1, FALSE) > ALL (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))

gtAny Source #

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"))

rowGtAny Source #

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_ myRow
ROW(1, FALSE) > ANY (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))

gteAll Source #

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"))

rowGteAll Source #

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_ myRow
ROW(1, FALSE) >= ALL (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))

gteAny Source #

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"))

rowGteAny Source #

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_ myRow
ROW(1, FALSE) >= ANY (SELECT * FROM (VALUES (1, FALSE)) AS t ("foo", "bar"))