HList-0.4.0.0: Heterogeneous lists

Safe HaskellNone
LanguageHaskell2010

Data.HList.Data

Contents

Description

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.

Synopsis

exports for type signatures/ haddock usage

type DataHListFlatCxt na g 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

class TypeRepsList a where Source

Methods

typeRepsList :: a -> [TypeRep] Source

Instances

(TypeRepsList (HList xs), Typeable * x) => TypeRepsList (HList ((:) * x xs)) 
TypeRepsList (HList ([] *)) 
TypeRepsList (HList xs) => TypeRepsList (Record xs) 

less likely to be used

class RecordLabelsStr xs where Source

Instances

RecordLabelsStr ([] *) 
(RecordLabelsStr xs, ShowLabel k x) => RecordLabelsStr ((:) * (Tagged k x t) xs) 

data GfoldlK c where Source

wraps up the first argument to gfoldl

Constructors

GfoldlK :: (forall d b. Data d => c (d -> b) -> d -> c b) -> GfoldlK c 

Instances

(Data d, (~) * (c (d -> b), d) x, (~) * (c b) y) => ApplyAB (GfoldlK c) x y 

data GunfoldK c where Source

Constructors

GunfoldK :: (forall b r. Data b => c (b -> r) -> c r) -> GunfoldK c 

Instances

(Data b, (~) * x (t, c (b -> r)), (~) * y (c r)) => ApplyAB (GunfoldK c) x y 

newtype HListFlat a Source

this data type only exists to have Data instance

Constructors

HListFlat (HList a) 

Instances

DataHListFlatCxt na g a => Data (HListFlat a) 
Typeable ([*] -> *) HListFlat