Portability | portable |
---|---|
Stability | experimental |
Maintainer | Drew Day <drewday@gmail.com> |
Safe Haskell | Safe-Infered |
A
Contents
Description
Code adapted from: http://web.engr.oregonstate.edu/~erwig/meta/
Documentation (and further updates in technique) forthcoming.
- class IIFunctor f where
- data Id a = Id a
- fromId :: (a -> b) -> Id a -> b
- toId :: (b -> a) -> b -> Id a
- fromU :: t -> (a -> t) -> I a -> t
- fromB :: t -> (a -> b -> t) -> II a b -> t
- fromT :: t -> (a -> b -> b -> t) -> IIV a b -> t
- fromP :: t -> (a -> [b] -> t) -> Power a b -> t
- toU :: (t -> Bool) -> (t -> a) -> t -> I a
- toB :: (t -> Bool) -> (t -> a) -> (t -> b) -> t -> II a b
- toT :: (t -> Bool) -> (t -> a) -> (t -> b) -> (t -> b) -> t -> IIV a b
- toP :: (t -> Bool) -> (t -> a) -> (t -> [b]) -> t -> Power a b
- toP' :: (t -> Bool) -> (t -> (a, [b])) -> t -> Power a b
- toB' :: (t -> Bool) -> (t -> (a, b)) -> t -> II a b
- data I a
- data II a b
- data IIV a b
- data Power a b
- ntBU :: (a -> b -> c) -> II a b -> I c
- ntTB :: (a -> c) -> (b -> b -> d) -> IIV a b -> II c d
- ntPB :: (a -> c) -> ([b] -> d) -> Power a b -> II c d
- data A s g t = A (s -> t) (t -> g t)
- con :: A t t1 t2 -> t -> t2
- des :: A t t1 t2 -> t2 -> t1 t2
- type BinA a t = SymA (II a) t
- type PowA a t = SymA (Power a) t
- type SymA g t = A (g t) g t
- type JoinA a g = A (II [a] (g a)) (II a) (g a)
- joinView :: Functor g => A (II a t) g t -> A (II [a] t) g t
- maybeView :: Functor g => A (II a t) g t -> A (II (Maybe a) t) g t
- fold :: Functor g => (g u -> u) -> A s g t -> t -> u
- unfold :: (Functor f, Functor g) => (t -> f t) -> A (f u) g u -> t -> u
- trans :: (Functor g, Functor h) => (g u -> r) -> A s g t -> A r h u -> t -> u
- transit :: (Functor g, Functor h) => A s g t -> A (g u) h u -> t -> u
- via :: (Functor g, Functor h, Functor i) => A s g t -> A (g u) h u -> A (h v) i v -> t -> v
- hylo :: Functor f => (f b -> b) -> (a -> f a) -> a -> b
- hylot :: Functor f => (f b -> g b) -> (g b -> b) -> (a -> f a) -> a -> b
- hhh :: Functor f => (f b -> i b) -> (i b -> g b) -> (g b -> b) -> (a -> f a) -> a -> b
- h :: Functor f => (f b -> i b) -> (i b -> j b) -> (j b -> k b) -> (k b -> b) -> (a -> f a) -> a -> b
- stream :: Functor g => [SymA g t] -> t -> t
Documentation
A standard Bifunctor, but with a Roman Numeral naming scheme:
- II
- instead of
Bi
- fmapII
- instead of
bimap
- fmapLI
- instead of
first
- fmapIR
- instead of
second
This is to remind us that the other column remains intact when focus on one (L or R).
joinView :: Functor g => A (II a t) g t -> A (II [a] t) g tSource
Equip an A having linear constructor with a join view
Fold and Unfold
hylo :: Functor f => (f b -> b) -> (a -> f a) -> a -> bSource
Hylomorphisms in binary and triplet form (just for completeness)