{-# LANGUAGE
AllowAmbiguousTypes
, DeriveAnyClass
, DeriveFoldable
, DeriveFunctor
, DeriveGeneric
, DeriveTraversable
, DerivingStrategies
, DefaultSignatures
, FlexibleContexts
, FlexibleInstances
, FunctionalDependencies
, GADTs
, LambdaCase
, MultiParamTypeClasses
, OverloadedStrings
, ScopedTypeVariables
, TypeApplications
, TypeFamilies
, TypeInType
, TypeOperators
, UndecidableInstances
, UndecidableSuperClasses
#-}
module Squeal.PostgreSQL.Type.PG
(
IsPG (..)
, NullPG
, TuplePG
, RowPG
, LabelsPG
, DimPG
, FixPG
, TupleOf
, TupleCodeOf
, RowOf
, ConstructorsOf
, ConstructorNameOf
, ConstructorNamesOf
) where
import Data.Aeson (Value)
import Data.Functor.Const (Const)
import Data.Functor.Constant (Constant)
import Data.Kind (Type)
import Data.Int (Int16, Int32, Int64)
import Data.Scientific (Scientific)
import Data.Time (Day, DiffTime, LocalTime, TimeOfDay, TimeZone, UTCTime)
import Data.Vector (Vector)
import Data.UUID.Types (UUID)
import GHC.TypeLits
import Network.IP.Addr (NetAddr, IP)
import qualified Data.ByteString.Lazy as Lazy (ByteString)
import qualified Data.ByteString as Strict (ByteString)
import qualified Data.Text.Lazy as Lazy (Text)
import qualified Data.Text as Strict (Text)
import qualified Database.PostgreSQL.LibPQ as LibPQ
import qualified Generics.SOP as SOP
import qualified Generics.SOP.Record as SOP
import qualified Generics.SOP.Type.Metadata as Type
import Squeal.PostgreSQL.Type
import Squeal.PostgreSQL.Type.Alias
import Squeal.PostgreSQL.Type.Schema
class IsPG (hask :: Type) where type PG hask :: PGType
instance IsPG Bool where type PG Bool = 'PGbool
instance IsPG Int16 where type PG Int16 = 'PGint2
instance IsPG Int32 where type PG Int32 = 'PGint4
instance IsPG Int64 where type PG Int64 = 'PGint8
instance IsPG LibPQ.Oid where type PG LibPQ.Oid = 'PGoid
instance IsPG Scientific where type PG Scientific = 'PGnumeric
instance IsPG Float where type PG Float = 'PGfloat4
instance IsPG Double where type PG Double = 'PGfloat8
instance IsPG Char where type PG Char = 'PGchar 1
instance IsPG Strict.Text where type PG Strict.Text = 'PGtext
instance IsPG Lazy.Text where type PG Lazy.Text = 'PGtext
instance IsPG String where type PG String = 'PGtext
instance IsPG Strict.ByteString where type PG Strict.ByteString = 'PGbytea
instance IsPG Lazy.ByteString where type PG Lazy.ByteString = 'PGbytea
instance IsPG LocalTime where type PG LocalTime = 'PGtimestamp
instance IsPG UTCTime where type PG UTCTime = 'PGtimestamptz
instance IsPG Day where type PG Day = 'PGdate
instance IsPG TimeOfDay where type PG TimeOfDay = 'PGtime
instance IsPG (TimeOfDay, TimeZone) where type PG (TimeOfDay, TimeZone) = 'PGtimetz
instance IsPG DiffTime where type PG DiffTime = 'PGinterval
instance IsPG UUID where type PG UUID = 'PGuuid
instance IsPG (NetAddr IP) where type PG (NetAddr IP) = 'PGinet
instance IsPG Value where type PG Value = 'PGjson
instance IsPG (VarChar n) where type PG (VarChar n) = 'PGvarchar n
instance IsPG (FixChar n) where type PG (FixChar n) = 'PGchar n
instance IsPG hask => IsPG (Const hask tag) where type PG (Const hask tag) = PG hask
instance IsPG hask => IsPG (SOP.K hask tag) where type PG (SOP.K hask tag) = PG hask
instance IsPG hask => IsPG (Constant hask tag) where type PG (Constant hask tag) = PG hask
instance IsPG Money where type PG Money = 'PGmoney
instance IsPG (Json hask) where type PG (Json hask) = 'PGjson
instance IsPG (Jsonb hask) where type PG (Jsonb hask) = 'PGjsonb
instance IsPG (Composite hask) where
type PG (Composite hask) = 'PGcomposite (RowPG hask)
instance IsPG (Enumerated hask) where
type PG (Enumerated hask) = 'PGenum (LabelsPG hask)
instance IsPG (VarArray (Vector x)) where
type PG (VarArray (Vector x)) = 'PGvararray (NullPG x)
instance IsPG (VarArray [x]) where
type PG (VarArray [x]) = 'PGvararray (NullPG x)
instance IsPG (FixArray hask) where
type PG (FixArray hask) = 'PGfixarray (DimPG hask) (FixPG hask)
type family LabelsPG (hask :: Type) :: [Type.ConstructorName] where
LabelsPG hask =
ConstructorNamesOf (ConstructorsOf (SOP.DatatypeInfoOf hask))
type family RowPG (hask :: Type) :: RowType where
RowPG hask = RowOf (SOP.RecordCodeOf hask)
type family RowOf (record :: [(Symbol, Type)]) :: RowType where
RowOf (col ::: ty ': record) = col ::: NullPG ty ': RowOf record
RowOf '[] = '[]
type family NullPG (hask :: Type) :: NullType where
NullPG (Maybe hask) = 'Null (PG hask)
NullPG hask = 'NotNull (PG hask)
type family TuplePG (hask :: Type) :: [NullType] where
TuplePG hask = TupleOf (TupleCodeOf hask (SOP.Code hask))
type family TupleOf (tuple :: [Type]) :: [NullType] where
TupleOf (hask ': tuple) = NullPG hask ': TupleOf tuple
TupleOf '[] = '[]
type family TupleCodeOf (hask :: Type) (code :: [[Type]]) :: [Type] where
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 :: Type.DatatypeInfo)
:: [Type.ConstructorInfo] where
ConstructorsOf ('Type.ADT _module _datatype constructors _strictness) =
constructors
ConstructorsOf ('Type.Newtype _module _datatype constructor) =
'[constructor]
type family ConstructorNameOf (constructor :: Type.ConstructorInfo)
:: Type.ConstructorName where
ConstructorNameOf ('Type.Constructor name) = name
ConstructorNameOf ('Type.Infix name _assoc _fix) = TypeError
('Text "ConstructorNameOf error: non-nullary constructor "
':<>: 'Text name)
ConstructorNameOf ('Type.Record name _fields) = TypeError
('Text "ConstructorNameOf error: non-nullary constructor "
':<>: 'Text name)
type family ConstructorNamesOf (constructors :: [Type.ConstructorInfo])
:: [Type.ConstructorName] where
ConstructorNamesOf '[] = '[]
ConstructorNamesOf (constructor ': constructors) =
ConstructorNameOf constructor ': ConstructorNamesOf constructors
type family DimPG (hask :: Type) :: [Nat] where
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
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