squeal-postgresql-0.5.2.0: Squeal PostgreSQL Library

Copyright(c) Eitan Chatav 2019
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Squeal.PostgreSQL.Expression.Type

Description

Type expressions.

Synopsis

Documentation

newtype TypeExpression (schemas :: SchemasType) (ty :: NullityType) Source #

TypeExpressions are used in casts and createTable commands.

Instances
Eq (TypeExpression schemas ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

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

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

Ord (TypeExpression schemas ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

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

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

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

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

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

max :: TypeExpression schemas ty -> TypeExpression schemas ty -> TypeExpression schemas ty #

min :: TypeExpression schemas ty -> TypeExpression schemas ty -> TypeExpression schemas ty #

Show (TypeExpression schemas ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

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

show :: TypeExpression schemas ty -> String #

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

Generic (TypeExpression schemas ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Associated Types

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

Methods

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

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

NFData (TypeExpression schemas ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

rnf :: TypeExpression schemas ty -> () #

RenderSQL (TypeExpression schemas ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

renderSQL :: TypeExpression schemas ty -> ByteString Source #

type Rep (TypeExpression schemas ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

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

cast Source #

Arguments

:: TypeExpression schemas ty1

type to cast as

-> Expression outer commons grp schemas params from ty0

value to convert

-> Expression outer commons grp schemas params from ty1 
>>> printSQL $ true & cast int4
(TRUE :: int4)

astype Source #

Arguments

:: TypeExpression schemas ty

type to specify as

-> Expression outer commons grp schemas params from ty

value

-> Expression outer commons grp schemas params from ty 

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

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

inferredtype :: PGTyped schemas ty => Expression outer common grp schemas params from ty -> Expression outer common grp schemas params from ty Source #

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)

class PGTyped schemas (ty :: NullityType) where Source #

pgtype is a demoted version of a PGType

Methods

pgtype :: TypeExpression schemas ty Source #

Instances
PGTyped schemas (null PGtsquery) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null PGtsquery) Source #

PGTyped schemas (null PGtsvector) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null PGtsvector) Source #

(All KnownNat dims, PGTyped schemas ty) => PGTyped schemas (null (PGfixarray dims ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null (PGfixarray dims ty)) Source #

PGTyped schemas ty => PGTyped schemas (null (PGvararray ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null (PGvararray ty)) Source #

PGTyped schemas (null PGjsonb) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null PGjsonb) Source #

PGTyped schemas (null PGjson) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null PGjson) Source #

PGTyped schemas (null PGuuid) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null PGuuid) Source #

PGTyped schemas (null PGinterval) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null PGinterval) Source #

PGTyped schemas (null PGtimetz) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null PGtimetz) Source #

PGTyped schemas (null PGtime) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null PGtime) Source #

PGTyped schemas (null PGdate) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null PGdate) Source #

PGTyped schemas (null PGtimestamptz) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null PGtimestamptz) Source #

PGTyped schemas (null PGtimestamp) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null PGtimestamp) Source #

PGTyped schemas (null PGbytea) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null PGbytea) Source #

(KnownNat n, 1 <= n) => PGTyped schemas (null (PGvarchar n)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null (PGvarchar n)) Source #

(KnownNat n, 1 <= n) => PGTyped schemas (null (PGchar n)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null (PGchar n)) Source #

PGTyped schemas (null PGtext) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null PGtext) Source #

PGTyped schemas (null PGmoney) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null PGmoney) Source #

PGTyped schemas (null PGfloat8) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null PGfloat8) Source #

PGTyped schemas (null PGfloat4) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null PGfloat4) Source #

PGTyped schemas (null PGnumeric) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null PGnumeric) Source #

PGTyped schemas (null PGint8) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null PGint8) Source #

PGTyped schemas (null PGint4) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null PGint4) Source #

PGTyped schemas (null PGint2) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null PGint2) Source #

PGTyped schemas (null PGbool) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

Methods

pgtype :: TypeExpression schemas (null PGbool) Source #

typedef :: (Has sch schemas schema, Has td schema (Typedef ty)) => QualifiedAlias sch td -> TypeExpression schemas (null ty) Source #

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

typetable :: (Has sch schemas schema, Has tab schema (Table table)) => QualifiedAlias sch tab -> TypeExpression schemas (null (PGcomposite (TableToRow table))) Source #

The composite type corresponding to a Table definition can be expressed by its alias.

typeview :: (Has sch schemas schema, Has vw schema (View view)) => QualifiedAlias sch vw -> TypeExpression schemas (null (PGcomposite view)) Source #

The composite type corresponding to a View definition can be expressed by its alias.

bool :: TypeExpression schemas (null PGbool) Source #

logical Boolean (true/false)

int2 :: TypeExpression schemas (null PGint2) Source #

signed two-byte integer

smallint :: TypeExpression schemas (null PGint2) Source #

signed two-byte integer

int4 :: TypeExpression schemas (null PGint4) Source #

signed four-byte integer

int :: TypeExpression schemas (null PGint4) Source #

signed four-byte integer

integer :: TypeExpression schemas (null PGint4) Source #

signed four-byte integer

int8 :: TypeExpression schemas (null PGint8) Source #

signed eight-byte integer

bigint :: TypeExpression schemas (null PGint8) Source #

signed eight-byte integer

numeric :: TypeExpression schemas (null PGnumeric) Source #

arbitrary precision numeric type

float4 :: TypeExpression schemas (null PGfloat4) Source #

single precision floating-point number (4 bytes)

real :: TypeExpression schemas (null PGfloat4) Source #

single precision floating-point number (4 bytes)

float8 :: TypeExpression schemas (null PGfloat8) Source #

double precision floating-point number (8 bytes)

doublePrecision :: TypeExpression schemas (null PGfloat8) Source #

double precision floating-point number (8 bytes)

money :: TypeExpression schema (null PGmoney) Source #

currency amount

text :: TypeExpression schemas (null PGtext) Source #

variable-length character string

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

fixed-length character string

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

fixed-length character string

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

variable-length character string

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

variable-length character string

bytea :: TypeExpression schemas (null PGbytea) Source #

binary data ("byte array")

timestamp :: TypeExpression schemas (null PGtimestamp) Source #

date and time (no time zone)

timestampWithTimeZone :: TypeExpression schemas (null PGtimestamptz) Source #

date and time, including time zone

date :: TypeExpression schemas (null PGdate) Source #

calendar date (year, month, day)

time :: TypeExpression schemas (null PGtime) Source #

time of day (no time zone)

timeWithTimeZone :: TypeExpression schemas (null PGtimetz) Source #

time of day, including time zone

interval :: TypeExpression schemas (null PGinterval) Source #

time span

uuid :: TypeExpression schemas (null PGuuid) Source #

universally unique identifier

inet :: TypeExpression schemas (null PGinet) Source #

IPv4 or IPv6 host address

json :: TypeExpression schemas (null PGjson) Source #

textual JSON data

jsonb :: TypeExpression schemas (null PGjsonb) Source #

binary JSON data, decomposed

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

variable length array

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

fixed length array

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

tsvector :: TypeExpression schemas (null PGtsvector) Source #

text search query

tsquery :: TypeExpression schemas (null PGtsquery) Source #

text search document