Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | [email protected] |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Squeal.PostgreSQL.Expression.Type
Description
type expressions
Synopsis
- cast :: TypeExpression db ty1 -> Expression grp lat with db params from ty0 -> Expression grp lat with db params from ty1
- astype :: TypeExpression db ty -> Expression grp lat with db params from ty -> Expression grp lat with db params from ty
- inferredtype :: NullTyped db ty => Expression lat common grp db params from ty -> Expression lat common grp db params from ty
- newtype TypeExpression (db :: SchemasType) (ty :: NullType) = UnsafeTypeExpression {}
- typedef :: (Has sch db schema, Has td schema (Typedef ty)) => QualifiedAlias sch td -> TypeExpression db (null ty)
- typetable :: (Has sch db schema, Has tab schema (Table table)) => QualifiedAlias sch tab -> TypeExpression db (null (PGcomposite (TableToRow table)))
- typeview :: (Has sch db schema, Has vw schema (View view)) => QualifiedAlias sch vw -> TypeExpression db (null (PGcomposite view))
- bool :: TypeExpression db (null PGbool)
- int2 :: TypeExpression db (null PGint2)
- smallint :: TypeExpression db (null PGint2)
- int4 :: TypeExpression db (null PGint4)
- int :: TypeExpression db (null PGint4)
- integer :: TypeExpression db (null PGint4)
- int8 :: TypeExpression db (null PGint8)
- bigint :: TypeExpression db (null PGint8)
- numeric :: TypeExpression db (null PGnumeric)
- float4 :: TypeExpression db (null PGfloat4)
- real :: TypeExpression db (null PGfloat4)
- float8 :: TypeExpression db (null PGfloat8)
- doublePrecision :: TypeExpression db (null PGfloat8)
- money :: TypeExpression schema (null PGmoney)
- text :: TypeExpression db (null PGtext)
- char :: forall n db null. (KnownNat n, 1 <= n) => TypeExpression db (null (PGchar n))
- character :: forall n db null. (KnownNat n, 1 <= n) => TypeExpression db (null (PGchar n))
- varchar :: forall n db null. (KnownNat n, 1 <= n) => TypeExpression db (null (PGvarchar n))
- characterVarying :: forall n db null. (KnownNat n, 1 <= n) => TypeExpression db (null (PGvarchar n))
- bytea :: TypeExpression db (null PGbytea)
- timestamp :: TypeExpression db (null PGtimestamp)
- timestampWithTimeZone :: TypeExpression db (null PGtimestamptz)
- timestamptz :: TypeExpression db (null PGtimestamptz)
- date :: TypeExpression db (null PGdate)
- time :: TypeExpression db (null PGtime)
- timeWithTimeZone :: TypeExpression db (null PGtimetz)
- timetz :: TypeExpression db (null PGtimetz)
- interval :: TypeExpression db (null PGinterval)
- uuid :: TypeExpression db (null PGuuid)
- inet :: TypeExpression db (null PGinet)
- json :: TypeExpression db (null PGjson)
- jsonb :: TypeExpression db (null PGjsonb)
- vararray :: TypeExpression db pg -> TypeExpression db (null (PGvararray pg))
- fixarray :: forall dims db null pg. All KnownNat dims => TypeExpression db pg -> TypeExpression db (null (PGfixarray dims pg))
- tsvector :: TypeExpression db (null PGtsvector)
- tsquery :: TypeExpression db (null PGtsquery)
- oid :: TypeExpression db (null PGoid)
- int4range :: TypeExpression db (null (PGrange PGint4))
- int8range :: TypeExpression db (null (PGrange PGint8))
- numrange :: TypeExpression db (null (PGrange PGnumeric))
- tsrange :: TypeExpression db (null (PGrange PGtimestamp))
- tstzrange :: TypeExpression db (null (PGrange PGtimestamptz))
- daterange :: TypeExpression db (null (PGrange PGdate))
- record :: TypeExpression db (null (PGcomposite record))
- newtype ColumnTypeExpression (db :: SchemasType) (ty :: ColumnType) = UnsafeColumnTypeExpression {}
- nullable :: TypeExpression db (null ty) -> ColumnTypeExpression db (NoDef :=> Null ty)
- notNullable :: TypeExpression db (null ty) -> ColumnTypeExpression db (NoDef :=> NotNull ty)
- default_ :: Expression Ungrouped '[] '[] db '[] '[] ty -> ColumnTypeExpression db (NoDef :=> ty) -> ColumnTypeExpression db (Def :=> ty)
- serial2 :: ColumnTypeExpression db (Def :=> NotNull PGint2)
- smallserial :: ColumnTypeExpression db (Def :=> NotNull PGint2)
- serial4 :: ColumnTypeExpression db (Def :=> NotNull PGint4)
- serial :: ColumnTypeExpression db (Def :=> NotNull PGint4)
- serial8 :: ColumnTypeExpression db (Def :=> NotNull PGint8)
- bigserial :: ColumnTypeExpression db (Def :=> NotNull PGint8)
- class PGTyped db (ty :: PGType) where
- pgtype :: TypeExpression db (null ty)
- pgtypeFrom :: forall hask db null. PGTyped db (PG hask) => TypeExpression db (null (PG hask))
- class NullTyped db (ty :: NullType) where
- nulltype :: TypeExpression db ty
- nulltypeFrom :: forall hask db. NullTyped db (NullPG hask) => TypeExpression db (NullPG hask)
- class ColumnTyped db (column :: ColumnType) where
- columntype :: ColumnTypeExpression db column
- columntypeFrom :: forall hask db. ColumnTyped db (NoDef :=> NullPG hask) => ColumnTypeExpression db (NoDef :=> NullPG hask)
- class FieldTyped db ty where
- fieldtype :: Aliased (TypeExpression db) ty
Type Cast
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)
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)
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 #
TypeExpression
s are used in cast
s and
createTable
commands.
Constructors
UnsafeTypeExpression | |
Fields |
Instances
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.
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.
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.
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.
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
record :: TypeExpression db (null (PGcomposite record)) Source #
Anonymous composite record
Column Type
newtype ColumnTypeExpression (db :: SchemasType) (ty :: ColumnType) Source #
ColumnTypeExpression
s are used in
createTable
commands.
Constructors
UnsafeColumnTypeExpression | |
Fields |
Instances
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
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
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 #
Methods
pgtype :: TypeExpression db (null ty) Source #
Instances
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.
Methods
nulltype :: TypeExpression db ty Source #
Instances
PGTyped db ty => NullTyped db (null ty) Source # | |
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.
Methods
columntype :: ColumnTypeExpression db column Source #
Instances
NullTyped db (NotNull ty) => ColumnTyped db (NoDef :=> NotNull ty) Source # | |
Defined in Squeal.PostgreSQL.Expression.Type Methods columntype :: ColumnTypeExpression db (NoDef :=> NotNull ty) Source # | |
NullTyped db (Null ty) => ColumnTyped db (NoDef :=> Null ty) Source # | |
Defined in Squeal.PostgreSQL.Expression.Type Methods columntype :: ColumnTypeExpression db (NoDef :=> Null ty) Source # |
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
Methods
fieldtype :: Aliased (TypeExpression db) ty Source #
Instances
(KnownSymbol alias, NullTyped db ty) => FieldTyped db (alias ::: ty) Source # | |
Defined in Squeal.PostgreSQL.Expression.Type |