| Copyright | (c) Eitan Chatav 2019 |
|---|---|
| Maintainer | eitan@morphism.tech |
| Stability | experimental |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Squeal.PostgreSQL.Query.Table
Description
intermediate table expressions
Synopsis
- data TableExpression (grp :: Grouping) (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType) = TableExpression {
- fromClause :: FromClause lat with db params from
- whereClause :: [Condition 'Ungrouped lat with db params from]
- groupByClause :: GroupByClause grp from
- havingClause :: HavingClause grp lat with db params from
- orderByClause :: [SortExpression grp lat with db params from]
- limitClause :: [Word64]
- offsetClause :: [Word64]
- lockingClauses :: [LockingClause from]
- from :: FromClause lat with db params from -> TableExpression 'Ungrouped lat with db params from
- where_ :: Condition 'Ungrouped lat with db params from -> TableExpression grp lat with db params from -> TableExpression grp lat with db params from
- groupBy :: SListI bys => NP (By from) bys -> TableExpression 'Ungrouped lat with db params from -> TableExpression ('Grouped bys) lat with db params from
- having :: Condition ('Grouped bys) lat with db params from -> TableExpression ('Grouped bys) lat with db params from -> TableExpression ('Grouped bys) lat with db params from
- limit :: Word64 -> TableExpression grp lat with db params from -> TableExpression grp lat with db params from
- offset :: Word64 -> TableExpression grp lat with db params from -> TableExpression grp lat with db params from
- lockRows :: LockingClause from -> TableExpression 'Ungrouped lat with db params from -> TableExpression 'Ungrouped lat with db params from
- data By (from :: FromType) (by :: (Symbol, Symbol)) where
- newtype GroupByClause grp from = UnsafeGroupByClause {}
- data HavingClause grp lat with db params from where
- 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
- data LockingClause from where
- For :: HasAll tabs from tables => LockStrength -> NP Alias tabs -> Waiting -> LockingClause from
- data LockStrength
- = Update
- | NoKeyUpdate
- | Share
- | KeyShare
- data Waiting
- = Wait
- | NoWait
- | SkipLocked
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
| |
Instances
| OrderBy (TableExpression grp) grp Source # | |
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 # | |
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 |
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 # | |
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]))))) | |
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.
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.
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.
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.
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.
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.
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
| (Has rel rels cols, Has col cols ty, by ~ '(rel, col)) => IsQualified rel col (By rels by) Source # | |
| (Has rel rels cols, Has col cols ty, bys ~ '['(rel, col)]) => IsQualified rel col (NP (By rels) bys) Source # | |
| (HasUnique rel rels cols, Has col cols ty, by ~ '(rel, col)) => IsLabel col (By rels by) Source # | |
Defined in Squeal.PostgreSQL.Query.Table | |
| (HasUnique rel rels cols, Has col cols ty, bys ~ '['(rel, col)]) => IsLabel col (NP (By rels) bys) Source # | |
Defined in Squeal.PostgreSQL.Query.Table | |
| Show (By from by) Source # | |
| Eq (By from by) Source # | |
| Ord (By from by) Source # | |
Defined in Squeal.PostgreSQL.Query.Table | |
| RenderSQL (By from by) Source # | |
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.
Constructors
| UnsafeGroupByClause | |
Fields | |
Instances
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
| Show (HavingClause grp lat with db params from) Source # | |
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 # | |
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 # | |
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 |
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
| RenderSQL (LockingClause from) Source # | |
Defined in Squeal.PostgreSQL.Query.Table Methods renderSQL :: LockingClause from -> ByteString Source # | |
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 |
The |
| NoKeyUpdate | |
| Share | Behaves similarly to |
| KeyShare | Behaves similarly to |
Instances
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
| Enum Waiting Source # | |
| Generic Waiting Source # | |
| Read Waiting Source # | |
| Show Waiting Source # | |
| Eq Waiting Source # | |
| Ord Waiting Source # | |
Defined in Squeal.PostgreSQL.Query.Table | |
| RenderSQL Waiting Source # | |
Defined in Squeal.PostgreSQL.Query.Table Methods renderSQL :: Waiting -> ByteString Source # | |
| type Rep Waiting Source # | |
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))) | |