multistate-0.7.1.2: like mtl's ReaderT / WriterT / StateT, but more than one contained value/type.

Safe HaskellSafe
LanguageHaskell2010

Data.HList.HList

Description

A GADT HList implementation

Probably exists somewhere else already, but why add a dependency for something so simple.

Documentation

data HList :: [*] -> * where Source #

Constructors

HNil :: HList '[] 
(:+:) :: x -> HList xs -> HList (x ': xs) infixr 5 

Instances

(Eq x, Eq (HList xs)) => Eq (HList ((:) * x xs)) Source # 

Methods

(==) :: HList ((* ': x) xs) -> HList ((* ': x) xs) -> Bool #

(/=) :: HList ((* ': x) xs) -> HList ((* ': x) xs) -> Bool #

Eq (HList ([] *)) Source # 

Methods

(==) :: HList [*] -> HList [*] -> Bool #

(/=) :: HList [*] -> HList [*] -> Bool #

(Show a, Show (HList b)) => Show (HList ((:) * a b)) Source # 

Methods

showsPrec :: Int -> HList ((* ': a) b) -> ShowS #

show :: HList ((* ': a) b) -> String #

showList :: [HList ((* ': a) b)] -> ShowS #

Show (HList ([] *)) Source # 

Methods

showsPrec :: Int -> HList [*] -> ShowS #

show :: HList [*] -> String #

showList :: [HList [*]] -> ShowS #

(Monoid x, Monoid (HList xs)) => Monoid (HList ((:) * x xs)) Source # 

Methods

mempty :: HList ((* ': x) xs) #

mappend :: HList ((* ': x) xs) -> HList ((* ': x) xs) -> HList ((* ': x) xs) #

mconcat :: [HList ((* ': x) xs)] -> HList ((* ': x) xs) #

Monoid (HList ([] *)) Source # 

Methods

mempty :: HList [*] #

mappend :: HList [*] -> HList [*] -> HList [*] #

mconcat :: [HList [*]] -> HList [*] #

type family Append (l1 :: [*]) (l2 :: [*]) :: [*] Source #

Instances

type Append ([] *) l2 Source # 
type Append ([] *) l2 = l2
type Append ((:) * car1 cdr2) l2 Source # 
type Append ((:) * car1 cdr2) l2 = (:) * car1 (Append cdr2 l2)

hAppend :: HList ts1 -> HList ts2 -> HList (Append ts1 ts2) Source #

class HInit l1 where Source #

Minimal complete definition

hInit, hSplit

Methods

hInit :: forall l2. Proxy l2 -> HList (Append l1 l2) -> HList l1 Source #

hSplit :: forall l2. HList (Append l1 l2) -> (HList l1, HList l2) Source #

Instances

HInit ([] *) Source # 

Methods

hInit :: Proxy [*] l2 -> HList (Append [*] l2) -> HList [*] Source #

hSplit :: HList (Append [*] l2) -> (HList [*], HList l2) Source #

HInit l1 => HInit ((:) * x l1) Source # 

Methods

hInit :: Proxy [*] l2 -> HList (Append ((* ': x) l1) l2) -> HList ((* ': x) l1) Source #

hSplit :: HList (Append ((* ': x) l1) l2) -> (HList ((* ': x) l1), HList l2) Source #