| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Generics.SOP.Record
Synopsis
- type FieldLabel = Symbol
- type RecordCode = [(FieldLabel, Type)]
- type Record (r :: RecordCode) = NP P r
- type RecordRep (a :: Type) = Record (RecordCodeOf a)
- type RecordCodeOf a = ToRecordCode_Datatype a (DatatypeInfoOf a) (Code a)
- type IsRecord (a :: Type) (r :: RecordCode) = IsRecord' a r (GetSingleton (Code a))
- type ValidRecordCode (r :: RecordCode) (xs :: [Type]) = (ExtractTypesFromRecordCode r ~ xs, RecombineRecordCode (ExtractLabelsFromRecordCode r) xs ~ r)
- type family ExtractTypesFromRecordCode (r :: RecordCode) :: [Type] where ...
- type family ExtractLabelsFromRecordCode (r :: RecordCode) :: [FieldLabel] where ...
- type family RecombineRecordCode (ls :: [FieldLabel]) (ts :: [Type]) :: RecordCode where ...
- toRecord :: IsRecord a _r => a -> RecordRep a
- fromRecord :: IsRecord a r => RecordRep a -> a
- newtype P (p :: (a, Type)) = P (Snd p)
- type family Snd (p :: (a, b)) :: b where ...
A suitable representation for single-constructor records
type FieldLabel = Symbol Source #
On the type-level, we represent fiel labels using symbols.
type RecordCode = [(FieldLabel, Type)] Source #
The record code deviates from the normal SOP code in two ways:
- There is only one list, because we require that there is only a single constructor.
- In addition to the types of the fields, we store the labels of the fields.
type Record (r :: RecordCode) = NP P r Source #
The representation of a record is just a product indexed by a record code, containing elements of the types indicated by the code.
Note that the representation is deliberately chosen such that it has the same run-time representation as the product part of the normal SOP representation.
type RecordRep (a :: Type) = Record (RecordCodeOf a) Source #
The record representation of a type is a record indexed by the record code.
Computing the record code
type RecordCodeOf a = ToRecordCode_Datatype a (DatatypeInfoOf a) (Code a) Source #
This type-level function takes the type-level metadata provided by generics-sop as well as the normal generics-sop code, and transforms them into the record code.
Arguably, the record code is more usable than the representation directly on offer by generics-sop. So it's worth asking whether this representation should be included in generics-sop ...
The function will only reduce if the argument type actually is a record, meaning it must have exactly one constructor, and that constructor must have field labels attached to it.
type IsRecord (a :: Type) (r :: RecordCode) = IsRecord' a r (GetSingleton (Code a)) Source #
The constraint IsRecord a r states that the type a is a record type
 (i.e., has exactly one constructor and field labels) and that r is the
 record code associated with a.
type ValidRecordCode (r :: RecordCode) (xs :: [Type]) = (ExtractTypesFromRecordCode r ~ xs, RecombineRecordCode (ExtractLabelsFromRecordCode r) xs ~ r) Source #
Relates a recordcode r and a list of types xs, stating that
 xs is indeed the list of types contained in r.
type family ExtractTypesFromRecordCode (r :: RecordCode) :: [Type] where ... Source #
Extracts all the types from a record code.
Equations
| ExtractTypesFromRecordCode '[] = '[] | |
| ExtractTypesFromRecordCode ('(_, a) ': r) = a ': ExtractTypesFromRecordCode r | 
type family ExtractLabelsFromRecordCode (r :: RecordCode) :: [FieldLabel] where ... Source #
Extracts all the field labels from a record code.
Equations
| ExtractLabelsFromRecordCode '[] = '[] | |
| ExtractLabelsFromRecordCode ('(l, _) ': r) = l ': ExtractLabelsFromRecordCode r | 
type family RecombineRecordCode (ls :: [FieldLabel]) (ts :: [Type]) :: RecordCode where ... Source #
Given a list of labels and types, recombines them into a record code.
An important aspect of this function is that it is defined by induction on the list of types, and forces the list of field labels to be at least as long.
Equations
| RecombineRecordCode _ '[] = '[] | |
| RecombineRecordCode ls (t ': ts) = '(Head ls, t) ': RecombineRecordCode (Tail ls) ts | 
Conversion between a type and its record representation.
toRecord :: IsRecord a _r => a -> RecordRep a Source #
Convert a value into its record representation.
fromRecord :: IsRecord a r => RecordRep a -> a Source #
Convert a record representation back into a value.
Utilities
newtype P (p :: (a, Type)) Source #
Projection of the second component of a type-level pair, wrapped in a newtype.
Instances
| Eq a2 => Eq (P '(l, a2)) Source # | |
| Ord a2 => Ord (P '(l, a2)) Source # | |
| Defined in Generics.SOP.Record | |
| Show a2 => Show (P '(l, a2)) Source # | |
| Generic (P p) Source # | |
| NFData a2 => NFData (P '(l, a2)) Source # | |
| Defined in Generics.SOP.Record | |
| type Rep (P p) Source # | |
| Defined in Generics.SOP.Record | |