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

Squeal.PostgreSQL.Type.Schema

Description

Provides a type-level DSL for kinds of Postgres types, tables, schema, constraints, and more. It also defines useful type families to operate on these.

Synopsis

Postgres Type

data PGType Source #

PGType is the promoted datakind of PostgreSQL types.

>>> :kind 'PGbool
'PGbool :: PGType

Constructors

PGbool

logical Boolean (true/false)

PGint2

signed two-byte integer

PGint4

signed four-byte integer

PGint8

signed eight-byte integer

PGnumeric

arbitrary precision numeric type

PGfloat4

single precision floating-point number (4 bytes)

PGfloat8

double precision floating-point number (8 bytes)

PGmoney

currency amount

PGchar Nat

fixed-length character string

PGvarchar Nat

variable-length character string

PGtext

variable-length character string

PGbytea

binary data ("byte array")

PGtimestamp

date and time (no time zone)

PGtimestamptz

date and time, including time zone

PGdate

calendar date (year, month, day)

PGtime

time of day (no time zone)

PGtimetz

time of day, including time zone

PGinterval

time span

PGuuid

universally unique identifier

PGinet

IPv4 or IPv6 host address

PGjson

textual JSON data

PGjsonb

binary JSON data, decomposed

PGvararray NullType

variable length array

PGfixarray [Nat] NullType

fixed length array

PGenum [Symbol]

enumerated (enum) types are data types that comprise a static, ordered set of values.

PGcomposite RowType

a composite type represents the structure of a row or record; it is essentially just a list of field names and their data types.

PGtsvector

A tsvector value is a sorted list of distinct lexemes, which are words that have been normalized to merge different variants of the same word.

PGtsquery

A tsquery value stores lexemes that are to be searched for.

PGoid

Object identifiers (OIDs) are used internally by PostgreSQL as primary keys for various system tables.

PGrange PGType

Range types are data types representing a range of values of some element type (called the range's subtype).

UnsafePGType Symbol

an escape hatch for unsupported PostgreSQL types

Instances

Instances details
PGSubset 'PGjsonb Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(@>) :: forall (null0 :: k -> NullType) (null1 :: k -> NullType). Operator (null0 'PGjsonb) (null1 'PGjsonb) ('Null 'PGbool) Source #

(<@) :: forall (null0 :: k -> NullType) (null1 :: k -> NullType). Operator (null0 'PGjsonb) (null1 'PGjsonb) ('Null 'PGbool) Source #

PGSubset 'PGtsquery Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(@>) :: forall (null0 :: k -> NullType) (null1 :: k -> NullType). Operator (null0 'PGtsquery) (null1 'PGtsquery) ('Null 'PGbool) Source #

(<@) :: forall (null0 :: k -> NullType) (null1 :: k -> NullType). Operator (null0 'PGtsquery) (null1 'PGtsquery) ('Null 'PGbool) Source #

TimeOp 'PGtimestamp 'PGinterval Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

Methods

(!+) :: forall (null :: k -> NullType). Operator (null 'PGtimestamp) (null 'PGinterval) (null 'PGtimestamp) Source #

(+!) :: forall (null :: k -> NullType). Operator (null 'PGinterval) (null 'PGtimestamp) (null 'PGtimestamp) Source #

(!-) :: forall (null :: k -> NullType). Operator (null 'PGtimestamp) (null 'PGinterval) (null 'PGtimestamp) Source #

(!-!) :: forall (null :: k -> NullType). Operator (null 'PGtimestamp) (null 'PGtimestamp) (null 'PGinterval) Source #

TimeOp 'PGtimestamptz 'PGinterval Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

Methods

(!+) :: forall (null :: k -> NullType). Operator (null 'PGtimestamptz) (null 'PGinterval) (null 'PGtimestamptz) Source #

(+!) :: forall (null :: k -> NullType). Operator (null 'PGinterval) (null 'PGtimestamptz) (null 'PGtimestamptz) Source #

(!-) :: forall (null :: k -> NullType). Operator (null 'PGtimestamptz) (null 'PGinterval) (null 'PGtimestamptz) Source #

(!-!) :: forall (null :: k -> NullType). Operator (null 'PGtimestamptz) (null 'PGtimestamptz) (null 'PGinterval) Source #

TimeOp 'PGdate 'PGint4 Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

Methods

(!+) :: forall (null :: k -> NullType). Operator (null 'PGdate) (null 'PGint4) (null 'PGdate) Source #

(+!) :: forall (null :: k -> NullType). Operator (null 'PGint4) (null 'PGdate) (null 'PGdate) Source #

(!-) :: forall (null :: k -> NullType). Operator (null 'PGdate) (null 'PGint4) (null 'PGdate) Source #

(!-!) :: forall (null :: k -> NullType). Operator (null 'PGdate) (null 'PGdate) (null 'PGint4) Source #

TimeOp 'PGtime 'PGinterval Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

Methods

(!+) :: forall (null :: k -> NullType). Operator (null 'PGtime) (null 'PGinterval) (null 'PGtime) Source #

(+!) :: forall (null :: k -> NullType). Operator (null 'PGinterval) (null 'PGtime) (null 'PGtime) Source #

(!-) :: forall (null :: k -> NullType). Operator (null 'PGtime) (null 'PGinterval) (null 'PGtime) Source #

(!-!) :: forall (null :: k -> NullType). Operator (null 'PGtime) (null 'PGtime) (null 'PGinterval) Source #

TimeOp 'PGtimetz 'PGinterval Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

Methods

(!+) :: forall (null :: k -> NullType). Operator (null 'PGtimetz) (null 'PGinterval) (null 'PGtimetz) Source #

(+!) :: forall (null :: k -> NullType). Operator (null 'PGinterval) (null 'PGtimetz) (null 'PGtimetz) Source #

(!-) :: forall (null :: k -> NullType). Operator (null 'PGtimetz) (null 'PGinterval) (null 'PGtimetz) Source #

(!-!) :: forall (null :: k -> NullType). Operator (null 'PGtimetz) (null 'PGtimetz) (null 'PGinterval) Source #

TimeOp 'PGinterval 'PGinterval Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

Methods

(!+) :: forall (null :: k -> NullType). Operator (null 'PGinterval) (null 'PGinterval) (null 'PGinterval) Source #

(+!) :: forall (null :: k -> NullType). Operator (null 'PGinterval) (null 'PGinterval) (null 'PGinterval) Source #

(!-) :: forall (null :: k -> NullType). Operator (null 'PGinterval) (null 'PGinterval) (null 'PGinterval) Source #

(!-!) :: forall (null :: k -> NullType). Operator (null 'PGinterval) (null 'PGinterval) (null 'PGinterval) Source #

PGIntersect ('PGvararray ty :: PGType) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(@&&) :: forall (null0 :: k -> NullType) (null1 :: k -> NullType). Operator (null0 ('PGvararray ty)) (null1 ('PGvararray ty)) ('Null 'PGbool) Source #

PGIntersect ('PGrange ty :: PGType) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(@&&) :: forall (null0 :: k -> NullType) (null1 :: k -> NullType). Operator (null0 ('PGrange ty)) (null1 ('PGrange ty)) ('Null 'PGbool) Source #

PGSubset ('PGvararray ty :: PGType) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(@>) :: forall (null0 :: k -> NullType) (null1 :: k -> NullType). Operator (null0 ('PGvararray ty)) (null1 ('PGvararray ty)) ('Null 'PGbool) Source #

(<@) :: forall (null0 :: k -> NullType) (null1 :: k -> NullType). Operator (null0 ('PGvararray ty)) (null1 ('PGvararray ty)) ('Null 'PGbool) Source #

PGSubset ('PGrange ty :: PGType) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(@>) :: forall (null0 :: k -> NullType) (null1 :: k -> NullType). Operator (null0 ('PGrange ty)) (null1 ('PGrange ty)) ('Null 'PGbool) Source #

(<@) :: forall (null0 :: k -> NullType) (null1 :: k -> NullType). Operator (null0 ('PGrange ty)) (null1 ('PGrange ty)) ('Null 'PGbool) Source #

data NullType Source #

NullType encodes the potential presence or definite absence of a NULL allowing operations which are sensitive to such to be well typed.

>>> :kind 'Null 'PGint4
'Null 'PGint4 :: NullType
>>> :kind 'NotNull ('PGvarchar 50)
'NotNull ('PGvarchar 50) :: NullType

Constructors

Null PGType

NULL may be present

NotNull PGType

NULL is absent

Instances

Instances details
Aggregate AggregateArg (Expression ('Grouped bys) :: FromType -> FromType -> SchemasType -> [NullType] -> FromType -> NullType -> Type) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Aggregate

Methods

countStar :: forall (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). Expression ('Grouped bys) lat with db params from ('NotNull 'PGint8) Source #

count :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('NotNull 'PGint8) Source #

sum_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGSum ty)) Source #

arrayAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null ('PGvararray ty)) Source #

jsonAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGjson) Source #

jsonbAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGjsonb) Source #

bitAnd :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => AggregateArg '[null int] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null int) Source #

bitOr :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => AggregateArg '[null int] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null int) Source #

boolAnd :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGbool] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGbool) Source #

boolOr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGbool] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGbool) Source #

every :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGbool] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGbool) Source #

max_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null ty) Source #

min_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null ty) Source #

avg :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source #

corr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source #

covarPop :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source #

covarSamp :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source #

regrAvgX :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source #

regrAvgY :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source #

regrCount :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGint8) Source #

regrIntercept :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source #

regrR2 :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source #

regrSlope :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source #

regrSxx :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source #

regrSxy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source #

regrSyy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source #

stddev :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source #

stddevPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source #

stddevSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source #

variance :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source #

varPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source #

varSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source #

Aggregate (WindowArg grp :: [NullType] -> FromType -> FromType -> SchemasType -> [NullType] -> FromType -> Type) (WindowFunction grp :: FromType -> FromType -> SchemasType -> [NullType] -> FromType -> NullType -> Type) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Window

Methods

countStar :: forall (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowFunction grp lat with db params from ('NotNull 'PGint8) Source #

count :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('NotNull 'PGint8) Source #

sum_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGSum ty)) Source #

arrayAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('Null ('PGvararray ty)) Source #

jsonAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGjson) Source #

jsonbAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGjsonb) Source #

bitAnd :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => WindowArg grp '[null int] lat with db params from -> WindowFunction grp lat with db params from ('Null int) Source #

bitOr :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => WindowArg grp '[null int] lat with db params from -> WindowFunction grp lat with db params from ('Null int) Source #

boolAnd :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGbool] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGbool) Source #

boolOr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGbool] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGbool) Source #

every :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGbool] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGbool) Source #

max_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null ty) Source #

min_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null ty) Source #

avg :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

corr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

covarPop :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

covarSamp :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrAvgX :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrAvgY :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrCount :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGint8) Source #

regrIntercept :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrR2 :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrSlope :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrSxx :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrSxy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrSyy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

stddev :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

stddevPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

stddevSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

variance :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

varPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

varSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

(Has tab (Join from lat) row, Has col row ty, GroupedBy tab col bys, columns ~ '[col ::: ty]) => IsQualified tab col (NP (Aliased (Expression ('Grouped bys) lat with db params from)) columns) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias tab -> Alias col -> NP (Aliased (Expression ('Grouped bys) lat with db params from)) columns Source #

(Has tab (Join from lat) row, Has col row ty, GroupedBy tab col bys, column ~ (col ::: ty)) => IsQualified tab col (Aliased (Expression ('Grouped bys) lat with db params from) column) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias tab -> Alias col -> Aliased (Expression ('Grouped bys) lat with db params from) column Source #

(Has tab (Join from lat) row, Has col row ty, GroupedBy tab col bys, tys ~ '[ty]) => IsQualified tab col (NP (Expression ('Grouped bys) lat with db params from) tys) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias tab -> Alias col -> NP (Expression ('Grouped bys) lat with db params from) tys Source #

(Has tab (Join from lat) row, Has col row ty, columns ~ '[col ::: ty]) => IsQualified tab col (NP (Aliased (Expression 'Ungrouped lat with db params from)) columns) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias tab -> Alias col -> NP (Aliased (Expression 'Ungrouped lat with db params from)) columns Source #

(Has tab (Join from lat) row, Has col row ty, column ~ (col ::: ty)) => IsQualified tab col (Aliased (Expression 'Ungrouped lat with db params from) column) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias tab -> Alias col -> Aliased (Expression 'Ungrouped lat with db params from) column Source #

(Has tab (Join from lat) row, Has col row ty, tys ~ '[ty]) => IsQualified tab col (NP (Expression 'Ungrouped lat with db params from) tys) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias tab -> Alias col -> NP (Expression 'Ungrouped lat with db params from) tys Source #

(Has tab (Join from lat) row, Has col row ty) => IsQualified tab col (AggregateArg '[ty] lat with db params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Aggregate

Methods

(!) :: Alias tab -> Alias col -> AggregateArg '[ty] lat with db params from Source #

(Has tab (Join from lat) row, Has col row ty, GroupedBy tab col bys) => IsQualified tab col (WindowArg ('Grouped bys) '[ty] lat with db params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Window

Methods

(!) :: Alias tab -> Alias col -> WindowArg ('Grouped bys) '[ty] lat with db params from Source #

(Has tab (Join from lat) row, Has col row ty) => IsQualified tab col (WindowArg 'Ungrouped '[ty] lat with db params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Window

Methods

(!) :: Alias tab -> Alias col -> WindowArg 'Ungrouped '[ty] lat with db params from Source #

IsLabel fld (MaybeT (DecodeRow row) y) => IsLabel fld (MaybeT (DecodeRow (field ': row)) y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Methods

fromLabel :: MaybeT (DecodeRow (field ': row)) y #

(KnownSymbol fld, FromValue ty (Maybe y)) => IsLabel fld (MaybeT (DecodeRow ((fld ::: ty) ': row)) y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Methods

fromLabel :: MaybeT (DecodeRow ((fld ::: ty) ': row)) y #

IsLabel fld (DecodeRow row y) => IsLabel fld (DecodeRow (field ': row) y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Methods

fromLabel :: DecodeRow (field ': row) y #

(KnownSymbol fld, FromValue ty y) => IsLabel fld (DecodeRow ((fld ::: ty) ': row) y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Methods

fromLabel :: DecodeRow ((fld ::: ty) ': row) y #

(HasUnique tab (Join from lat) row, Has col row ty, GroupedBy tab col bys, columns ~ '[col ::: ty]) => IsLabel col (NP (Aliased (Expression ('Grouped bys) lat with db params from)) columns) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: NP (Aliased (Expression ('Grouped bys) lat with db params from)) columns #

(HasUnique tab (Join from lat) row, Has col row ty, GroupedBy tab col bys, column ~ (col ::: ty)) => IsLabel col (Aliased (Expression ('Grouped bys) lat with db params from) column) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: Aliased (Expression ('Grouped bys) lat with db params from) column #

(HasUnique tab (Join from lat) row, Has col row ty, GroupedBy tab col bys, tys ~ '[ty]) => IsLabel col (NP (Expression ('Grouped bys) lat with db params from) tys) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: NP (Expression ('Grouped bys) lat with db params from) tys #

(HasUnique tab (Join from lat) row, Has col row ty, columns ~ '[col ::: ty]) => IsLabel col (NP (Aliased (Expression 'Ungrouped lat with db params from)) columns) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: NP (Aliased (Expression 'Ungrouped lat with db params from)) columns #

(HasUnique tab (Join from lat) row, Has col row ty, column ~ (col ::: ty)) => IsLabel col (Aliased (Expression 'Ungrouped lat with db params from) column) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: Aliased (Expression 'Ungrouped lat with db params from) column #

(HasUnique tab (Join from lat) row, Has col row ty, tys ~ '[ty]) => IsLabel col (NP (Expression 'Ungrouped lat with db params from) tys) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: NP (Expression 'Ungrouped lat with db params from) tys #

OidOfNull db ty => OidOfField db (fld ::: ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Oid

(KnownSymbol alias, NullTyped db ty) => FieldTyped db (alias ::: ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

fieldtype :: Aliased (TypeExpression db) (alias ::: ty) Source #

(fld0 ~ fld1, ToParam db ty x) => ToField db (fld0 ::: ty) (fld1 ::: x) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

Methods

toField :: P (fld1 ::: x) -> ReaderT (K Connection db) IO (K (Maybe Encoding) (fld0 ::: ty)) Source #

NullTyped db ('NotNull ty) => ColumnTyped db ('NoDef :=> 'NotNull ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

NullTyped db ('Null ty) => ColumnTyped db ('NoDef :=> 'Null ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

(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 #

(HasUnique tab (Join from lat) row, Has col row ty) => IsLabel col (AggregateArg '[ty] lat with db params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Aggregate

Methods

fromLabel :: AggregateArg '[ty] lat with db params from #

(HasUnique tab (Join from lat) row, Has col row ty, GroupedBy tab col bys) => IsLabel col (WindowArg ('Grouped bys) '[ty] lat with db params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Window

Methods

fromLabel :: WindowArg ('Grouped bys) '[ty] lat with db params from #

(HasUnique tab (Join from lat) row, Has col row ty) => IsLabel col (WindowArg 'Ungrouped '[ty] lat with db params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Window

Methods

fromLabel :: WindowArg 'Ungrouped '[ty] lat with db params from #

JsonBuildObject ('[] :: [NullType]) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Json

Methods

jsonBuildObject :: forall (null :: PGType -> NullType). '[] ---> null 'PGjson Source #

jsonbBuildObject :: forall (null :: PGType -> NullType). '[] ---> null 'PGjsonb Source #

FilterWhere AggregateArg 'Ungrouped Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Aggregate

Methods

filterWhere :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType) (xs :: k). Condition 'Ungrouped lat with db params from -> AggregateArg xs lat with db params from -> AggregateArg xs lat with db params from Source #

FilterWhere (WindowArg grp :: [NullType] -> FromType -> FromType -> SchemasType -> [NullType] -> FromType -> Type) grp Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Window

Methods

filterWhere :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType) (xs :: k). Condition grp lat with db params from -> WindowArg grp xs lat with db params from -> WindowArg grp xs lat with db params from Source #

Additional (FromClause lat with db params :: FromType -> Type) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.From

Methods

also :: forall (ys :: [a]) (xs :: [a]). FromClause lat with db params ys -> FromClause lat with db params xs -> FromClause lat with db params (Join xs ys) Source #

Additional (Selection grp lat with db params from :: RowType -> Type) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Select

Methods

also :: forall (ys :: [a]) (xs :: [a]). Selection grp lat with db params from ys -> Selection grp lat with db params from xs -> Selection grp lat with db params from (Join xs ys) Source #

(JsonBuildObject tys, In key PGJsonKey) => JsonBuildObject ('NotNull key ': (value ': tys)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Json

Methods

jsonBuildObject :: forall (null :: PGType -> NullType). ('NotNull key ': (value ': tys)) ---> null 'PGjson Source #

jsonbBuildObject :: forall (null :: PGType -> NullType). ('NotNull key ': (value ': tys)) ---> null 'PGjsonb Source #

ty0 ~ ty1 => SamePGType (alias0 ::: (def0 :=> null0 ty0)) (alias1 ::: (def1 :=> null1 ty1)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.Schema

(FromValue ty y, fld0 ~ fld1) => FromField (fld0 ::: ty) (fld1 ::: y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Methods

fromField :: Maybe ByteString -> Either Text (P (fld1 ::: y)) Source #

(KnownSymbol col, InlineParam x ty) => InlineColumn (col ::: Optional I ('Def :=> x)) (col ::: ('Def :=> ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Inline

Methods

inlineColumn :: forall (grp :: Grouping) (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType). P (col ::: Optional I ('Def :=> x)) -> Aliased (Optional (Expression grp lat with db params from)) (col ::: ('Def :=> ty)) Source #

(KnownSymbol col, InlineParam x ty) => InlineColumn (col ::: x) (col ::: ('NoDef :=> ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Inline

Methods

inlineColumn :: forall (grp :: Grouping) (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType). P (col ::: x) -> Aliased (Optional (Expression grp lat with db params from)) (col ::: ('NoDef :=> ty)) Source #

(KnownSymbol alias, InlineParam x ty) => InlineField (alias ::: x) (alias ::: ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Inline

Methods

inlineField :: forall (grp :: Grouping) (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType). P (alias ::: x) -> Aliased (Expression grp lat with db params from) (alias ::: ty) Source #

AddColumn ('Def :=> ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Table

Methods

addColumn :: forall (column :: Symbol) (sch :: Symbol) (db :: [(Symbol, [(Symbol, SchemumType)])]) (schema :: [(Symbol, SchemumType)]) (tab :: Symbol) (constraints :: TableConstraints) (columns :: ColumnsType). (KnownSymbol column, Has sch db schema, Has tab schema ('Table (constraints :=> columns))) => Alias column -> ColumnTypeExpression db ('Def :=> ty) -> AlterTable sch tab db (constraints :=> Create column ('Def :=> ty) columns) Source #

AddColumn ('NoDef :=> 'Null ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Table

Methods

addColumn :: forall (column :: Symbol) (sch :: Symbol) (db :: [(Symbol, [(Symbol, SchemumType)])]) (schema :: [(Symbol, SchemumType)]) (tab :: Symbol) (constraints :: TableConstraints) (columns :: ColumnsType). (KnownSymbol column, Has sch db schema, Has tab schema ('Table (constraints :=> columns))) => Alias column -> ColumnTypeExpression db ('NoDef :=> 'Null ty) -> AlterTable sch tab db (constraints :=> Create column ('NoDef :=> 'Null ty) columns) Source #

IsString (Selection grp lat with db params from '["fromOnly" ::: 'NotNull 'PGtext]) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Select

Methods

fromString :: String -> Selection grp lat with db params from '["fromOnly" ::: 'NotNull 'PGtext] #

type RowType = [(Symbol, NullType)] Source #

A RowType is a row of NullTypes. They correspond to Haskell record types by means of RowPG and are used in many places.

>>> :{
type family PersonRow :: RowType where
  PersonRow =
    '[ "name"        ::: 'NotNull 'PGtext
     , "age"         ::: 'NotNull 'PGint4
     , "dateOfBirth" :::    'Null 'PGdate
     ]
:}

type FromType = [(Symbol, RowType)] Source #

FromType is a row of RowTypes. It can be thought of as a product, or horizontal gluing and is used in FromClauses and TableExpressions.

Schema Type

type ColumnType = (Optionality, NullType) Source #

ColumnType encodes the allowance of DEFAULT and NULL and the base PGType for a column.

>>> :set -XTypeFamilies -XTypeInType
>>> import GHC.TypeLits
>>> type family IdColumn :: ColumnType where IdColumn = 'Def :=> 'NotNull 'PGint4
>>> type family EmailColumn :: ColumnType where EmailColumn = 'NoDef :=> 'Null 'PGtext

type ColumnsType = [(Symbol, ColumnType)] Source #

ColumnsType is a row of ColumnTypes.

>>> :{
type family UsersColumns :: ColumnsType where
  UsersColumns =
    '[ "name" ::: 'NoDef :=> 'NotNull 'PGtext
     , "id"   :::   'Def :=> 'NotNull 'PGint4
     ]
:}

type TableType = (TableConstraints, ColumnsType) Source #

TableType encodes a row of constraints on a table as well as the types of its columns.

>>> :{
type family UsersTable :: TableType where
  UsersTable =
    '[ "pk_users" ::: 'PrimaryKey '["id"] ] :=>
    '[ "id"       :::   'Def :=> 'NotNull 'PGint4
     , "name"     ::: 'NoDef :=> 'NotNull 'PGtext
     ]
:}

data SchemumType Source #

A SchemumType is a user-created type, like a Table, View or Typedef.

Instances

Instances details
Category Definition Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition

Methods

id :: forall (a :: k). Definition a a #

(.) :: forall (b :: k) (c :: k) (a :: k). Definition b c -> Definition a b -> Definition a c #

IndexedMonadTrans PQ Source # 
Instance details

Defined in Squeal.PostgreSQL.Session

Methods

pqAp :: forall (m :: Type -> Type) (i :: k) (j :: k) x y (k :: k). Monad m => PQ i j m (x -> y) -> PQ j k m x -> PQ i k m y Source #

pqJoin :: forall (m :: Type -> Type) (i :: k) (j :: k) (k :: k) y. Monad m => PQ i j m (PQ j k m y) -> PQ i k m y Source #

pqBind :: forall (m :: Type -> Type) x (j :: k) (k :: k) y (i :: k). Monad m => (x -> PQ j k m y) -> PQ i j m x -> PQ i k m y Source #

pqThen :: forall (m :: Type -> Type) (j :: k) (k :: k) y (i :: k) x. Monad m => PQ j k m y -> PQ i j m x -> PQ i k m y Source #

pqAndThen :: forall (m :: Type -> Type) y (j :: k) (k :: k) z x (i :: k). Monad m => (y -> PQ j k m z) -> (x -> PQ i j m y) -> x -> PQ i k m z Source #

Aggregate AggregateArg (Expression ('Grouped bys) :: FromType -> FromType -> SchemasType -> [NullType] -> FromType -> NullType -> Type) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Aggregate

Methods

countStar :: forall (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). Expression ('Grouped bys) lat with db params from ('NotNull 'PGint8) Source #

count :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('NotNull 'PGint8) Source #

sum_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGSum ty)) Source #

arrayAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null ('PGvararray ty)) Source #

jsonAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGjson) Source #

jsonbAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGjsonb) Source #

bitAnd :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => AggregateArg '[null int] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null int) Source #

bitOr :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => AggregateArg '[null int] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null int) Source #

boolAnd :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGbool] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGbool) Source #

boolOr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGbool] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGbool) Source #

every :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGbool] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGbool) Source #

max_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null ty) Source #

min_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null ty) Source #

avg :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source #

corr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source #

covarPop :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source #

covarSamp :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source #

regrAvgX :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source #

regrAvgY :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source #

regrCount :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGint8) Source #

regrIntercept :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source #

regrR2 :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source #

regrSlope :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source #

regrSxx :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source #

regrSxy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source #

regrSyy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source #

stddev :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source #

stddevPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source #

stddevSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source #

variance :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source #

varPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source #

varSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source #

Aggregate (WindowArg grp :: [NullType] -> FromType -> FromType -> SchemasType -> [NullType] -> FromType -> Type) (WindowFunction grp :: FromType -> FromType -> SchemasType -> [NullType] -> FromType -> NullType -> Type) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Window

Methods

countStar :: forall (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowFunction grp lat with db params from ('NotNull 'PGint8) Source #

count :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('NotNull 'PGint8) Source #

sum_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGSum ty)) Source #

arrayAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('Null ('PGvararray ty)) Source #

jsonAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGjson) Source #

jsonbAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGjsonb) Source #

bitAnd :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => WindowArg grp '[null int] lat with db params from -> WindowFunction grp lat with db params from ('Null int) Source #

bitOr :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => WindowArg grp '[null int] lat with db params from -> WindowFunction grp lat with db params from ('Null int) Source #

boolAnd :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGbool] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGbool) Source #

boolOr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGbool] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGbool) Source #

every :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGbool] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGbool) Source #

max_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null ty) Source #

min_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null ty) Source #

avg :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

corr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

covarPop :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

covarSamp :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrAvgX :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrAvgY :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrCount :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGint8) Source #

regrIntercept :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrR2 :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrSlope :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrSxx :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrSxy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrSyy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

stddev :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

stddevPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

stddevSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

variance :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

varPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

varSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

Migratory Definition (Indexed PQ IO ()) Source #

pure migrations

Instance details

Defined in Squeal.PostgreSQL.Session.Migration

Methods

runMigrations :: forall (db0 :: k) (db1 :: k). Path (Migration Definition) db0 db1 -> Indexed PQ IO () db0 db1 Source #

Migratory (IsoQ Definition) (IsoQ (Indexed PQ IO ())) Source #

pure rewindable migrations

Instance details

Defined in Squeal.PostgreSQL.Session.Migration

Methods

runMigrations :: forall (db0 :: k) (db1 :: k). Path (Migration (IsoQ Definition)) db0 db1 -> IsoQ (Indexed PQ IO ()) db0 db1 Source #

Migratory (IsoQ (Indexed PQ IO ())) (IsoQ (Indexed PQ IO ())) Source #

impure rewindable migrations

Instance details

Defined in Squeal.PostgreSQL.Session.Migration

Methods

runMigrations :: forall (db0 :: k) (db1 :: k). Path (Migration (IsoQ (Indexed PQ IO ()))) db0 db1 -> IsoQ (Indexed PQ IO ()) db0 db1 Source #

Migratory (OpQ Definition) (OpQ (Indexed PQ IO ())) Source #

pure rewinds

Instance details

Defined in Squeal.PostgreSQL.Session.Migration

Methods

runMigrations :: forall (db0 :: k) (db1 :: k). Path (Migration (OpQ Definition)) db0 db1 -> OpQ (Indexed PQ IO ()) db0 db1 Source #

Migratory (OpQ (Indexed PQ IO ())) (OpQ (Indexed PQ IO ())) Source #

impure rewinds

Instance details

Defined in Squeal.PostgreSQL.Session.Migration

Methods

runMigrations :: forall (db0 :: k) (db1 :: k). Path (Migration (OpQ (Indexed PQ IO ()))) db0 db1 -> OpQ (Indexed PQ IO ()) db0 db1 Source #

Migratory (Indexed PQ IO ()) (Indexed PQ IO ()) Source #

impure migrations

Instance details

Defined in Squeal.PostgreSQL.Session.Migration

Methods

runMigrations :: forall (db0 :: k) (db1 :: k). Path (Migration (Indexed PQ IO ())) db0 db1 -> Indexed PQ IO () db0 db1 Source #

data IndexType Source #

PostgreSQL provides several index types: B-tree, Hash, GiST, SP-GiST, GIN and BRIN. Each index type uses a different algorithm that is best suited to different types of queries.

Constructors

Btree

B-trees can handle equality and range queries on data that can be sorted into some ordering.

Hash

Hash indexes can only handle simple equality comparisons.

Gist

GiST indexes are not a single kind of index, but rather an infrastructure within which many different indexing strategies can be implemented.

Spgist

SP-GiST indexes, like GiST indexes, offer an infrastructure that supports various kinds of searches.

Gin

GIN indexes are “inverted indexes” which are appropriate for data values that contain multiple component values, such as arrays.

Brin

BRIN indexes (a shorthand for Block Range INdexes) store summaries about the values stored in consecutive physical block ranges of a table.

type FunctionType = ([NullType], ReturnsType) Source #

Use :=> to pair the parameter types with the return type of a function.

>>> :{
type family Fn :: FunctionType where
  Fn = '[ 'NotNull 'PGint4] :=> 'Returns ('NotNull 'PGint4)
:}

data ReturnsType Source #

Return type of a function

Constructors

Returns NullType

function

ReturnsTable RowType

set returning function

type SchemaType = [(Symbol, SchemumType)] Source #

A schema of a database consists of a list of aliased, user-defined SchemumTypes.

>>> :{
type family Schema :: SchemaType where
  Schema =
    '[ "users" ::: 'Table (
        '[ "pk_users" ::: 'PrimaryKey '["id"] ] :=>
        '[ "id"   :::   'Def :=> 'NotNull 'PGint4
        , "name" ::: 'NoDef :=> 'NotNull 'PGtext
        ])
    , "emails" ::: 'Table (
        '[ "pk_emails"  ::: 'PrimaryKey '["id"]
        , "fk_user_id" ::: 'ForeignKey '["user_id"] "public" "users" '["id"]
        ] :=>
        '[ "id"      :::   'Def :=> 'NotNull 'PGint4
        , "user_id" ::: 'NoDef :=> 'NotNull 'PGint4
        , "email"   ::: 'NoDef :=>    'Null 'PGtext
        ])
    ]
:}

type SchemasType = [(Symbol, SchemaType)] Source #

A database contains one or more named schemas, which in turn contain tables. The same object name can be used in different schemas without conflict; for example, both schema1 and myschema can contain tables named mytable. Unlike databases, schemas are not rigidly separated: a user can access objects in any of the schemas in the database they are connected to, if they have privileges to do so.

There are several reasons why one might want to use schemas:

  • To allow many users to use one database without interfering with each other.
  • To organize database objects into logical groups to make them more manageable.
  • Third-party applications can be put into separate schemas so they do not collide with the names of other objects.

type family Public (schema :: SchemaType) :: SchemasType where ... Source #

A type family to use for a single schema database.

Equations

Public schema = '["public" ::: schema] 

Database Subsets

type family SubDB (db0 :: SchemasType) (db1 :: SchemasType) :: Bool where ... Source #

SubDB checks that one SchemasType is a sublist of another, with the same ordering.

>>> :kind! SubDB '["a" ::: '["b" ::: 'View '[]]] '["a" ::: '["b" ::: 'View '[], "c" ::: 'Typedef 'PGint4]]
SubDB '["a" ::: '["b" ::: 'View '[]]] '["a" ::: '["b" ::: 'View '[], "c" ::: 'Typedef 'PGint4]] :: Bool
= 'True

Equations

SubDB '[] db1 = 'True 
SubDB (sch ': db0) '[] = 'False 
SubDB ((sch ::: schema0) ': db0) ((sch ::: schema1) ': db1) = If (SubList schema0 schema1) (SubDB db0 db1) (SubDB ((sch ::: schema0) ': db0) db1) 
SubDB db0 (sch1 ': db1) = SubDB db0 db1 

type family SubsetDB (db0 :: SchemasType) (db1 :: SchemasType) :: Bool where ... Source #

SubsetDB checks that one SchemasType is a subset of another, regardless of ordering.

>>> :kind! SubsetDB '["a" ::: '["d" ::: 'Typedef 'PGint2, "b" ::: 'View '[]]] '["a" ::: '["b" ::: 'View '[], "c" ::: 'Typedef 'PGint4, "d" ::: 'Typedef 'PGint2]]
SubsetDB '["a" ::: '["d" ::: 'Typedef 'PGint2, "b" ::: 'View '[]]] '["a" ::: '["b" ::: 'View '[], "c" ::: 'Typedef 'PGint4, "d" ::: 'Typedef 'PGint2]] :: Bool
= 'True

Equations

SubsetDB '[] db1 = 'True 
SubsetDB (sch ': db0) db1 = ElemDB sch db1 && SubsetDB db0 db1 

type family ElemDB (sch :: (Symbol, SchemaType)) (db :: SchemasType) :: Bool where ... Source #

ElemDB checks that a schema may be found as a subset of another in a database, regardless of ordering.

Equations

ElemDB sch '[] = 'False 
ElemDB (sch ::: schema0) ((sch ::: schema1) ': _) = SubsetList schema0 schema1 
ElemDB sch (_ ': schs) = ElemDB sch schs 

Constraint

type (:=>) constraint ty = '(constraint, ty) infixr 7 Source #

The constraint operator, :=> is a type level pair between a "constraint" and some type, for use in pairing an Optionality with a NullType to produce a ColumnType or a TableConstraints and a ColumnsType to produce a TableType.

data Optionality Source #

Optionality encodes the availability of DEFAULT for inserts and updates. A column can be assigned a default value. A data Manipulation command can also request explicitly that a column be set to its default value, without having to know what that value is.

Constructors

Def

DEFAULT is available for inserts and updates

NoDef

DEFAULT is unavailable for inserts and updates

Instances

Instances details
NullTyped db ('NotNull ty) => ColumnTyped db ('NoDef :=> 'NotNull ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

NullTyped db ('Null ty) => ColumnTyped db ('NoDef :=> 'Null ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

ty0 ~ ty1 => SamePGType (alias0 ::: (def0 :=> null0 ty0)) (alias1 ::: (def1 :=> null1 ty1)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.Schema

(KnownSymbol col, InlineParam x ty) => InlineColumn (col ::: Optional I ('Def :=> x)) (col ::: ('Def :=> ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Inline

Methods

inlineColumn :: forall (grp :: Grouping) (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType). P (col ::: Optional I ('Def :=> x)) -> Aliased (Optional (Expression grp lat with db params from)) (col ::: ('Def :=> ty)) Source #

(KnownSymbol col, InlineParam x ty) => InlineColumn (col ::: x) (col ::: ('NoDef :=> ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Inline

Methods

inlineColumn :: forall (grp :: Grouping) (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType). P (col ::: x) -> Aliased (Optional (Expression grp lat with db params from)) (col ::: ('NoDef :=> ty)) Source #

AddColumn ('Def :=> ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Table

Methods

addColumn :: forall (column :: Symbol) (sch :: Symbol) (db :: [(Symbol, [(Symbol, SchemumType)])]) (schema :: [(Symbol, SchemumType)]) (tab :: Symbol) (constraints :: TableConstraints) (columns :: ColumnsType). (KnownSymbol column, Has sch db schema, Has tab schema ('Table (constraints :=> columns))) => Alias column -> ColumnTypeExpression db ('Def :=> ty) -> AlterTable sch tab db (constraints :=> Create column ('Def :=> ty) columns) Source #

AddColumn ('NoDef :=> 'Null ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Table

Methods

addColumn :: forall (column :: Symbol) (sch :: Symbol) (db :: [(Symbol, [(Symbol, SchemumType)])]) (schema :: [(Symbol, SchemumType)]) (tab :: Symbol) (constraints :: TableConstraints) (columns :: ColumnsType). (KnownSymbol column, Has sch db schema, Has tab schema ('Table (constraints :=> columns))) => Alias column -> ColumnTypeExpression db ('NoDef :=> 'Null ty) -> AlterTable sch tab db (constraints :=> Create column ('NoDef :=> 'Null ty) columns) Source #

data TableConstraint Source #

TableConstraint encodes various forms of data constraints of columns in a table. TableConstraints give you as much control over the data in your tables as you wish. If a user attempts to store data in a column that would violate a constraint, an error is raised. This applies even if the value came from the default value definition.

type TableConstraints = [(Symbol, TableConstraint)] Source #

A TableConstraints is a row of TableConstraints.

>>> :{
type family UsersConstraints :: TableConstraints where
  UsersConstraints = '[ "pk_users" ::: 'PrimaryKey '["id"] ]
:}

type family Uniquely (key :: [Symbol]) (constraints :: TableConstraints) :: Constraint where ... Source #

A ForeignKey must reference columns that either are a PrimaryKey or form a Unique constraint.

Equations

Uniquely key ((uq ::: 'Unique key) ': constraints) = () 
Uniquely key ((pk ::: 'PrimaryKey key) ': constraints) = () 
Uniquely key (_ ': constraints) = Uniquely key constraints 

Enumerated Label

class IsPGlabel (label :: Symbol) expr where Source #

IsPGlabel looks very much like the IsLabel class. Whereas the overloaded label, fromLabel is used for column references, labels are used for enum terms. A label is called with type application like label @"beef".

Methods

label :: expr Source #

Instances

Instances details
label ~ label1 => IsPGlabel label (PGlabel label1) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.Schema

Methods

label :: PGlabel label1 Source #

IsPGlabel label (y -> NP (K y :: Symbol -> Type) '[label]) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.Schema

Methods

label :: y -> NP (K y) '[label] Source #

IsPGlabel label (y -> K y label) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.Schema

Methods

label :: y -> K y label Source #

labels ~ '[label] => IsPGlabel label (NP PGlabel labels) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.Schema

Methods

label :: NP PGlabel labels Source #

(KnownSymbol label, In label labels) => IsPGlabel label (Expression grp lat with db params from (null ('PGenum labels))) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

label :: Expression grp lat with db params from (null ('PGenum labels)) Source #

data PGlabel (label :: Symbol) Source #

A PGlabel unit type with an IsPGlabel instance

Constructors

PGlabel 

Instances

Instances details
label ~ label1 => IsPGlabel label (PGlabel label1) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.Schema

Methods

label :: PGlabel label1 Source #

labels ~ '[label] => IsPGlabel label (NP PGlabel labels) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.Schema

Methods

label :: NP PGlabel labels Source #

KnownSymbol label => RenderSQL (PGlabel label) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.Schema

Methods

renderSQL :: PGlabel label -> ByteString Source #

All KnownSymbol labels => RenderSQL (NP PGlabel labels) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.Schema

Methods

renderSQL :: NP PGlabel labels -> ByteString Source #

Data Definition

type family Create alias x xs where ... Source #

Create alias x xs adds alias ::: x to the end of xs and is used in createTable statements and in ALTER TABLE addColumn.

Equations

Create alias x '[] = '[alias ::: x] 
Create alias x ((alias ::: y) ': xs) = TypeError (('Text "Create: alias " :<>: 'ShowType alias) :<>: 'Text "already exists") 
Create alias y (x ': xs) = x ': Create alias y xs 

type family CreateIfNotExists alias x xs where ... Source #

Similar to Create but no error on pre-existence

Equations

CreateIfNotExists alias x '[] = '[alias ::: x] 
CreateIfNotExists alias x ((alias ::: y) ': xs) = (alias ::: y) ': xs 
CreateIfNotExists alias y (x ': xs) = x ': CreateIfNotExists alias y xs 

type family CreateOrReplace alias x xs where ... Source #

Similar to Create but used to replace values with the same type.

Equations

CreateOrReplace alias x '[] = '[alias ::: x] 
CreateOrReplace alias x ((alias ::: x) ': xs) = (alias ::: x) ': xs 
CreateOrReplace alias x ((alias ::: y) ': xs) = TypeError ((((('Text "CreateOrReplace: expected type " :<>: 'ShowType x) :<>: 'Text " but alias ") :<>: 'ShowType alias) :<>: 'Text " has type ") :<>: 'ShowType y) 
CreateOrReplace alias y (x ': xs) = x ': CreateOrReplace alias y xs 

type family Drop alias xs where ... Source #

Drop alias xs removes the type associated with alias in xs and is used in dropTable statements and in ALTER TABLE dropColumn statements.

Equations

Drop alias '[] = TypeError (('Text "Drop: alias " :<>: 'ShowType alias) :<>: 'Text " does not exist") 
Drop alias ((alias ::: x) ': xs) = xs 
Drop alias (x ': xs) = x ': Drop alias xs 

type family DropSchemum alias sch xs where ... Source #

Drop a particular flavor of schemum type

Equations

DropSchemum alias sch '[] = TypeError (('Text "DropSchemum: alias " :<>: 'ShowType alias) :<>: 'Text " does not exist") 
DropSchemum alias sch ((alias ::: sch x) ': xs) = xs 
DropSchemum alias sch0 ((alias ::: sch1 x) ': xs) = TypeError ((((('Text "DropSchemum: expected schemum " :<>: 'ShowType sch0) :<>: 'Text " but alias ") :<>: 'ShowType alias) :<>: 'Text " has schemum ") :<>: 'ShowType sch1) 
DropSchemum alias sch (x ': xs) = x ': DropSchemum alias sch xs 

type family DropIfExists alias xs where ... Source #

Similar to Drop but no error on non-existence

Equations

DropIfExists alias '[] = '[] 
DropIfExists alias ((alias ::: x) ': xs) = xs 
DropIfExists alias (x ': xs) = x ': DropIfExists alias xs 

type family DropSchemumIfExists alias sch xs where ... Source #

Similar to DropSchemum but no error on non-existence

Equations

DropSchemumIfExists alias sch '[] = '[] 
DropSchemumIfExists alias sch ((alias ::: sch x) ': xs) = xs 
DropSchemumIfExists alias sch0 ((alias ::: sch1 x) ': xs) = TypeError ((((('Text "DropSchemumIfExists: expected schemum " :<>: 'ShowType sch1) :<>: 'Text " but alias ") :<>: 'ShowType alias) :<>: 'Text " has schemum ") :<>: 'ShowType sch0) 
DropSchemumIfExists alias sch (x ': xs) = x ': DropSchemumIfExists alias sch xs 

type family Alter alias x xs where ... Source #

Alter alias x xs replaces the type associated with an alias in xs with the type x and is used in alterTable and alterColumn.

Equations

Alter alias x '[] = TypeError (('Text "Alter: alias " :<>: 'ShowType alias) :<>: 'Text " does not exist") 
Alter alias x1 ((alias ::: x0) ': xs) = (alias ::: x1) ': xs 
Alter alias x1 (x0 ': xs) = x0 ': Alter alias x1 xs 

type family AlterIfExists alias x xs where ... Source #

Similar to Alter but no error on non-existence

Equations

AlterIfExists alias x '[] = '[] 
AlterIfExists alias x1 ((alias ::: x0) ': xs) = (alias ::: x1) ': xs 
AlterIfExists alias x1 (x0 ': xs) = x0 ': AlterIfExists alias x1 xs 

type family Rename alias0 alias1 xs where ... Source #

Rename alias0 alias1 xs replaces the alias alias0 by alias1 in xs and is used in alterTableRename and renameColumn.

Equations

Rename alias0 alias1 '[] = TypeError (('Text "Rename: alias " :<>: 'ShowType alias0) :<>: 'Text " does not exist") 
Rename alias0 alias1 ((alias0 ::: x0) ': xs) = (alias1 ::: x0) ': xs 
Rename alias0 alias1 (x ': xs) = x ': Rename alias0 alias1 xs 

type family RenameIfExists alias0 alias1 xs where ... Source #

Similar to Rename but no error on non-existence

Equations

RenameIfExists alias x '[] = '[] 
RenameIfExists alias0 alias1 ((alias0 ::: x0) ': xs) = (alias1 ::: x0) ': xs 
RenameIfExists alias0 alias1 (x ': xs) = x ': RenameIfExists alias0 alias1 xs 

type family SetSchema sch0 sch1 schema0 schema1 obj srt ty db where ... Source #

Move an object from one schema to another

Equations

SetSchema sch0 sch1 schema0 schema1 obj srt ty db = Alter sch1 (Create obj (srt ty) schema1) (Alter sch0 (DropSchemum obj srt schema0) db) 

type family ConstraintInvolves column constraint where ... Source #

Check if a TableConstraint involves a column

Equations

ConstraintInvolves column ('Check columns) = column `Elem` columns 
ConstraintInvolves column ('Unique columns) = column `Elem` columns 
ConstraintInvolves column ('PrimaryKey columns) = column `Elem` columns 
ConstraintInvolves column ('ForeignKey columns sch tab refcolumns) = column `Elem` columns 

type family DropIfConstraintsInvolve column constraints where ... Source #

Drop all TableConstraints that involve a column

Equations

DropIfConstraintsInvolve column '[] = '[] 
DropIfConstraintsInvolve column ((alias ::: constraint) ': constraints) = If (ConstraintInvolves column constraint) (DropIfConstraintsInvolve column constraints) ((alias ::: constraint) ': DropIfConstraintsInvolve column constraints) 

Type Classification

type PGNum = '['PGint2, 'PGint4, 'PGint8, 'PGnumeric, 'PGfloat4, 'PGfloat8] Source #

Numeric Postgres types.

type PGIntegral = '['PGint2, 'PGint4, 'PGint8] Source #

Integral Postgres types.

type PGFloating = '['PGfloat4, 'PGfloat8, 'PGnumeric] Source #

Floating Postgres types.

type PGJsonType = '['PGjson, 'PGjsonb] Source #

Is a type a valid JSON type?

type PGJsonKey = '['PGint2, 'PGint4, 'PGtext] Source #

Is a type a valid JSON key?

class SamePGType (ty0 :: (Symbol, ColumnType)) (ty1 :: (Symbol, ColumnType)) Source #

Equality constraint on the underlying PGType of two columns.

Instances

Instances details
ty0 ~ ty1 => SamePGType (alias0 ::: (def0 :=> null0 ty0)) (alias1 ::: (def1 :=> null1 ty1)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.Schema

type family AllNotNull (columns :: ColumnsType) :: Constraint where ... Source #

AllNotNull is a constraint that proves a ColumnsType has no NULLs.

Equations

AllNotNull ((_ ::: (_ :=> 'NotNull _)) ': columns) = AllNotNull columns 
AllNotNull '[] = () 

type family NotAllNull (columns :: ColumnsType) :: Constraint where ... Source #

NotAllNull is a constraint that proves a ColumnsType has some NOT NULL.

Equations

NotAllNull ((_ ::: (_ :=> 'NotNull _)) ': _) = () 
NotAllNull ((_ ::: (_ :=> 'Null _)) ': columns) = NotAllNull columns 

Nullification

type family NullifyType (ty :: NullType) :: NullType where ... Source #

NullifyType is an idempotent that nullifies a NullType.

Equations

NullifyType (null ty) = 'Null ty 

type family NullifyRow (columns :: RowType) :: RowType where ... Source #

NullifyRow is an idempotent that nullifies a RowType.

Equations

NullifyRow ((column ::: ty) ': columns) = (column ::: NullifyType ty) ': NullifyRow columns 
NullifyRow '[] = '[] 

type family NullifyFrom (tables :: FromType) :: FromType where ... Source #

NullifyFrom is an idempotent that nullifies a FromType used to nullify the left or right hand side of an outer join in a FromClause.

Equations

NullifyFrom ((table ::: columns) ': tables) = (table ::: NullifyRow columns) ': NullifyFrom tables 
NullifyFrom '[] = '[] 

Table Conversion

type family TableToColumns (table :: TableType) :: ColumnsType where ... Source #

TableToColumns removes table constraints.

Equations

TableToColumns (constraints :=> columns) = columns 

type family ColumnsToRow (columns :: ColumnsType) :: RowType where ... Source #

ColumnsToRow removes column constraints.

Equations

ColumnsToRow ((column ::: (_ :=> ty)) ': columns) = (column ::: ty) ': ColumnsToRow columns 
ColumnsToRow '[] = '[] 

type family TableToRow (table :: TableType) :: RowType where ... Source #

Convert a table to a row type.

Equations

TableToRow tab = ColumnsToRow (TableToColumns tab) 

Updatable

type Updatable table columns = (All (HasIn (TableToColumns table)) columns, AllUnique columns, SListI (TableToColumns table)) Source #

Updatable lists of columns

class AllUnique (xs :: [(Symbol, a)]) Source #

No elem of xs appears more than once, in the context of assignment.

Instances

Instances details
AllUnique ('[] :: [(Symbol, a)]) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.Schema

(IsNotElem x (Elem x xs), AllUnique xs) => AllUnique (x ': xs :: [(Symbol, a)]) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.Schema

class IsNotElem x isElem Source #

Utility class for AllUnique to provide nicer error messages.

Instances

Instances details
IsNotElem (x :: k) 'False Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.Schema

(TypeError (('Text "Cannot assign to " :<>: 'ShowType alias) :<>: 'Text " more than once") :: Constraint) => IsNotElem ('(alias, a) :: (k1, k2)) 'True Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.Schema

User Types

type family UserType (db :: SchemasType) (ty :: PGType) where ... Source #

Calculate the schema and name of a user defined type.

Equations

UserType '[] ty = TypeError ('Text "No such user type: " :<>: 'ShowType ty) 
UserType ((sch ::: schema) ': schemas) ty = UserTypeNamespace sch (UserTypeName schema ty) schemas ty 

type family UserTypeName (schema :: SchemaType) (ty :: PGType) where ... Source #

Calculate the name of a user defined type.

Equations

UserTypeName '[] ty = 'Nothing 
UserTypeName ((td ::: 'Typedef ty) ': _) ty = 'Just td 
UserTypeName (_ ': schema) ty = UserTypeName schema ty 

type family UserTypeNamespace (sch :: Symbol) (td :: Maybe Symbol) (schemas :: SchemasType) (ty :: PGType) where ... Source #

Helper to calculate the schema of a user defined type.

Equations

UserTypeNamespace sch 'Nothing schemas ty = UserType schemas ty 
UserTypeNamespace sch ('Just td) schemas ty = '(sch, td)