Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | eitan@morphism.tech |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Type expressions.
Synopsis
- newtype TypeExpression (schemas :: SchemasType) (ty :: NullityType) = UnsafeTypeExpression {}
- cast :: TypeExpression schemas ty1 -> Expression outer commons grp schemas params from ty0 -> Expression outer commons grp schemas params from ty1
- astype :: TypeExpression schemas ty -> Expression outer commons grp schemas params from ty -> Expression outer commons grp schemas params from ty
- inferredtype :: PGTyped schemas ty => Expression outer common grp schemas params from ty -> Expression outer common grp schemas params from ty
- class PGTyped schemas (ty :: NullityType) where
- pgtype :: TypeExpression schemas ty
- typedef :: (Has sch schemas schema, Has td schema (Typedef ty)) => QualifiedAlias sch td -> TypeExpression schemas (null ty)
- typetable :: (Has sch schemas schema, Has tab schema (Table table)) => QualifiedAlias sch tab -> TypeExpression schemas (null (PGcomposite (TableToRow table)))
- typeview :: (Has sch schemas schema, Has vw schema (View view)) => QualifiedAlias sch vw -> TypeExpression schemas (null (PGcomposite view))
- bool :: TypeExpression schemas (null PGbool)
- int2 :: TypeExpression schemas (null PGint2)
- smallint :: TypeExpression schemas (null PGint2)
- int4 :: TypeExpression schemas (null PGint4)
- int :: TypeExpression schemas (null PGint4)
- integer :: TypeExpression schemas (null PGint4)
- int8 :: TypeExpression schemas (null PGint8)
- bigint :: TypeExpression schemas (null PGint8)
- numeric :: TypeExpression schemas (null PGnumeric)
- float4 :: TypeExpression schemas (null PGfloat4)
- real :: TypeExpression schemas (null PGfloat4)
- float8 :: TypeExpression schemas (null PGfloat8)
- doublePrecision :: TypeExpression schemas (null PGfloat8)
- money :: TypeExpression schema (null PGmoney)
- text :: TypeExpression schemas (null PGtext)
- char :: forall n schemas null. (KnownNat n, 1 <= n) => TypeExpression schemas (null (PGchar n))
- character :: forall n schemas null. (KnownNat n, 1 <= n) => TypeExpression schemas (null (PGchar n))
- varchar :: forall n schemas null. (KnownNat n, 1 <= n) => TypeExpression schemas (null (PGvarchar n))
- characterVarying :: forall n schemas null. (KnownNat n, 1 <= n) => TypeExpression schemas (null (PGvarchar n))
- bytea :: TypeExpression schemas (null PGbytea)
- timestamp :: TypeExpression schemas (null PGtimestamp)
- timestampWithTimeZone :: TypeExpression schemas (null PGtimestamptz)
- date :: TypeExpression schemas (null PGdate)
- time :: TypeExpression schemas (null PGtime)
- timeWithTimeZone :: TypeExpression schemas (null PGtimetz)
- interval :: TypeExpression schemas (null PGinterval)
- uuid :: TypeExpression schemas (null PGuuid)
- inet :: TypeExpression schemas (null PGinet)
- json :: TypeExpression schemas (null PGjson)
- jsonb :: TypeExpression schemas (null PGjsonb)
- vararray :: TypeExpression schemas pg -> TypeExpression schemas (null (PGvararray pg))
- fixarray :: forall dims schemas null pg. All KnownNat dims => TypeExpression schemas pg -> TypeExpression schemas (null (PGfixarray dims pg))
- tsvector :: TypeExpression schemas (null PGtsvector)
- tsquery :: TypeExpression schemas (null PGtsquery)
Documentation
newtype TypeExpression (schemas :: SchemasType) (ty :: NullityType) Source #
TypeExpression
s are used in cast
s and
createTable
commands.
Instances
:: 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)
:: 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 :: TypeExpression schemas ty Source #
Instances
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