squeal-postgresql-0.9.1.3: Squeal PostgreSQL Library
Copyright(c) Eitan Chatav 2010
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Squeal.PostgreSQL.Type.PG

Description

Provides type families for turning Haskell Types into corresponding Postgres types.

Synopsis

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 PGs 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]

Associated Types

type PG hask :: PGType Source #

Instances

Instances details
IsPG Value Source #

PGjson

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG Value :: PGType Source #

IsPG Int16 Source #

PGint2

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG Int16 :: PGType Source #

IsPG Int32 Source #

PGint4

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG Int32 :: PGType Source #

IsPG Int64 Source #

PGint8

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG Int64 :: PGType Source #

IsPG ByteString Source #

PGbytea

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG ByteString :: PGType Source #

IsPG ByteString Source #

PGbytea

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG ByteString :: PGType Source #

IsPG Oid Source #

PGint2

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG Oid :: PGType Source #

IsPG Scientific Source #

PGnumeric

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG Scientific :: PGType Source #

IsPG Money Source #

PGmoney

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG Money :: PGType Source #

IsPG Text Source #

PGtext

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG Text :: PGType Source #

IsPG Text Source #

PGtext

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG Text :: PGType Source #

IsPG Day Source #

PGdate

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG Day :: PGType Source #

IsPG DiffTime Source #

PGinterval

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG DiffTime :: PGType Source #

IsPG UTCTime Source #

PGtimestamptz

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG UTCTime :: PGType Source #

IsPG LocalTime Source #

PGtimestamp

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG LocalTime :: PGType Source #

IsPG TimeOfDay Source #

PGtime

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG TimeOfDay :: PGType Source #

IsPG UUID Source #

PGuuid

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG UUID :: PGType Source #

IsPG String Source #

PGtext

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG String :: PGType Source #

IsPG Bool Source #

PGbool

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG Bool :: PGType Source #

IsPG Char Source #

PGchar 1

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG Char :: PGType Source #

IsPG Double Source #

PGfloat8

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG Double :: PGType Source #

IsPG Float Source #

PGfloat4

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG Float :: PGType Source #

IsPG (NetAddr IP) Source #

PGinet

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (NetAddr IP) :: PGType Source #

IsPG hask => IsPG (Range hask) Source #

PGrange (PG hask)

Instance details

Defined in Squeal.PostgreSQL.Expression.Range

Associated Types

type PG (Range hask) :: PGType Source #

IsPG (Composite hask) Source #

PGcomposite (RowPG hask)

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (Composite hask) :: PGType Source #

IsPG (Enumerated hask) Source #

PGenum (LabelsPG hask)

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (Enumerated hask) :: PGType Source #

IsPG (FixArray hask) Source #

PGfixarray (DimPG hask) (FixPG hask)

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (FixArray hask) :: PGType Source #

IsPG (FixChar n) Source #

PGvarchar

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (FixChar n) :: PGType Source #

IsPG (Json hask) Source #

PGjson

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (Json hask) :: PGType Source #

IsPG (Jsonb hask) Source #

PGjsonb

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (Jsonb hask) :: PGType Source #

IsPG (VarArray (Vector x)) Source #

PGvararray (NullPG x)

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (VarArray (Vector x)) :: PGType Source #

IsPG (VarArray [x]) Source #

PGvararray (NullPG x)

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (VarArray [x]) :: PGType Source #

IsPG (VarChar n) Source #

PGvarchar

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (VarChar n) :: PGType Source #

IsPG (TimeOfDay, TimeZone) Source #

PGtimetz

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (TimeOfDay, TimeZone) :: PGType Source #

IsPG hask => IsPG (Const hask tag) Source #

`PG hask`

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (Const hask tag) :: PGType Source #

IsPG hask => IsPG (K hask tag) Source #

`PG hask`

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (K hask tag) :: PGType Source #

IsPG hask => IsPG (Constant hask tag) Source #

`PG hask`

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (Constant hask tag) :: PGType Source #

type family NullPG (hask :: Type) :: NullType where ... Source #

NullPG turns a Haskell type into a NullType.

>>> :kind! NullPG Double
NullPG Double :: NullType
= 'NotNull 'PGfloat8
>>> :kind! NullPG (Maybe Double)
NullPG (Maybe Double) :: NullType
= 'Null 'PGfloat8

Equations

NullPG (Maybe hask) = 'Null (PG hask) 
NullPG hask = 'NotNull (PG hask) 

type family TuplePG (hask :: Type) :: [NullType] where ... Source #

TuplePG turns a Haskell tuple type (including record types) into the corresponding list of NullTypes.

>>> :kind! TuplePG (Double, Maybe Char)
TuplePG (Double, Maybe Char) :: [NullType]
= '[ 'NotNull 'PGfloat8, 'Null ('PGchar 1)]

Equations

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]

Equations

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"]

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.

Equations

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.

Equations

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 TupleOf (tuple :: [Type]) :: [NullType] where ... Source #

TupleOf turns a list of Haskell Types into a list of NullTypes.

Equations

TupleOf (hask ': tuple) = NullPG hask ': TupleOf tuple 
TupleOf '[] = '[] 

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.

Equations

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 RowOf (record :: [(Symbol, Type)]) :: RowType where ... Source #

RowOf applies NullPG to the fields of a list.

Equations

RowOf ((col ::: ty) ': record) = (col ::: NullPG ty) ': RowOf record 
RowOf '[] = '[] 

type family ConstructorsOf (datatype :: DatatypeInfo) :: [ConstructorInfo] where ... Source #

Calculates constructors of a datatype.

Equations

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.

Equations

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.

Equations

ConstructorNamesOf '[] = '[] 
ConstructorNamesOf (constructor ': constructors) = ConstructorNameOf constructor ': ConstructorNamesOf constructors