squeal-postgresql-0.9.1.3: Squeal PostgreSQL Library
Copyright(c) Eitan Chatav 2019
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Squeal.PostgreSQL.Query.Table

Description

intermediate table expressions

Synopsis

Table Expression

data TableExpression (grp :: Grouping) (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType) Source #

A TableExpression computes a table. The table expression contains a fromClause that is optionally followed by a whereClause, groupByClause, havingClause, orderByClause, limitClause offsetClause and lockingClauses. 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 lat with db 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 'Ungrouped lat with db params from]

    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 grp from

    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 grp lat with db params from

    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 grp lat with db params from]

    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.

  • lockingClauses :: [LockingClause from]

    lockingClauses can be added to a table expression with lockRows.

Instances

Instances details
OrderBy (TableExpression grp) grp Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Methods

orderBy :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType). [SortExpression grp lat with db params from] -> TableExpression grp lat with db params from -> TableExpression grp lat with db params from Source #

Generic (TableExpression grp lat with db params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Associated Types

type Rep (TableExpression grp lat with db params from) :: Type -> Type #

Methods

from :: TableExpression grp lat with db params from -> Rep (TableExpression grp lat with db params from) x #

to :: Rep (TableExpression grp lat with db params from) x -> TableExpression grp lat with db params from #

RenderSQL (TableExpression grp lat with db params from) Source #

Render a TableExpression

Instance details

Defined in Squeal.PostgreSQL.Query.Table

Methods

renderSQL :: TableExpression grp lat with db params from -> ByteString Source #

type Rep (TableExpression grp lat with db params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

type Rep (TableExpression grp lat with db params from) = D1 ('MetaData "TableExpression" "Squeal.PostgreSQL.Query.Table" "squeal-postgresql-0.9.1.3-FfCgbPNg57H53ZAGizr3Nu" 'False) (C1 ('MetaCons "TableExpression" 'PrefixI 'True) (((S1 ('MetaSel ('Just "fromClause") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (FromClause lat with db params from)) :*: S1 ('MetaSel ('Just "whereClause") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Condition 'Ungrouped lat with db params from])) :*: (S1 ('MetaSel ('Just "groupByClause") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GroupByClause grp from)) :*: S1 ('MetaSel ('Just "havingClause") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HavingClause grp lat with db params from)))) :*: ((S1 ('MetaSel ('Just "orderByClause") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SortExpression grp lat with db params from]) :*: S1 ('MetaSel ('Just "limitClause") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Word64])) :*: (S1 ('MetaSel ('Just "offsetClause") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Word64]) :*: S1 ('MetaSel ('Just "lockingClauses") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [LockingClause from])))))

from Source #

Arguments

:: FromClause lat with db params from

table reference

-> TableExpression 'Ungrouped lat with db params from 

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_, groupBy, having, orderBy, limit and offset, using the & operator to match the left-to-right sequencing of their placement in SQL.

where_ Source #

Arguments

:: Condition 'Ungrouped lat with db params from

filtering condition

-> TableExpression grp lat with db params from 
-> TableExpression grp lat with db params from 

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 'Ungrouped lat with db params from 
-> TableExpression ('Grouped bys) lat with db params from 

A groupBy is a transformation of TableExpressions which switches its Grouping from Ungrouped to Grouped. Use groupBy Nil to perform a "grand total" aggregation query.

having Source #

Arguments

:: Condition ('Grouped bys) lat with db params from

having condition

-> TableExpression ('Grouped bys) lat with db params from 
-> TableExpression ('Grouped bys) lat with db params from 

A having is an endomorphism of TableExpressions which adds a search condition to the havingClause.

limit Source #

Arguments

:: Word64

limit parameter

-> TableExpression grp lat with db params from 
-> TableExpression grp lat with db params from 

A limit is an endomorphism of TableExpressions which adds to the limitClause.

offset Source #

Arguments

:: Word64

offset parameter

-> TableExpression grp lat with db params from 
-> TableExpression grp lat with db params from 

An offset is an endomorphism of TableExpressions which adds to the offsetClause.

lockRows Source #

Arguments

:: LockingClause from

row-level lock

-> TableExpression 'Ungrouped lat with db params from 
-> TableExpression 'Ungrouped lat with db params from 

Add a LockingClause to a TableExpression. Multiple LockingClauses can be written if it is necessary to specify different locking behavior for different tables. If the same table is mentioned (or implicitly affected) by more than one locking clause, then it is processed as if it was only specified by the strongest one. Similarly, a table is processed as NoWait if that is specified in any of the clauses affecting it. Otherwise, it is processed as SkipLocked if that is specified in any of the clauses affecting it. Further, a LockingClause cannot be added to a grouped table expression.

Grouping

data By (from :: FromType) (by :: (Symbol, Symbol)) where Source #

Bys are used in groupBy 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

Instances details
(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.Table

Methods

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

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

Defined in Squeal.PostgreSQL.Query.Table

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

Methods

fromLabel :: By rels by #

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

Defined in Squeal.PostgreSQL.Query.Table

Methods

fromLabel :: NP (By rels) bys #

Show (By from by) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Methods

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

show :: By from by -> String #

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

Eq (By from by) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

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

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 #

RenderSQL (By from by) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Methods

renderSQL :: By from by -> ByteString Source #

newtype GroupByClause grp from Source #

A GroupByClause indicates the Grouping of a TableExpression.

Instances

Instances details
Generic (GroupByClause grp from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Associated Types

type Rep (GroupByClause grp from) :: Type -> Type #

Methods

from :: GroupByClause grp from -> Rep (GroupByClause grp from) x #

to :: Rep (GroupByClause grp from) x -> GroupByClause grp from #

Show (GroupByClause grp from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Methods

showsPrec :: Int -> GroupByClause grp from -> ShowS #

show :: GroupByClause grp from -> String #

showList :: [GroupByClause grp from] -> ShowS #

NFData (GroupByClause grp from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Methods

rnf :: GroupByClause grp from -> () #

Eq (GroupByClause grp from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Methods

(==) :: GroupByClause grp from -> GroupByClause grp from -> Bool #

(/=) :: GroupByClause grp from -> GroupByClause grp from -> Bool #

Ord (GroupByClause grp from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Methods

compare :: GroupByClause grp from -> GroupByClause grp from -> Ordering #

(<) :: GroupByClause grp from -> GroupByClause grp from -> Bool #

(<=) :: GroupByClause grp from -> GroupByClause grp from -> Bool #

(>) :: GroupByClause grp from -> GroupByClause grp from -> Bool #

(>=) :: GroupByClause grp from -> GroupByClause grp from -> Bool #

max :: GroupByClause grp from -> GroupByClause grp from -> GroupByClause grp from #

min :: GroupByClause grp from -> GroupByClause grp from -> GroupByClause grp from #

RenderSQL (GroupByClause grp from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Methods

renderSQL :: GroupByClause grp from -> ByteString Source #

type Rep (GroupByClause grp from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

type Rep (GroupByClause grp from) = D1 ('MetaData "GroupByClause" "Squeal.PostgreSQL.Query.Table" "squeal-postgresql-0.9.1.3-FfCgbPNg57H53ZAGizr3Nu" 'True) (C1 ('MetaCons "UnsafeGroupByClause" 'PrefixI 'True) (S1 ('MetaSel ('Just "renderGroupByClause") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

data HavingClause grp lat with db params from 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 'Ungrouped lat with db params from 
Having :: [Condition ('Grouped bys) lat with db params from] -> HavingClause ('Grouped bys) lat with db params from 

Instances

Instances details
Show (HavingClause grp lat with db params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Methods

showsPrec :: Int -> HavingClause grp lat with db params from -> ShowS #

show :: HavingClause grp lat with db params from -> String #

showList :: [HavingClause grp lat with db params from] -> ShowS #

Eq (HavingClause grp lat with db params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Methods

(==) :: HavingClause grp lat with db params from -> HavingClause grp lat with db params from -> Bool #

(/=) :: HavingClause grp lat with db params from -> HavingClause grp lat with db params from -> Bool #

Ord (HavingClause grp lat with db params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Methods

compare :: HavingClause grp lat with db params from -> HavingClause grp lat with db params from -> Ordering #

(<) :: HavingClause grp lat with db params from -> HavingClause grp lat with db params from -> Bool #

(<=) :: HavingClause grp lat with db params from -> HavingClause grp lat with db params from -> Bool #

(>) :: HavingClause grp lat with db params from -> HavingClause grp lat with db params from -> Bool #

(>=) :: HavingClause grp lat with db params from -> HavingClause grp lat with db params from -> Bool #

max :: HavingClause grp lat with db params from -> HavingClause grp lat with db params from -> HavingClause grp lat with db params from #

min :: HavingClause grp lat with db params from -> HavingClause grp lat with db params from -> HavingClause grp lat with db params from #

RenderSQL (HavingClause grp lat with db params from) Source #

Render a HavingClause.

Instance details

Defined in Squeal.PostgreSQL.Query.Table

Methods

renderSQL :: HavingClause grp lat with db params from -> ByteString Source #

Row Locks

data LockingClause from where Source #

If specific tables are named in a locking clause, then only rows coming from those tables are locked; any other tables used in the select are simply read as usual. A locking clause with a Nil table list affects all tables used in the statement. If a locking clause is applied to a view or subquery, it affects all tables used in the view or subquery. However, these clauses do not apply to with queries referenced by the primary query. If you want row locking to occur within a with query, specify a LockingClause within the with query.

Constructors

For 

Fields

Instances

Instances details
RenderSQL (LockingClause from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

data LockStrength Source #

Row-level locks, which are listed as below with the contexts in which they are used automatically by PostgreSQL. Note that a transaction can hold conflicting locks on the same row, even in different subtransactions; but other than that, two transactions can never hold conflicting locks on the same row. Row-level locks do not affect data querying; they block only writers and lockers to the same row. Row-level locks are released at transaction end or during savepoint rollback.

Constructors

Update

For Update causes the rows retrieved by the select statement to be locked as though for update. This prevents them from being locked, modified or deleted by other transactions until the current transaction ends. That is, other transactions that attempt update, deleteFrom, select For Update, select For NoKeyUpdate, select For Share or select For KeyShare of these rows will be blocked until the current transaction ends; conversely, select For Update will wait for a concurrent transaction that has run any of those commands on the same row, and will then lock and return the updated row (or no row, if the row was deleted). Within a RepeatableRead or Serializable transaction, however, an error will be thrown if a row to be locked has changed since the transaction started.

The For Update lock mode is also acquired by any deleteFrom a row, and also by an Update that modifies the values on certain columns. Currently, the set of columns considered for the update case are those that have a unique index on them that can be used in a foreign key (so partial indexes and expressional indexes are not considered), but this may change in the future.

NoKeyUpdate 
Share

Behaves similarly to For Update, except that the lock acquired is weaker: this lock will not block select For KeyShare commands that attempt to acquire a lock on the same rows. This lock mode is also acquired by any update that does not acquire a For Update lock.

KeyShare

Behaves similarly to For Share, except that the lock is weaker: select For Update is blocked, but not select For NoKeyUpdate. A key-shared lock blocks other transactions from performing deleteFrom or any update that changes the key values, but not other Update, and neither does it prevent select For NoKeyUpdate, select For Share, or select For KeyShare.

Instances

Instances details
Enum LockStrength Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Generic LockStrength Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Associated Types

type Rep LockStrength :: Type -> Type #

Read LockStrength Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Show LockStrength Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Eq LockStrength Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Ord LockStrength Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

RenderSQL LockStrength Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

type Rep LockStrength Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

type Rep LockStrength = D1 ('MetaData "LockStrength" "Squeal.PostgreSQL.Query.Table" "squeal-postgresql-0.9.1.3-FfCgbPNg57H53ZAGizr3Nu" 'False) ((C1 ('MetaCons "Update" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoKeyUpdate" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Share" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyShare" 'PrefixI 'False) (U1 :: Type -> Type)))

data Waiting Source #

To prevent the operation from Waiting for other transactions to commit, use either the NoWait or SkipLocked option.

Constructors

Wait

wait for other transactions to commit

NoWait

reports an error, rather than waiting

SkipLocked

any selected rows that cannot be immediately locked are skipped

Instances

Instances details
Enum Waiting Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Generic Waiting Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Associated Types

type Rep Waiting :: Type -> Type #

Methods

from :: Waiting -> Rep Waiting x #

to :: Rep Waiting x -> Waiting #

Read Waiting Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Show Waiting Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Eq Waiting Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Methods

(==) :: Waiting -> Waiting -> Bool #

(/=) :: Waiting -> Waiting -> Bool #

Ord Waiting Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

RenderSQL Waiting Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

type Rep Waiting Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

type Rep Waiting = D1 ('MetaData "Waiting" "Squeal.PostgreSQL.Query.Table" "squeal-postgresql-0.9.1.3-FfCgbPNg57H53ZAGizr3Nu" 'False) (C1 ('MetaCons "Wait" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NoWait" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SkipLocked" 'PrefixI 'False) (U1 :: Type -> Type)))