module Database.PostgreSQL.Store.Generics (
Generic,
Rep,
toGeneric,
fromGeneric,
KRecord (..),
KFlatSum (..),
KDataType (..),
GRecord (..),
GFlatSum (..),
GDataType (..),
Record (..),
FlatSum (..),
DataType (..),
AnalyzeRecordRep,
AnalyzeFlatSumRep,
AnalyzeDataType
) where
import GHC.Generics hiding (Generic (..))
import qualified GHC.Generics as G
import GHC.TypeLits
import Data.Kind
data KRecord
= TCombine KRecord KRecord
| TSingle Meta Type
class GRecord (rec :: KRecord) where
type RecordRep rec :: * -> *
data Record rec
toRecord :: RecordRep rec x -> Record rec
fromRecord :: Record rec -> RecordRep rec x
instance GRecord ('TSingle meta typ) where
type RecordRep ('TSingle meta typ) = S1 meta (Rec0 typ)
data Record ('TSingle meta typ) = Single typ
toRecord (M1 (K1 x)) = Single x
fromRecord (Single x) = M1 (K1 x)
deriving instance (Show typ) => Show (Record ('TSingle meta typ))
instance (GRecord lhs, GRecord rhs) => GRecord ('TCombine lhs rhs) where
type RecordRep ('TCombine lhs rhs) = RecordRep lhs :*: RecordRep rhs
data Record ('TCombine lhs rhs) = Combine (Record lhs) (Record rhs)
toRecord (lhs :*: rhs) = Combine (toRecord lhs) (toRecord rhs)
fromRecord (Combine lhs rhs) = fromRecord lhs :*: fromRecord rhs
deriving instance (Show (Record lhs), Show (Record rhs)) => Show (Record ('TCombine lhs rhs))
type family AnalyzeRecordRep org (sel :: * -> *) :: KRecord where
AnalyzeRecordRep org (S1 meta (Rec0 typ)) =
'TSingle meta typ
AnalyzeRecordRep org (lhs :*: rhs) =
'TCombine (AnalyzeRecordRep org lhs) (AnalyzeRecordRep org rhs)
AnalyzeRecordRep org U1 =
TypeError ('Text "Given type "
':<>: 'ShowType org
':<>: 'Text " has one constructor, therefore that constructor must have \
\at least one field")
AnalyzeRecordRep org other =
TypeError ('Text "Given type "
':<>: 'ShowType org
':<>: 'Text " has a constructor with an invalid selector"
':$$: 'ShowType other)
data KFlatSum
= TChoose KFlatSum KFlatSum
| TValue Meta
class GFlatSum (enum :: KFlatSum) where
type FlatSumRep enum :: * -> *
data FlatSum enum
toFlatSum :: FlatSumRep enum x -> FlatSum enum
fromFlatSum :: FlatSum enum -> FlatSumRep enum x
instance GFlatSum ('TValue meta) where
type FlatSumRep ('TValue meta) = C1 meta U1
data FlatSum ('TValue meta) = Unit
toFlatSum (M1 U1) = Unit
fromFlatSum Unit = M1 U1
deriving instance Show (FlatSum ('TValue meta))
instance (GFlatSum lhs, GFlatSum rhs) => GFlatSum ('TChoose lhs rhs) where
type FlatSumRep ('TChoose lhs rhs) = FlatSumRep lhs :+: FlatSumRep rhs
data FlatSum ('TChoose lhs rhs) = ChooseLeft (FlatSum lhs) | ChooseRight (FlatSum rhs)
toFlatSum (L1 lhs) = ChooseLeft (toFlatSum lhs)
toFlatSum (R1 rhs) = ChooseRight (toFlatSum rhs)
fromFlatSum (ChooseLeft lhs) = L1 (fromFlatSum lhs)
fromFlatSum (ChooseRight rhs) = R1 (fromFlatSum rhs)
deriving instance (Show (FlatSum lhs), Show (FlatSum rhs)) => Show (FlatSum ('TChoose lhs rhs))
type family AnalyzeFlatSumRep org (cons :: * -> *) :: KFlatSum where
AnalyzeFlatSumRep org (C1 meta U1) =
'TValue meta
AnalyzeFlatSumRep org (C1 meta1 (S1 meta2 rec)) =
TypeError ('Text "Given type "
':<>: 'ShowType org
':<>: 'Text " has multiple constructors, therefore these constructors must have \
\no fields")
AnalyzeFlatSumRep org (C1 meta1 (lhs :*: rhs)) =
TypeError ('Text "Given type "
':<>: 'ShowType org
':<>: 'Text " has multiple constructors, therefore these constructors must have \
\no fields")
AnalyzeFlatSumRep org (lhs :+: rhs) =
'TChoose (AnalyzeFlatSumRep org lhs) (AnalyzeFlatSumRep org rhs)
AnalyzeFlatSumRep org other =
TypeError ('Text "Given type "
':<>: 'ShowType org
':<>: 'Text " has an invalid constructor"
':$$: 'ShowType other)
data KDataType
= TRecord Meta Meta KRecord
| TFlatSum Meta KFlatSum
class GDataType (dat :: KDataType) where
type DataTypeRep dat :: * -> *
data DataType dat
toDataType :: DataTypeRep dat x -> DataType dat
fromDataType :: DataType dat -> DataTypeRep dat x
instance (GRecord rec) => GDataType ('TRecord d c rec) where
type DataTypeRep ('TRecord d c rec) = D1 d (C1 c (RecordRep rec))
data DataType ('TRecord d c rec) = Record (Record rec)
toDataType (M1 (M1 rec)) = Record (toRecord rec)
fromDataType (Record rec) = M1 (M1 (fromRecord rec))
deriving instance (Show (Record rec)) => Show (DataType ('TRecord d c rec))
instance (GFlatSum enum) => GDataType ('TFlatSum d enum) where
type DataTypeRep ('TFlatSum d enum) = D1 d (FlatSumRep enum)
data DataType ('TFlatSum d enum) = FlatSum (FlatSum enum)
toDataType (M1 enum) = FlatSum (toFlatSum enum)
fromDataType (FlatSum flatSum) = M1 (fromFlatSum flatSum)
deriving instance (Show (FlatSum enum)) => Show (DataType ('TFlatSum d enum))
type family AnalyzeDataType org (dat :: * -> *) :: KDataType where
AnalyzeDataType org (D1 meta1 (C1 meta2 sel)) =
'TRecord meta1 meta2 (AnalyzeRecordRep org sel)
AnalyzeDataType org (D1 meta (lhs :+: rhs)) =
'TFlatSum meta (AnalyzeFlatSumRep org (lhs :+: rhs))
AnalyzeDataType org (D1 meta V1) =
TypeError ('Text "Given type "
':<>: 'ShowType org
':<>: 'Text " must have a constructor")
AnalyzeDataType org (D1 meta other) =
TypeError ('Text "Given type "
':<>: 'ShowType org
':<>: 'Text " has an invalid constructor"
':$$: 'ShowType other)
AnalyzeDataType org other =
TypeError ('Text "Given type "
':<>: 'ShowType org
':<>: 'Text " is not a valid data type"
':$$: 'ShowType other)
type Rep a = AnalyzeDataType a (G.Rep a)
type Generic a = (G.Generic a, GDataType (Rep a), DataTypeRep (Rep a) ~ G.Rep a)
fromGeneric :: (Generic a) => a -> DataType (Rep a)
fromGeneric = toDataType . G.from
toGeneric :: (Generic a) => DataType (Rep a) -> a
toGeneric = G.to . fromDataType