Copyright | (c) Ole Krüger 2016 |
---|---|
License | BSD3 |
Maintainer | Ole Krüger <ole@vprsm.de> |
Safe Haskell | Safe |
Language | Haskell2010 |
- type Generic a = (Generic a, GDataType (Rep a), DataTypeRep (Rep a) ~ Rep a)
- type Rep a = AnalyzeDataType a (Rep a)
- toGeneric :: Generic a => DataType (Rep a) -> a
- fromGeneric :: Generic a => a -> DataType (Rep a)
- data KRecord
- data KFlatSum
- data KDataType
- class GRecord rec where
- class GFlatSum enum where
- type FlatSumRep enum :: * -> *
- data FlatSum enum
- class GDataType dat where
- type DataTypeRep dat :: * -> *
- data DataType dat
- type family AnalyzeRecordRep org (sel :: * -> *) :: KRecord where ...
- type family AnalyzeFlatSumRep org (cons :: * -> *) :: KFlatSum where ...
- type family AnalyzeDataType org (dat :: * -> *) :: KDataType where ...
Generic Entity
type Generic a = (Generic a, GDataType (Rep a), DataTypeRep (Rep a) ~ Rep a) Source #
Make sure a
has a safe generic representation. Types that qualify implement Generic
(GHC)
and fulfill one of the following criteria:
- single constructor with 1 or more fields
- multiple constructors with no fields
This constraint is mostly utilized to give the user more information about why their type has been rejected.
Type-Level Information
Information about a record
Information about the constructors of an enumeration
Information about a data type
Mapper classes
class GFlatSum enum where Source #
toFlatSum :: FlatSumRep enum x -> FlatSum enum Source #
From Generic
representation
fromFlatSum :: FlatSum enum -> FlatSumRep enum x Source #
To Generic
representation
class GDataType dat where Source #
toDataType :: DataTypeRep dat x -> DataType dat Source #
From Generic
representation
fromDataType :: DataType dat -> DataTypeRep dat x Source #
To Generic
representation
Analyzers
type family AnalyzeRecordRep org (sel :: * -> *) :: KRecord where ... Source #
Analyze the Generic
representation of the selectors. Make sure it has 1 or more fields. Then
transform it into a KRecord
.
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) |
type family AnalyzeFlatSumRep org (cons :: * -> *) :: KFlatSum where ... Source #
Analyze the Generic
representation of constructors. Make sure every constructor has zero
fields. Then transform it into a KFlatSum
.
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) |
type family AnalyzeDataType org (dat :: * -> *) :: KDataType where ... Source #
Analyze the Generic
representation of a data type. If only one constructor exists, further
analyzing is delegated to AnalyzeRecordRep
. When two or more exist, analyzing is performed by
AnalyzeFlatSumRep
. The results are gather in a KDataType
instance.
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) |