Copyright | (c) Eitan Chatav 2010 |
---|---|
Maintainer | eitan@morphism.tech |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Provides type families for turning Haskell Type
s
into corresponding Postgres types.
Synopsis
- class IsPG (hask :: Type) where
- type family NullPG (hask :: Type) :: NullType where ...
- type family TuplePG (hask :: Type) :: [NullType] where ...
- type family RowPG (hask :: Type) :: RowType where ...
- type family LabelsPG (hask :: Type) :: [ConstructorName] where ...
- type family DimPG (hask :: Type) :: [Nat] where ...
- type family FixPG (hask :: Type) :: NullType where ...
- type family TupleOf (tuple :: [Type]) :: [NullType] where ...
- type family TupleCodeOf (hask :: Type) (code :: [[Type]]) :: [Type] where ...
- type family RowOf (record :: [(Symbol, Type)]) :: RowType where ...
- type family ConstructorsOf (datatype :: DatatypeInfo) :: [ConstructorInfo] where ...
- type family ConstructorNameOf (constructor :: ConstructorInfo) :: ConstructorName where ...
- type family ConstructorNamesOf (constructors :: [ConstructorInfo]) :: [ConstructorName] where ...
PG
class IsPG (hask :: Type) Source #
The PG
type family embeds a subset of Haskell types
as Postgres types. As an open type family, PG
is extensible.
>>>
:kind! PG LocalTime
PG LocalTime :: PGType = 'PGtimestamp
The preferred way to generate PG
s of your own type is through
generalized newtype deriving or via deriving.
>>>
newtype UserId = UserId {getUserId :: UUID} deriving newtype IsPG
>>>
:kind! PG UserId
PG UserId :: PGType = 'PGuuid
>>>
:{
data Answer = Yes | No deriving stock GHC.Generic deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo) deriving IsPG via Enumerated Answer :}
>>>
:kind! PG Answer
PG Answer :: PGType = 'PGenum '["Yes", "No"]
>>>
:{
data Complex = Complex {real :: Double, imaginary :: Double} deriving stock GHC.Generic deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo) deriving IsPG via Composite Complex :}
>>>
:kind! PG Complex
PG Complex :: PGType = 'PGcomposite '["real" ::: 'NotNull 'PGfloat8, "imaginary" ::: 'NotNull 'PGfloat8]
Instances
type family NullPG (hask :: Type) :: NullType where ... Source #
type family TuplePG (hask :: Type) :: [NullType] where ... Source #
TuplePG
turns a Haskell tuple type (including record types) into
the corresponding list of NullType
s.
>>>
:kind! TuplePG (Double, Maybe Char)
TuplePG (Double, Maybe Char) :: [NullType] = '[ 'NotNull 'PGfloat8, 'Null ('PGchar 1)]
TuplePG hask = TupleOf (TupleCodeOf hask (Code hask)) |
type family RowPG (hask :: Type) :: RowType where ... Source #
RowPG
turns a Haskell Type
into a RowType
.
RowPG
may be applied to normal Haskell record types provided they
have Generic
and HasDatatypeInfo
instances;
>>>
data Person = Person { name :: Strict.Text, age :: Int32 } deriving GHC.Generic
>>>
instance SOP.Generic Person
>>>
instance SOP.HasDatatypeInfo Person
>>>
:kind! RowPG Person
RowPG Person :: [(Symbol, NullType)] = '["name" ::: 'NotNull 'PGtext, "age" ::: 'NotNull 'PGint4]
RowPG hask = RowOf (RecordCodeOf hask) |
Type families
type family LabelsPG (hask :: Type) :: [ConstructorName] where ... Source #
The LabelsPG
type family calculates the constructors of a
Haskell enum type.
>>>
data Schwarma = Beef | Lamb | Chicken deriving GHC.Generic
>>>
instance SOP.Generic Schwarma
>>>
instance SOP.HasDatatypeInfo Schwarma
>>>
:kind! LabelsPG Schwarma
LabelsPG Schwarma :: [Type.ConstructorName] = '["Beef", "Lamb", "Chicken"]
LabelsPG hask = ConstructorNamesOf (ConstructorsOf (DatatypeInfoOf hask)) |
type family DimPG (hask :: Type) :: [Nat] where ... Source #
DimPG
turns Haskell nested homogeneous tuples into a list of lengths,
up to a depth of 10 for each dimension.
DimPG (x, x) = 2 ': DimPG x | |
DimPG (x, x, x) = 3 ': DimPG x | |
DimPG (x, x, x, x) = 4 ': DimPG x | |
DimPG (x, x, x, x, x) = 5 ': DimPG x | |
DimPG (x, x, x, x, x, x) = 6 ': DimPG x | |
DimPG (x, x, x, x, x, x, x) = 7 ': DimPG x | |
DimPG (x, x, x, x, x, x, x, x) = 8 ': DimPG x | |
DimPG (x, x, x, x, x, x, x, x, x) = 9 ': DimPG x | |
DimPG (x, x, x, x, x, x, x, x, x, x) = 10 ': DimPG x | |
DimPG x = '[] |
type family FixPG (hask :: Type) :: NullType where ... Source #
FixPG
extracts NullPG
of the base type of nested homogeneous tuples,
up to a depth of 10 for each dimension.
FixPG (x, x) = FixPG x | |
FixPG (x, x, x) = FixPG x | |
FixPG (x, x, x, x) = FixPG x | |
FixPG (x, x, x, x, x) = FixPG x | |
FixPG (x, x, x, x, x, x) = FixPG x | |
FixPG (x, x, x, x, x, x, x) = FixPG x | |
FixPG (x, x, x, x, x, x, x, x) = FixPG x | |
FixPG (x, x, x, x, x, x, x, x, x) = FixPG x | |
FixPG (x, x, x, x, x, x, x, x, x, x) = FixPG x | |
FixPG (x, x, x, x, x, x, x, x, x, x, x) = FixPG x | |
FixPG x = NullPG x |
type family TupleCodeOf (hask :: Type) (code :: [[Type]]) :: [Type] where ... Source #
TupleCodeOf
takes the Code
of a haskell Type
and if it's a simple product returns it, otherwise giving a TypeError
.
TupleCodeOf hask '[tuple] = tuple | |
TupleCodeOf hask '[] = TypeError ((('Text "The type `" :<>: 'ShowType hask) :<>: 'Text "' is not a tuple type.") :$$: 'Text "It is a void type with no constructors.") | |
TupleCodeOf hask (_ ': (_ ': _)) = TypeError ((('Text "The type `" :<>: 'ShowType hask) :<>: 'Text "' is not a tuple type.") :$$: 'Text "It is a sum type with more than one constructor.") |
type family ConstructorsOf (datatype :: DatatypeInfo) :: [ConstructorInfo] where ... Source #
Calculates constructors of a datatype.
ConstructorsOf ('ADT _module _datatype constructors _strictness) = constructors | |
ConstructorsOf ('Newtype _module _datatype constructor) = '[constructor] |
type family ConstructorNameOf (constructor :: ConstructorInfo) :: ConstructorName where ... Source #
Calculates the name of a nullary constructor, otherwise generates a type error.
ConstructorNameOf ('Constructor name) = name | |
ConstructorNameOf ('Infix name _assoc _fix) = TypeError ('Text "ConstructorNameOf error: non-nullary constructor " :<>: 'Text name) | |
ConstructorNameOf ('Record name _fields) = TypeError ('Text "ConstructorNameOf error: non-nullary constructor " :<>: 'Text name) |
type family ConstructorNamesOf (constructors :: [ConstructorInfo]) :: [ConstructorName] where ... Source #
Calculate the names of nullary constructors.
ConstructorNamesOf '[] = '[] | |
ConstructorNamesOf (constructor ': constructors) = ConstructorNameOf constructor ': ConstructorNamesOf constructors |