| Copyright | (c) Eitan Chatav 2019 |
|---|---|
| Maintainer | eitan@morphism.tech |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
Squeal.PostgreSQL.Query.Table
Contents
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]
- 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
- 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
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
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
| |
Instances
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.
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 ': ([] :: [(Symbol, Symbol)]))) => 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 ': ([] :: [(Symbol, Symbol)]))) => IsLabel col (NP (By rels) bys) Source # | |
Defined in Squeal.PostgreSQL.Query.Table | |
| Eq (By from by) Source # | |
| Ord (By from by) Source # | |
Defined in Squeal.PostgreSQL.Query.Table | |
| Show (By from by) Source # | |
| 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
| 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 # | |
| 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 # | |
| 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 # | |