Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | [email protected] |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Squeal.PostgreSQL.Query.With
Contents
Description
with statements
Synopsis
- class With statement where
- with :: Path (CommonTableExpression statement db params) with0 with1 -> statement with1 db params row -> statement with0 db params row
- data CommonTableExpression statement (db :: SchemasType) (params :: [NullType]) (with0 :: FromType) (with1 :: FromType) where
- CommonTableExpression :: Aliased (statement with db params) (cte ::: common) -> CommonTableExpression statement db params with ((cte ::: common) ': with)
- withRecursive :: Aliased (Query lat (recursive ': with) db params) recursive -> Query lat (recursive ': with) db params row -> Query lat with db params row
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 CommonTableExpression
s, can be thought of as
defining temporary tables that exist just for one query.
Methods
Arguments
:: Path (CommonTableExpression statement db params) with0 with1 | common table expressions |
-> statement with1 db params row | larger query |
-> statement with0 db params row |
Instances
With Manipulation Source # | |
Defined in Squeal.PostgreSQL.Manipulation Methods with :: Path (CommonTableExpression Manipulation db params) with0 with1 -> Manipulation with1 db params row -> Manipulation with0 db params row Source # | |
With (Query lat) Source # | |
Defined in Squeal.PostgreSQL.Query.With |
data CommonTableExpression statement (db :: SchemasType) (params :: [NullType]) (with0 :: FromType) (with1 :: FromType) where Source #
A CommonTableExpression
is an auxiliary statement in a with
clause.
Constructors
CommonTableExpression | |
Fields
|
Instances
(KnownSymbol cte, with1 ~ ((cte ::: common) ': with)) => Aliasable cte (statement with db params common) (Path (CommonTableExpression statement db params) with with1) Source # | |
Defined in Squeal.PostgreSQL.Query.With | |
(KnownSymbol cte, with1 ~ ((cte ::: common) ': with)) => Aliasable cte (statement with db params common) (CommonTableExpression statement db params with with1) Source # | |
Defined in Squeal.PostgreSQL.Query.With Methods as :: statement with db params common -> Alias cte -> CommonTableExpression statement db params with with1 Source # | |
(forall (c :: FromType) (s :: SchemasType) (p :: [NullType]) (r :: RowType). RenderSQL (statement c s p r)) => RenderSQL (CommonTableExpression statement db params with0 with1) Source # | |
Defined in Squeal.PostgreSQL.Query.With Methods renderSQL :: CommonTableExpression statement db params with0 with1 -> ByteString Source # |
Arguments
:: Aliased (Query lat (recursive ': with) db params) recursive | recursive query |
-> Query lat (recursive ': with) db params row | larger query |
-> Query lat with db params row |
>>>
import Data.Monoid (Sum (..))
>>>
import Data.Int (Int64)
>>>
:{
let query :: Query_ schema () (Sum Int64) query = withRecursive ( values_ ((1 & astype int) `as` #n) `unionAll` select_ ((#n + 1) `as` #n) (from (common #t) & where_ (#n .< 100)) `as` #t ) ( select_ (fromNull 0 (sum_ (All #n)) `as` #getSum) (from (common #t) & groupBy Nil)) in printSQL query :} WITH RECURSIVE "t" AS ((SELECT * FROM (VALUES (((1 :: int4) :: int))) AS t ("n")) UNION ALL (SELECT ("n" + (1 :: int4)) AS "n" FROM "t" AS "t" WHERE ("n" < (100 :: int4)))) SELECT COALESCE(sum(ALL "n"), (0 :: int8)) AS "getSum" FROM "t" AS "t"