pg-store-0.4.0: Simple storage interface to PostgreSQL

Copyright(c) Ole Krüger 2016
LicenseBSD3
MaintainerOle Krüger <ole@vprsm.de>
Safe HaskellSafe
LanguageHaskell2010

Database.PostgreSQL.Store.Generics

Contents

Description

 

Synopsis

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 Rep a = AnalyzeDataType a (Rep a) Source #

KDataType representation of a data type

toGeneric :: Generic a => DataType (Rep a) -> a Source #

Build from generic representation.

fromGeneric :: Generic a => a -> DataType (Rep a) Source #

Convert to generic representation.

Type-Level Information

data KRecord Source #

Information about a record

Constructors

TCombine KRecord KRecord

Combination of two records

TSingle Meta Type

Single element with meta information and type

data KFlatSum Source #

Information about the constructors of an enumeration

Constructors

TChoose KFlatSum KFlatSum

Combination of values

TValue Meta

Single value of the enumeration

data KDataType Source #

Information about a data type

Constructors

TRecord Meta Meta KRecord

Record

TFlatSum Meta KFlatSum

Enumeration

Mapper classes

class GRecord rec where Source #

Mappings between a Generic representation and our KRecord-based representation

Minimal complete definition

toRecord, fromRecord

Associated Types

type RecordRep rec :: * -> * Source #

Generic representation

data Record rec Source #

KRecord-based representation

Methods

toRecord :: RecordRep rec x -> Record rec Source #

From Generic representation

fromRecord :: Record rec -> RecordRep rec x Source #

To Generic representation

Instances

(GRecord lhs, GRecord rhs) => GRecord (TCombine lhs rhs) Source #

Combination of records

Associated Types

type RecordRep (TCombine lhs rhs :: KRecord) :: * -> * Source #

data Record (TCombine lhs rhs :: KRecord) :: * Source #

Methods

toRecord :: RecordRep (TCombine lhs rhs) x -> Record (TCombine lhs rhs) Source #

fromRecord :: Record (TCombine lhs rhs) -> RecordRep (TCombine lhs rhs) x Source #

GRecord (TSingle meta typ) Source #

Single record

Associated Types

type RecordRep (TSingle meta typ :: KRecord) :: * -> * Source #

data Record (TSingle meta typ :: KRecord) :: * Source #

Methods

toRecord :: RecordRep (TSingle meta typ) x -> Record (TSingle meta typ) Source #

fromRecord :: Record (TSingle meta typ) -> RecordRep (TSingle meta typ) x Source #

class GFlatSum enum where Source #

Mappings between a Generic representation and our KFlatSum-based representation

Minimal complete definition

toFlatSum, fromFlatSum

Associated Types

type FlatSumRep enum :: * -> * Source #

Generic representation

data FlatSum enum Source #

KFlatSum-based representation

Methods

toFlatSum :: FlatSumRep enum x -> FlatSum enum Source #

From Generic representation

fromFlatSum :: FlatSum enum -> FlatSumRep enum x Source #

To Generic representation

Instances

GFlatSum (TValue meta) Source #

Single constructor

Associated Types

type FlatSumRep (TValue meta :: KFlatSum) :: * -> * Source #

data FlatSum (TValue meta :: KFlatSum) :: * Source #

Methods

toFlatSum :: FlatSumRep (TValue meta) x -> FlatSum (TValue meta) Source #

fromFlatSum :: FlatSum (TValue meta) -> FlatSumRep (TValue meta) x Source #

(GFlatSum lhs, GFlatSum rhs) => GFlatSum (TChoose lhs rhs) Source #

Combination of multiple constructors

Associated Types

type FlatSumRep (TChoose lhs rhs :: KFlatSum) :: * -> * Source #

data FlatSum (TChoose lhs rhs :: KFlatSum) :: * Source #

Methods

toFlatSum :: FlatSumRep (TChoose lhs rhs) x -> FlatSum (TChoose lhs rhs) Source #

fromFlatSum :: FlatSum (TChoose lhs rhs) -> FlatSumRep (TChoose lhs rhs) x Source #

class GDataType dat where Source #

Mappings between a Generic representation and our KDataType-based representation

Minimal complete definition

toDataType, fromDataType

Associated Types

type DataTypeRep dat :: * -> * Source #

Generic representation

data DataType dat Source #

KDataType-based representation

Methods

toDataType :: DataTypeRep dat x -> DataType dat Source #

From Generic representation

fromDataType :: DataType dat -> DataTypeRep dat x Source #

To Generic representation

Instances

GFlatSum enum => GDataType (TFlatSum d enum) Source #

With multiple constructors

Associated Types

type DataTypeRep (TFlatSum d enum :: KDataType) :: * -> * Source #

data DataType (TFlatSum d enum :: KDataType) :: * Source #

Methods

toDataType :: DataTypeRep (TFlatSum d enum) x -> DataType (TFlatSum d enum) Source #

fromDataType :: DataType (TFlatSum d enum) -> DataTypeRep (TFlatSum d enum) x Source #

GRecord rec => GDataType (TRecord d c rec) Source #

With single constructor

Associated Types

type DataTypeRep (TRecord d c rec :: KDataType) :: * -> * Source #

data DataType (TRecord d c rec :: KDataType) :: * Source #

Methods

toDataType :: DataTypeRep (TRecord d c rec) x -> DataType (TRecord d c rec) Source #

fromDataType :: DataType (TRecord d c rec) -> DataTypeRep (TRecord d c rec) x Source #

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.

Equations

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.

Equations

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.

Equations

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)