multistate-0.8.0.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

There exist other implementations of HList on hackage, but none seem to be reliably maintained.

Documentation

data HList :: [Type] -> Type 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 ([] Type)) Source # 

Methods

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

(/=) :: HList [Type] -> HList [Type] -> 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 ([] Type)) Source # 

Methods

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

show :: HList [Type] -> String #

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

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

Methods

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

sconcat :: NonEmpty (HList ((* ': x) xs)) -> HList ((* ': x) xs) #

stimes :: Integral b => b -> HList ((* ': x) xs) -> HList ((* ': x) xs) #

Semigroup (HList ([] Type)) Source # 

Methods

(<>) :: HList [Type] -> HList [Type] -> HList [Type] #

sconcat :: NonEmpty (HList [Type]) -> HList [Type] #

stimes :: Integral b => b -> HList [Type] -> HList [Type] #

(Semigroup x, Monoid x, Semigroup (HList xs), 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 ([] Type)) Source # 

Methods

mempty :: HList [Type] #

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

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

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

Instances

type Append ([] Type) l2 Source # 
type Append ([] Type) l2 = l2
type Append ((:) Type car1 cdr2) l2 Source # 
type Append ((:) Type car1 cdr2) l2 = (:) Type 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 ([] Type) Source # 

Methods

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

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

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

Methods

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

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