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

Squeal.PostgreSQL.Query.With

Contents

Description

with statements

Synopsis

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.

with can be used for a Query. Multiple CommonTableExpressions can be chained together with the Path constructor :>>, and each CommonTableExpression is constructed via overloaded as.

>>> type Columns = '["col1" ::: 'NoDef :=> 'NotNull 'PGint4, "col2" ::: 'NoDef :=> 'NotNull 'PGint4]
>>> type Schema = '["tab" ::: 'Table ('[] :=> Columns)]
>>> :{
let
  qry :: Query lat with (Public Schema) params '["col1" ::: 'NotNull 'PGint4, "col2" ::: 'NotNull 'PGint4]
  qry = with (
    select Star (from (table #tab)) `as` #cte1 :>>
    select Star (from (common #cte1)) `as` #cte2
    ) (select Star (from (common #cte2)))
in printSQL qry
:}
WITH "cte1" AS (SELECT * FROM "tab" AS "tab"), "cte2" AS (SELECT * FROM "cte1" AS "cte1") SELECT * FROM "cte2" AS "cte2"

You can use data-modifying statements in with. This allows you to perform several different operations in the same query. An example is:

>>> type ProductsColumns = '["product" ::: 'NoDef :=> 'NotNull 'PGtext, "date" ::: 'Def :=> 'NotNull 'PGdate]
>>> type ProductsSchema = '["products" ::: 'Table ('[] :=> ProductsColumns), "products_deleted" ::: 'Table ('[] :=> ProductsColumns)]
>>> :{
let
  manp :: Manipulation with (Public ProductsSchema) '[ 'NotNull 'PGdate] '[]
  manp = with
    (deleteFrom #products NoUsing (#date .< param @1) (Returning Star) `as` #del)
    (insertInto_ #products_deleted (Subquery (select Star (from (common #del)))))
in printSQL manp
:}
WITH "del" AS (DELETE FROM "products" AS "products" WHERE ("date" < ($1 :: date)) RETURNING *) INSERT INTO "products_deleted" AS "products_deleted" SELECT * FROM "del" AS "del"

Methods

with Source #

Arguments

:: Path (CommonTableExpression statement db params) with0 with1

common table expressions

-> statement with1 db params row

larger query

-> statement with0 db params row 

Instances

Instances details
With Manipulation Source # 
Instance details

Defined in Squeal.PostgreSQL.Manipulation

Methods

with :: forall (db :: SchemasType) (params :: [NullType]) (with0 :: FromType) (with1 :: FromType) (row :: RowType). Path (CommonTableExpression Manipulation db params) with0 with1 -> Manipulation with1 db params row -> Manipulation with0 db params row Source #

With (Query lat) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.With

Methods

with :: forall (db :: SchemasType) (params :: [NullType]) (with0 :: FromType) (with1 :: FromType) (row :: RowType). Path (CommonTableExpression (Query lat) db params) with0 with1 -> Query lat with1 db params row -> Query lat with0 db params row Source #

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

Instances details
(KnownSymbol cte, with1 ~ ((cte ::: common) ': with)) => Aliasable cte (statement with db params common) (Path (CommonTableExpression statement db params) with with1) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.With

Methods

as :: statement with db params common -> Alias cte -> Path (CommonTableExpression statement db params) with with1 Source #

(KnownSymbol cte, with1 ~ ((cte ::: common) ': with)) => Aliasable cte (statement with db params common) (CommonTableExpression statement db params with with1) Source # 
Instance details

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

Defined in Squeal.PostgreSQL.Query.With

Methods

renderSQL :: CommonTableExpression statement db params with0 with1 -> ByteString Source #

withRecursive 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 

A withRecursive Query can refer to its own output. A very simple example is this query to sum the integers from 1 through 100:

>>> import Data.Monoid (Sum (..))
>>> import Data.Int (Int64)
>>> :{
  let
    sum100 :: Statement db () (Sum Int64)
    sum100 = 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 sum100
:}
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"

The general form of a recursive WITH query is always a non-recursive term, then union (or unionAll), then a recursive term, where only the recursive term can contain a reference to the query's own output.

data Materialization Source #

Whether the contents of the WITH clause are materialized. If a WITH query is non-recursive and side-effect-free (that is, it is a SELECT containing no volatile functions) then it can be folded into the parent query, allowing joint optimization of the two query levels.

Note: Use of Materialized or NotMaterialized requires PostgreSQL version 12 or higher. For earlier versions, use DefaultMaterialization which in those earlier versions of PostgreSQL behaves as Materialized. PostgreSQL 12 both changes the default behavior as well as adds options for customizing the materialization behavior.

Constructors

DefaultMaterialization

By default, folding happens if the parent query references the WITH query just once, but not if it references the WITH query more than once. Note: this is the behavior in PostgreSQL 12+. In PostgreSQL 11 and earlier, all CTEs are materialized.

Materialized

You can override that decision by specifying MATERIALIZED to force separate calculation of the WITH query. Requires PostgreSQL 12+.

NotMaterialized

or by specifying NOT MATERIALIZED to force it to be merged into the parent query. Requires PostgreSQL 12+.

Instances

Instances details
Enum Materialization Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.With

Eq Materialization Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.With

Ord Materialization Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.With

Read Materialization Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.With

Show Materialization Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.With

Generic Materialization Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.With

Associated Types

type Rep Materialization :: Type -> Type #

Generic Materialization Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.With

Associated Types

type Code Materialization :: [[Type]] #

HasDatatypeInfo Materialization Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.With

RenderSQL Materialization Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.With

type Rep Materialization Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.With

type Rep Materialization = D1 ('MetaData "Materialization" "Squeal.PostgreSQL.Query.With" "squeal-postgresql-0.8.0.0-HHFIvalMWy63oPSAK2xG8g" 'False) (C1 ('MetaCons "DefaultMaterialization" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Materialized" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NotMaterialized" 'PrefixI 'False) (U1 :: Type -> Type)))
type Code Materialization Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.With

type DatatypeInfoOf Materialization Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.With

materialized Source #

Arguments

:: Aliased (statement with db params) (cte ::: common)

CTE

-> CommonTableExpression statement db params with ((cte ::: common) ': with) 

Force separate calculation of the WITH query.

>>> type Columns = '["col1" ::: 'NoDef :=> 'NotNull 'PGint4, "col2" ::: 'NoDef :=> 'NotNull 'PGint4]
>>> type Schema = '["tab" ::: 'Table ('[] :=> Columns)]
>>> :{
let
  qry :: Query lat with (Public Schema) params '["col1" ::: 'NotNull 'PGint4, "col2" ::: 'NotNull 'PGint4]
  qry = with (
    materialized (select Star (from (table #tab)) `as` #cte1) :>>
    select Star (from (common #cte1)) `as` #cte2
    ) (select Star (from (common #cte2)))
in printSQL qry
:}
WITH "cte1" AS MATERIALIZED (SELECT * FROM "tab" AS "tab"), "cte2" AS (SELECT * FROM "cte1" AS "cte1") SELECT * FROM "cte2" AS "cte2"

Note: if the last CTE has materialized or notMaterialized you must add `:>> Done`.

Requires PostgreSQL 12 or higher.

notMaterialized Source #

Arguments

:: Aliased (statement with db params) (cte ::: common)

CTE

-> CommonTableExpression statement db params with ((cte ::: common) ': with) 

Force the WITH query to be merged into the parent query.

>>> type Columns = '["col1" ::: 'NoDef :=> 'NotNull 'PGint4, "col2" ::: 'NoDef :=> 'NotNull 'PGint4]
>>> type Schema = '["tab" ::: 'Table ('[] :=> Columns)]
>>> :{
let
  qry :: Query lat with (Public Schema) params '["col1" ::: 'NotNull 'PGint4, "col2" ::: 'NotNull 'PGint4]
  qry = with (
    select Star (from (table #tab)) `as` #cte1 :>>
    notMaterialized (select Star (from (common #cte1)) `as` #cte2) :>>
    Done
    ) (select Star (from (common #cte2)))
in printSQL qry
:}
WITH "cte1" AS (SELECT * FROM "tab" AS "tab"), "cte2" AS NOT MATERIALIZED (SELECT * FROM "cte1" AS "cte1") SELECT * FROM "cte2" AS "cte2"

Note: if the last CTE has materialized or notMaterialized you must add `:>> Done` to finish the Path.

Requires PostgreSQL 12 or higher.