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

Squeal.PostgreSQL.Expression.Type

Description

type expressions

Synopsis

Type Cast

cast Source #

Arguments

:: TypeExpression db ty1

type to cast as

-> Expression grp lat with db params from ty0

value to convert

-> Expression grp lat with db params from ty1 
>>> printSQL $ true & cast int4
(TRUE :: int4)

astype Source #

Arguments

:: TypeExpression db ty

type to specify as

-> Expression grp lat with db params from ty

value

-> Expression grp lat with db params from ty 

A safe version of cast which just matches a value with its type.

>>> printSQL (1 & astype int)
((1 :: int4) :: int)

inferredtype Source #

Arguments

:: NullTyped db ty 
=> Expression lat common grp db params from ty

value

-> Expression lat common grp db params from ty 

inferredtype will add a type annotation to an Expression which can be useful for fixing the storage type of a value.

>>> printSQL (inferredtype true)
(TRUE :: bool)

Type Expression

newtype TypeExpression (db :: SchemasType) (ty :: NullType) Source #

TypeExpressions are used in casts and createTable commands.

Instances

Instances details
Eq (TypeExpression db ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

(==) :: TypeExpression db ty -> TypeExpression db ty -> Bool #

(/=) :: TypeExpression db ty -> TypeExpression db ty -> Bool #

Ord (TypeExpression db ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

compare :: TypeExpression db ty -> TypeExpression db ty -> Ordering #

(<) :: TypeExpression db ty -> TypeExpression db ty -> Bool #

(<=) :: TypeExpression db ty -> TypeExpression db ty -> Bool #

(>) :: TypeExpression db ty -> TypeExpression db ty -> Bool #

(>=) :: TypeExpression db ty -> TypeExpression db ty -> Bool #

max :: TypeExpression db ty -> TypeExpression db ty -> TypeExpression db ty #

min :: TypeExpression db ty -> TypeExpression db ty -> TypeExpression db ty #

Show (TypeExpression db ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

showsPrec :: Int -> TypeExpression db ty -> ShowS #

show :: TypeExpression db ty -> String #

showList :: [TypeExpression db ty] -> ShowS #

Generic (TypeExpression db ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Associated Types

type Rep (TypeExpression db ty) :: Type -> Type #

Methods

from :: TypeExpression db ty -> Rep (TypeExpression db ty) x #

to :: Rep (TypeExpression db ty) x -> TypeExpression db ty #

NFData (TypeExpression db ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

rnf :: TypeExpression db ty -> () #

RenderSQL (TypeExpression db ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

type Rep (TypeExpression db ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

type Rep (TypeExpression db ty) = D1 ('MetaData "TypeExpression" "Squeal.PostgreSQL.Expression.Type" "squeal-postgresql-0.9.0.0-D17NIjlcsGRAwJTaCTXyvM" 'True) (C1 ('MetaCons "UnsafeTypeExpression" 'PrefixI 'True) (S1 ('MetaSel ('Just "renderTypeExpression") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

typerow Source #

Arguments

:: (relss ~ DbRelations db, Has sch relss rels, Has rel rels row) 
=> QualifiedAlias sch rel

type alias

-> TypeExpression db (null ('PGcomposite row)) 

The composite type corresponding to a relation can be expressed by its alias. A relation is either a composite type, a table or a view. It subsumes typetable and typeview and partly overlaps typedef.

typeenum Source #

Arguments

:: (enumss ~ DbEnums db, Has sch enumss enums, Has enum enums labels) 
=> QualifiedAlias sch enum

type alias

-> TypeExpression db (null ('PGenum labels)) 

An enumerated type can be expressed by its alias. typeenum is subsumed by typedef.

typedef Source #

Arguments

:: (Has sch db schema, Has td schema ('Typedef ty)) 
=> QualifiedAlias sch td

type alias

-> TypeExpression db (null ty) 

The enum or composite type in a Typedef can be expressed by its alias.

typetable Source #

Arguments

:: (Has sch db schema, Has tab schema ('Table table)) 
=> QualifiedAlias sch tab

table alias

-> TypeExpression db (null ('PGcomposite (TableToRow table))) 

The composite type corresponding to a Table definition can be expressed by its alias. It is subsumed by typerow

typeview Source #

Arguments

:: (Has sch db schema, Has vw schema ('View view)) 
=> QualifiedAlias sch vw

view alias

-> TypeExpression db (null ('PGcomposite view)) 

The composite type corresponding to a View definition can be expressed by its alias. It is subsumed by typerow.

bool :: TypeExpression db (null 'PGbool) Source #

logical Boolean (true/false)

int2 :: TypeExpression db (null 'PGint2) Source #

signed two-byte integer

smallint :: TypeExpression db (null 'PGint2) Source #

signed two-byte integer

int4 :: TypeExpression db (null 'PGint4) Source #

signed four-byte integer

int :: TypeExpression db (null 'PGint4) Source #

signed four-byte integer

integer :: TypeExpression db (null 'PGint4) Source #

signed four-byte integer

int8 :: TypeExpression db (null 'PGint8) Source #

signed eight-byte integer

bigint :: TypeExpression db (null 'PGint8) Source #

signed eight-byte integer

numeric :: TypeExpression db (null 'PGnumeric) Source #

arbitrary precision numeric type

float4 :: TypeExpression db (null 'PGfloat4) Source #

single precision floating-point number (4 bytes)

real :: TypeExpression db (null 'PGfloat4) Source #

single precision floating-point number (4 bytes)

float8 :: TypeExpression db (null 'PGfloat8) Source #

double precision floating-point number (8 bytes)

doublePrecision :: TypeExpression db (null 'PGfloat8) Source #

double precision floating-point number (8 bytes)

money :: TypeExpression schema (null 'PGmoney) Source #

currency amount

text :: TypeExpression db (null 'PGtext) Source #

variable-length character string

char :: forall n db null. (KnownNat n, 1 <= n) => TypeExpression db (null ('PGchar n)) Source #

fixed-length character string

character :: forall n db null. (KnownNat n, 1 <= n) => TypeExpression db (null ('PGchar n)) Source #

fixed-length character string

varchar :: forall n db null. (KnownNat n, 1 <= n) => TypeExpression db (null ('PGvarchar n)) Source #

variable-length character string

characterVarying :: forall n db null. (KnownNat n, 1 <= n) => TypeExpression db (null ('PGvarchar n)) Source #

variable-length character string

bytea :: TypeExpression db (null 'PGbytea) Source #

binary data ("byte array")

timestamp :: TypeExpression db (null 'PGtimestamp) Source #

date and time (no time zone)

timestampWithTimeZone :: TypeExpression db (null 'PGtimestamptz) Source #

date and time, including time zone

timestamptz :: TypeExpression db (null 'PGtimestamptz) Source #

date and time, including time zone

date :: TypeExpression db (null 'PGdate) Source #

calendar date (year, month, day)

time :: TypeExpression db (null 'PGtime) Source #

time of day (no time zone)

timeWithTimeZone :: TypeExpression db (null 'PGtimetz) Source #

time of day, including time zone

timetz :: TypeExpression db (null 'PGtimetz) Source #

time of day, including time zone

interval :: TypeExpression db (null 'PGinterval) Source #

time span

uuid :: TypeExpression db (null 'PGuuid) Source #

universally unique identifier

inet :: TypeExpression db (null 'PGinet) Source #

IPv4 or IPv6 host address

json :: TypeExpression db (null 'PGjson) Source #

textual JSON data

jsonb :: TypeExpression db (null 'PGjsonb) Source #

binary JSON data, decomposed

vararray :: TypeExpression db pg -> TypeExpression db (null ('PGvararray pg)) Source #

variable length array

fixarray :: forall dims db null pg. All KnownNat dims => TypeExpression db pg -> TypeExpression db (null ('PGfixarray dims pg)) Source #

fixed length array

>>> renderSQL (fixarray @'[2] json)
"json[2]"

tsvector :: TypeExpression db (null 'PGtsvector) Source #

text search query

tsquery :: TypeExpression db (null 'PGtsquery) Source #

text search document

oid :: TypeExpression db (null 'PGoid) Source #

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

int4range :: TypeExpression db (null ('PGrange 'PGint4)) Source #

Range of integer

int8range :: TypeExpression db (null ('PGrange 'PGint8)) Source #

Range of bigint

numrange :: TypeExpression db (null ('PGrange 'PGnumeric)) Source #

Range of numeric

tsrange :: TypeExpression db (null ('PGrange 'PGtimestamp)) Source #

Range of timestamp without time zone

tstzrange :: TypeExpression db (null ('PGrange 'PGtimestamptz)) Source #

Range of timestamp with time zone

daterange :: TypeExpression db (null ('PGrange 'PGdate)) Source #

Range of date

record :: TypeExpression db (null ('PGcomposite record)) Source #

Anonymous composite record

Column Type

newtype ColumnTypeExpression (db :: SchemasType) (ty :: ColumnType) Source #

ColumnTypeExpressions are used in createTable commands.

Instances

Instances details
Eq (ColumnTypeExpression db ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Ord (ColumnTypeExpression db ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Show (ColumnTypeExpression db ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Generic (ColumnTypeExpression db ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Associated Types

type Rep (ColumnTypeExpression db ty) :: Type -> Type #

NFData (ColumnTypeExpression db ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

rnf :: ColumnTypeExpression db ty -> () #

RenderSQL (ColumnTypeExpression db ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

type Rep (ColumnTypeExpression db ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

type Rep (ColumnTypeExpression db ty) = D1 ('MetaData "ColumnTypeExpression" "Squeal.PostgreSQL.Expression.Type" "squeal-postgresql-0.9.0.0-D17NIjlcsGRAwJTaCTXyvM" 'True) (C1 ('MetaCons "UnsafeColumnTypeExpression" 'PrefixI 'True) (S1 ('MetaSel ('Just "renderColumnTypeExpression") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

nullable Source #

Arguments

:: TypeExpression db (null ty)

type

-> ColumnTypeExpression db ('NoDef :=> 'Null ty) 

used in createTable commands as a column constraint to note that NULL may be present in a column

notNullable Source #

Arguments

:: TypeExpression db (null ty)

type

-> ColumnTypeExpression db ('NoDef :=> 'NotNull ty) 

used in createTable commands as a column constraint to ensure NULL is not present in a column

default_ Source #

Arguments

:: Expression 'Ungrouped '[] '[] db '[] '[] ty

default value

-> ColumnTypeExpression db ('NoDef :=> ty)

column type

-> ColumnTypeExpression db ('Def :=> ty) 

used in createTable commands as a column constraint to give a default

serial2 :: ColumnTypeExpression db ('Def :=> 'NotNull 'PGint2) Source #

not a true type, but merely a notational convenience for creating unique identifier columns with type PGint2

smallserial :: ColumnTypeExpression db ('Def :=> 'NotNull 'PGint2) Source #

not a true type, but merely a notational convenience for creating unique identifier columns with type PGint2

serial4 :: ColumnTypeExpression db ('Def :=> 'NotNull 'PGint4) Source #

not a true type, but merely a notational convenience for creating unique identifier columns with type PGint4

serial :: ColumnTypeExpression db ('Def :=> 'NotNull 'PGint4) Source #

not a true type, but merely a notational convenience for creating unique identifier columns with type PGint4

serial8 :: ColumnTypeExpression db ('Def :=> 'NotNull 'PGint8) Source #

not a true type, but merely a notational convenience for creating unique identifier columns with type PGint8

bigserial :: ColumnTypeExpression db ('Def :=> 'NotNull 'PGint8) Source #

not a true type, but merely a notational convenience for creating unique identifier columns with type PGint8

Type Inference

class PGTyped db (ty :: PGType) where Source #

pgtype is a demoted version of a PGType

Methods

pgtype :: TypeExpression db (null ty) Source #

Instances

Instances details
PGTyped db 'PGoid Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null 'PGoid) Source #

PGTyped db 'PGtsquery Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null 'PGtsquery) Source #

PGTyped db 'PGtsvector Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null 'PGtsvector) Source #

PGTyped db 'PGjsonb Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null 'PGjsonb) Source #

PGTyped db 'PGjson Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null 'PGjson) Source #

PGTyped db 'PGinet Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null 'PGinet) Source #

PGTyped db 'PGuuid Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null 'PGuuid) Source #

PGTyped db 'PGinterval Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null 'PGinterval) Source #

PGTyped db 'PGtimetz Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null 'PGtimetz) Source #

PGTyped db 'PGtime Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null 'PGtime) Source #

PGTyped db 'PGdate Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null 'PGdate) Source #

PGTyped db 'PGtimestamptz Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null 'PGtimestamptz) Source #

PGTyped db 'PGtimestamp Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null 'PGtimestamp) Source #

PGTyped db 'PGbytea Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null 'PGbytea) Source #

PGTyped db 'PGtext Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null 'PGtext) Source #

PGTyped db 'PGmoney Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null 'PGmoney) Source #

PGTyped db 'PGfloat8 Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null 'PGfloat8) Source #

PGTyped db 'PGfloat4 Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null 'PGfloat4) Source #

PGTyped db 'PGnumeric Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null 'PGnumeric) Source #

PGTyped db 'PGint8 Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null 'PGint8) Source #

PGTyped db 'PGint4 Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null 'PGint4) Source #

PGTyped db 'PGint2 Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null 'PGint2) Source #

PGTyped db 'PGbool Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null 'PGbool) Source #

(enums ~ DbEnums db, FindQualified "no enum found with labels:" enums labels ~ '(sch, td), Has sch db schema, Has td schema ('Typedef ('PGenum labels))) => PGTyped db ('PGenum labels) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null ('PGenum labels)) Source #

(relss ~ DbRelations db, Has sch relss rels, Has rel rels row, FindQualified "no relation found with row:" relss row ~ '(sch, rel)) => PGTyped db ('PGcomposite row) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null ('PGcomposite row)) Source #

PGTyped db ('PGrange 'PGdate) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null ('PGrange 'PGdate)) Source #

PGTyped db ('PGrange 'PGtimestamptz) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null ('PGrange 'PGtimestamptz)) Source #

PGTyped db ('PGrange 'PGtimestamp) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null ('PGrange 'PGtimestamp)) Source #

PGTyped db ('PGrange 'PGnumeric) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null ('PGrange 'PGnumeric)) Source #

PGTyped db ('PGrange 'PGint8) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null ('PGrange 'PGint8)) Source #

PGTyped db ('PGrange 'PGint4) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null ('PGrange 'PGint4)) Source #

PGTyped db pg => PGTyped db ('PGvararray (null pg)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null0 :: PGType -> NullType). TypeExpression db (null0 ('PGvararray (null pg))) Source #

(KnownNat n, 1 <= n) => PGTyped db ('PGvarchar n) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null ('PGvarchar n)) Source #

(KnownNat n, 1 <= n) => PGTyped db ('PGchar n) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null :: PGType -> NullType). TypeExpression db (null ('PGchar n)) Source #

(All KnownNat dims, PGTyped db pg) => PGTyped db ('PGfixarray dims (null pg)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: forall (null0 :: PGType -> NullType). TypeExpression db (null0 ('PGfixarray dims (null pg))) Source #

pgtypeFrom :: forall hask db null. PGTyped db (PG hask) => TypeExpression db (null (PG hask)) Source #

Specify TypeExpression from a Haskell type.

>>> printSQL $ pgtypeFrom @String
text
>>> printSQL $ pgtypeFrom @Double
float8

class NullTyped db (ty :: NullType) where Source #

Like PGTyped but also accounts for null.

Instances

Instances details
PGTyped db ty => NullTyped db (null ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

nulltype :: TypeExpression db (null ty) Source #

nulltypeFrom :: forall hask db. NullTyped db (NullPG hask) => TypeExpression db (NullPG hask) Source #

Specify null TypeExpression from a Haskell type.

>>> printSQL $ nulltypeFrom @(Maybe String)
text
>>> printSQL $ nulltypeFrom @Double
float8

class ColumnTyped db (column :: ColumnType) where Source #

Like PGTyped but also accounts for null.

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

columntypeFrom :: forall hask db. ColumnTyped db ('NoDef :=> NullPG hask) => ColumnTypeExpression db ('NoDef :=> NullPG hask) Source #

Specify ColumnTypeExpression from a Haskell type.

>>> printSQL $ columntypeFrom @(Maybe String)
text NULL
>>> printSQL $ columntypeFrom @Double
float8 NOT NULL

class FieldTyped db ty where Source #

Lift PGTyped to a field

Instances

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