Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
- dicata :: Recursive a => (Base a (b, a) -> b) -> (Base a (b, a) -> a) -> a -> b
- dendro :: (SubHom (Base t) (Base t') a b, SubType b, Recursive t') => t -> (Base t a -> a) -> (Base t' b -> b) -> t' -> b
- dendroTri :: (SubHom (Base t) (Base t') a b, SubType b, Recursive t', SubHom (Base t'') (Base t) c a, SubType a, Recursive t) => t -> t'' -> (Base t'' c -> c) -> (Base t a -> a) -> (Base t' b -> b) -> t' -> b
- micro :: Corecursive a => (b -> Either a (Base a b)) -> b -> a
- symplecto :: (SubHom g f b b, CoSubHom g f a a) => (g b -> b) -> (a -> g a) -> (f b -> b) -> (a -> f a) -> a -> b
- chema :: (CoSubHom (Base t) (Base t') a b, SubType b, Corecursive t') => (a -> Base t a) -> (b -> Base t' b) -> b -> t'
- cataM :: (Recursive t, Traversable (Base t), Monad m) => (Base t a -> m a) -> t -> m a
- class (Functor f, Functor g) => SubHom f g a b where
- class SubType b where
- class (Functor f, Functor g) => CoSubHom f g a b where
- class Dummy t where
Documentation
dicata :: Recursive a => (Base a (b, a) -> b) -> (Base a (b, a) -> a) -> a -> b Source #
Catamorphism collapsing along two data types simultaneously. Basically a fancy zygomorphism.
:: (SubHom (Base t) (Base t') a b, SubType b, Recursive t') | |
=> t | dummy type |
-> (Base t a -> a) | A (Base t)-algebra |
-> (Base t' b -> b) | A (Base t')-algebra |
-> t' | |
-> b |
A dendromorphism allows us to entangle two catamorphisms
:: (SubHom (Base t) (Base t') a b, SubType b, Recursive t', SubHom (Base t'') (Base t) c a, SubType a, Recursive t) | |
=> t | dummy type |
-> t'' | another dummy type |
-> (Base t'' c -> c) | A (Base t'')-algebra |
-> (Base t a -> a) | |
-> (Base t' b -> b) | |
-> t' | |
-> b |
Entangle three base functors.
micro :: Corecursive a => (b -> Either a (Base a b)) -> b -> a Source #
A micromorphism is an Elgot algebra specialized to unfolding.
:: (SubHom g f b b, CoSubHom g f a a) | |
=> (g b -> b) | A g-algebra |
-> (a -> g a) | A g-coalgebra |
-> (f b -> b) | An f-algebra |
-> (a -> f a) | An f-coalgebra |
-> a | |
-> b |
Entangle two hylomorphisms. Not the same thing as a symplectomorphism from geometry.
chema :: (CoSubHom (Base t) (Base t') a b, SubType b, Corecursive t') => (a -> Base t a) -> (b -> Base t' b) -> b -> t' Source #
class (Functor f, Functor g) => SubHom f g a b where Source #
Class that yields g-algebra homomorphisms between mutually recursive types.