effect-monad-0.8.1.0: Embeds effect systems and program logics into Haskell using graded monads and parameterised monads

Safe HaskellSafe
LanguageHaskell98

Control.Effect.Helpers.List

Documentation

data List (l :: [*]) where Source #

Constructors

Nil :: List '[] 
Cons :: x -> List xs -> List (x ': xs) 

type family (s :: [*]) :++ (t :: [*]) :: [*] where ... Source #

Equations

'[] :++ ys = ys 
(x ': xs) :++ ys = x ': (xs :++ ys) 

append :: List s -> List t -> List (s :++ t) Source #

class Split (s :: [*]) (t :: [*]) where Source #

Minimal complete definition

split

Methods

split :: List (s :++ t) -> (List s, List t) Source #

Instances

Split ([] *) xs Source # 

Methods

split :: List ([*] :++ xs) -> (List [*], List xs) Source #

Split xs ys => Split ((:) * x xs) ys Source # 

Methods

split :: List ((* ': x) xs :++ ys) -> (List ((* ': x) xs), List ys) Source #

type family LookupT k xs where ... Source #

Equations

LookupT k '[] = Maybe () 
LookupT k ((k, x) ': xs) = Maybe x 
LookupT k ((j, x) ': xs) = LookupT k xs 

class LookUpA k xs (LookupT k xs) => Lookup k xs where Source #

Methods

lookup :: List xs -> Proxy k -> Maybe (LookupT k xs) Source #

class LookUpA k xs x where Source #

Minimal complete definition

lookupA

Methods

lookupA :: List xs -> Proxy k -> Maybe x Source #

Instances

LookUpA k1 k2 xs y => LookUpA k1 k2 ((:) * (j, x) xs) y Source # 

Methods

lookupA :: List y -> Proxy k2 ((* ': (j, x)) xs) -> Maybe x Source #

LookUpA * k ((:) * (k, x) xs) x Source # 

Methods

lookupA :: List x -> Proxy k ((* ': (k, x)) xs) -> Maybe x Source #