Copyright | (c) Eitan Chatav 2017 |
---|---|
Maintainer | [email protected] |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Squeal.PostgreSQL.Schema
Description
Embedding of PostgreSQL type and alias system
- data PGType
- data NullityType
- data ColumnType
- type ColumnsType = [(Symbol, ColumnType)]
- type TablesType = [(Symbol, ColumnsType)]
- data Grouping
- type PGNum ty = In ty '[PGint2, PGint4, PGint8, PGnumeric, PGfloat4, PGfloat8]
- type PGIntegral ty = In ty '[PGint2, PGint4, PGint8]
- type PGFloating ty = In ty '[PGfloat4, PGfloat8, PGnumeric]
- type (:::) (alias :: Symbol) (ty :: polykind) = '(alias, ty)
- data Alias (alias :: Symbol) = Alias
- renderAlias :: KnownSymbol alias => Alias alias -> ByteString
- data Aliased expression aliased where
- As :: KnownSymbol alias => expression ty -> Alias alias -> Aliased expression (alias ::: ty)
- renderAliased :: (forall ty. expression ty -> ByteString) -> Aliased expression aliased -> ByteString
- class IsLabel (x :: Symbol) a where
- class IsTableColumn table column expression where
- type family In x xs :: Constraint where ...
- type HasUnique alias xs x = xs ~ '[alias ::: x]
- type family BaseType (ty :: ColumnType) :: PGType where ...
- type family SameTypes (columns0 :: ColumnsType) (columns1 :: ColumnsType) :: Constraint where ...
- type family AllNotNull (columns :: ColumnsType) :: Constraint where ...
- type family NotAllNull columns :: Constraint where ...
- type family NullifyType (ty :: ColumnType) :: ColumnType where ...
- type family NullifyColumns (columns :: ColumnsType) :: ColumnsType where ...
- type family NullifyTables (tables :: TablesType) :: TablesType where ...
- type family Join xs ys where ...
- type family Create alias x xs where ...
- type family Drop alias xs where ...
- type family Alter alias xs x where ...
- type family Rename alias0 alias1 xs where ...
- class SameField (fieldInfo :: FieldInfo) (fieldty :: (Symbol, ColumnType))
- type family SameFields (datatypeInfo :: DatatypeInfo) (columns :: ColumnsType) :: Constraint where ...
Kinds
PGType
is the promoted datakind of PostgreSQL types.
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) |
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 |
UnsafePGType Symbol | an escape hatch for unsupported PostgreSQL types |
data NullityType Source #
NullityType
encodes the potential presence or definite absence of a
NULL
allowing operations which are sensitive to such to be well typed.
data ColumnType Source #
ColumnType
encodes the allowance of DEFAULT
and the only way
to generate an Optional
Expression
is to use def
,
unDef
or
param
.
Constructors
Optional NullityType |
|
Required NullityType |
|
Instances
type ColumnsType = [(Symbol, ColumnType)] Source #
ColumnsType
is a kind synonym for a row of ColumnType
s.
type TablesType = [(Symbol, ColumnsType)] Source #
TablesType
is a kind synonym for a row of ColumnsType
s.
It is used as a kind for both a schema, a disjoint union of tables,
and a joined table FromClause
,
a product of tables.
Constraints
type PGNum ty = In ty '[PGint2, PGint4, PGint8, PGnumeric, PGfloat4, PGfloat8] Source #
PGNum
is a constraint on PGType
whose
Expression
s have a Num
constraint.
type PGIntegral ty = In ty '[PGint2, PGint4, PGint8] Source #
PGIntegral
is a constraint on PGType
whose
Expression
s
have div_
and
mod_
functions.
type PGFloating ty = In ty '[PGfloat4, PGfloat8, PGnumeric] Source #
PGFloating
is a constraint on PGType
whose
Expression
s
have Fractional
and Floating
constraints.
Aliases
type (:::) (alias :: Symbol) (ty :: polykind) = '(alias, ty) Source #
:::
is like a promoted version of As
, a type level pair between
an alias and some type, usually a column alias and a ColumnType
or
a table alias and a ColumnsType
.
data Alias (alias :: Symbol) Source #
Alias
es are proxies for a type level string or Symbol
and have an IsLabel
instance so that with -XOverloadedLabels
>>>
:set -XOverloadedLabels
>>>
#foobar :: Alias "foobar"
Alias
Constructors
Alias |
Instances
IsTableColumn table column (Alias table, Alias column) Source # | |
(~) Symbol alias1 alias2 => IsLabel alias1 (Alias alias2) Source # | |
Eq (Alias alias) Source # | |
Ord (Alias alias) Source # | |
Show (Alias alias) Source # | |
Generic (Alias alias) Source # | |
NFData (Alias alias) Source # | |
type Rep (Alias alias) Source # | |
renderAlias :: KnownSymbol alias => Alias alias -> ByteString Source #
>>>
renderAlias #alias
"alias"
data Aliased expression aliased where Source #
The As
operator is used to name an expression. As
is like a demoted
version of :::
.
>>>
Just "hello" `As` #hi :: Aliased Maybe ("hi" ::: String)
As (Just "hello") Alias
Constructors
As :: KnownSymbol alias => expression ty -> Alias alias -> Aliased expression (alias ::: ty) |
renderAliased :: (forall ty. expression ty -> ByteString) -> Aliased expression aliased -> ByteString Source #
>>>
let renderMaybe = fromString . maybe "Nothing" (const "Just")
>>>
renderAliased renderMaybe (Just (3::Int) `As` #an_int)
"Just AS an_int"
class IsLabel (x :: Symbol) a where #
Minimal complete definition
Instances
(~) Symbol alias1 alias2 => IsLabel alias1 (Alias alias2) # | |
HasTable table schema columns => IsLabel table (Table schema columns) # | |
(HasUnique ColumnsType table tables columns, HasColumn column columns ty, GroupedBy table column bys) => IsLabel column (Expression tables (Grouped bys) params ty) # | |
(HasColumn column columns ty, HasUnique ColumnsType table tables columns) => IsLabel column (Expression tables Ungrouped params ty) # | |
class IsTableColumn table column expression where Source #
Analagous to IsLabel
, the constraint
IsTableColumn
defines !
for a column alias qualified
by a table alias.
Minimal complete definition
Instances
IsTableColumn table column (Alias table, Alias column) Source # | |
(HasTable table tables columns, HasColumn column columns ty, GroupedBy table column bys) => IsTableColumn table column (Expression tables (Grouped bys) params ty) Source # | |
(HasTable table tables columns, HasColumn column columns ty) => IsTableColumn table column (Expression tables Ungrouped params ty) Source # | |
Type Families
type family In x xs :: Constraint where ... Source #
In x xs
is a constraint that proves that x
is in xs
.
type HasUnique alias xs x = xs ~ '[alias ::: x] Source #
HasUnique alias xs x
is a constraint that proves that xs
is a singleton
of alias ::: x
.
type family BaseType (ty :: ColumnType) :: PGType where ... Source #
BaseType
forgets about NULL
and DEFAULT
Equations
BaseType (optionality (nullity pg)) = pg |
type family SameTypes (columns0 :: ColumnsType) (columns1 :: ColumnsType) :: Constraint where ... Source #
SameTypes
is a constraint that proves two ColumnsType
s have the same
length and the same ColumnType
s.
type family AllNotNull (columns :: ColumnsType) :: Constraint where ... Source #
AllNotNull
is a constraint that proves a ColumnsType
has no NULL
s.
Equations
AllNotNull '[] = () | |
AllNotNull ((column ::: optionality (NotNull ty)) ': columns) = AllNotNull columns |
type family NotAllNull columns :: Constraint where ... Source #
NotAllNull
is a constraint that proves a ColumnsType
has some
NOT NULL
.
Equations
NotAllNull ((column ::: optionality (NotNull ty)) ': columns) = () | |
NotAllNull ((column ::: optionality (Null ty)) ': columns) = NotAllNull columns |
type family NullifyType (ty :: ColumnType) :: ColumnType where ... Source #
NullifyType
is an idempotent that nullifies a ColumnType
.
Equations
NullifyType (optionality (Null ty)) = optionality (Null ty) | |
NullifyType (optionality (NotNull ty)) = optionality (Null ty) |
type family NullifyColumns (columns :: ColumnsType) :: ColumnsType where ... Source #
NullifyColumns
is an idempotent that nullifies a ColumnsType
.
Equations
NullifyColumns '[] = '[] | |
NullifyColumns ((column ::: ty) ': columns) = (column ::: NullifyType ty) ': NullifyColumns columns |
type family NullifyTables (tables :: TablesType) :: TablesType where ... Source #
NullifyTables
is an idempotent that nullifies a TablesType
used to nullify the left or right hand side of an outer join
in a FromClause
.
Equations
NullifyTables '[] = '[] | |
NullifyTables ((table ::: columns) ': tables) = (table ::: NullifyColumns columns) ': NullifyTables tables |
type family Join xs ys where ... Source #
Join
is simply promoted ++
and is used in JOIN
s in
FromClause
s.
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
addColumnDefault
and
addColumnNull
statements.
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.
type family Alter alias xs x where ... Source #
Alter alias xs x
replaces the type associated with an alias
in xs
with the type x
and is used in alterTable
and alterColumn
.
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
.
Generics
type family SameFields (datatypeInfo :: DatatypeInfo) (columns :: ColumnsType) :: Constraint where ... Source #
A SameFields
constraint proves that a
DatatypeInfo
of a record type has the same
field names as the column aliases of a ColumnsType
.
Equations
SameFields (ADT _module _datatype '[Record _constructor fields]) columns = AllZip SameField fields columns | |
SameFields (Newtype _module _datatype (Record _constructor fields)) columns = AllZip SameField fields columns |