Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data
instances for HListFlat
and Record
which pretend
to be flat data structures. The Data
instance for HList
gives a nested
structure.
NOTE: these instances do not work with ghc-7.8 with promoted string (Symbol) labels because of https://ghc.haskell.org/trac/ghc/ticket/9111
HList
The data instance for
a :: HList '[Int, Double, b]
Looks like the same instance for
type T b = (Int, (Double, (b, ())))
HListFlat
The Data instance for
a :: Data b => HListFlat '[Int,Double,b]
will look like the Data instance for:
data A b = A Int Double b
Record
For Record
similar ideas apply. An
a :: Record '[ LVPair "x" Int, LVPair "y" Double ]
should behave like a:
data A = A { x :: Int, y :: Double } deriving (Data)
Many unsafecoerces are necessary here because the Data class includes type
parameters c
that cannot be used in the class context for the instance.
Perhaps there is another way.
- type DataHListFlatCxt na g a = (g ~ FoldRArrow a (HList a), HBuild' '[] g, Typeable (HListFlat a), TypeablePolyK a, HFoldl (GfoldlK C) (C g) a (C (HList a)), HFoldr (GunfoldK C) (C g) (HReplicateR na ()) (C (HList a)), HLengthEq a na, HReplicate na ())
- type DataRecordCxt a = (Data (HListFlat (RecordValuesR a)), TypeablePolyK a, TypeRepsList (Record a), RecordValues a, RecordLabelsStr a)
- class TypeRepsList a where
- class RecordLabelsStr (xs :: [*]) where
- data GfoldlK c where
- data GunfoldK c where
- newtype HListFlat a = HListFlat (HList a)
- type TypeablePolyK (a :: k) = Typeable a
exports for type signatures/ haddock usage
type DataHListFlatCxt na g a = (g ~ FoldRArrow a (HList a), HBuild' '[] g, Typeable (HListFlat a), TypeablePolyK a, HFoldl (GfoldlK C) (C g) a (C (HList a)), HFoldr (GunfoldK C) (C g) (HReplicateR na ()) (C (HList a)), HLengthEq a na, HReplicate na ()) Source #
type DataRecordCxt a = (Data (HListFlat (RecordValuesR a)), TypeablePolyK a, TypeRepsList (Record a), RecordValues a, RecordLabelsStr a) Source #
class TypeRepsList a where Source #
typeRepsList :: a -> [TypeRep] Source #
(TypeRepsList (HList xs), Typeable * x) => TypeRepsList (HList ((:) * x xs)) Source # | |
TypeRepsList (HList ([] *)) Source # | |
TypeRepsList (HList xs) => TypeRepsList (Record xs) Source # | |
less likely to be used
class RecordLabelsStr (xs :: [*]) where Source #
recordLabelsStr :: Record xs -> [String] Source #
RecordLabelsStr ([] *) Source # | |
(RecordLabelsStr xs, ShowLabel k x) => RecordLabelsStr ((:) * (Tagged k x t) xs) Source # | |
wraps up the first argument to gfoldl
this data type only exists to have Data instance
DataHListFlatCxt na g a => Data (HListFlat a) Source # | |
type TypeablePolyK (a :: k) = Typeable a Source #
Orphan instances
(Data x, Data (HList xs), TypeablePolyK [*] ((:) * x xs), Typeable * (HList ((:) * x xs))) => Data (HList ((:) * x xs)) Source # | |
Typeable * (HList ([] *)) => Data (HList ([] *)) Source # | |
DataRecordCxt a => Data (Record a) Source # | |
(TypeablePolyK [*] xs, Typeable * (HList xs), Data (HList xs)) => Data (TIP xs) Source # | |
(TypeablePolyK [*] xs, Typeable * (Variant xs), Data (Variant xs)) => Data (TIC xs) Source # | |