Safe Haskell | Safe |
---|---|
Language | Haskell98 |
Fix-point type. It allows to define generic recurion schemes.
Fix f = f (Fix f)
Type f
should be a Functor
if you want to use
simple recursion schemes or Traversable
if you want to
use monadic recursion schemes. This style allows you to express
recursive functions in non-recursive manner.
You can imagine that a non-recursive function
holds values of the previous iteration.
Little example:
type List a = Fix (L a) data L a b = Nil | Cons a b instance Functor (L a) where fmap f x = case x of Nil -> Nil Cons a b -> Cons a (f b) length :: List a -> Int length = cata $ \x -> case x of Nil -> 0 Cons _ n -> n + 1 sum :: Num a => List a -> a sum = cata $ \x -> case x of Nil -> 0 Cons a s -> a + s
- newtype Fix f = Fix {}
- cata :: Functor f => (f a -> a) -> Fix f -> a
- ana :: Functor f => (a -> f a) -> a -> Fix f
- hylo :: Functor f => (f b -> b) -> (a -> f a) -> a -> b
- (~>) :: Functor f => (a -> f a) -> (f b -> b) -> a -> b
- cataM :: (Applicative m, Monad m, Traversable t) => (t a -> m a) -> Fix t -> m a
- anaM :: (Applicative m, Monad m, Traversable t) => (a -> m (t a)) -> a -> m (Fix t)
- hyloM :: (Applicative m, Monad m, Traversable t) => (t b -> m b) -> (a -> m (t a)) -> a -> m b
Documentation
A fix-point type.
Simple recursion
Type f
should be a Functor
. They transform
non-recursive functions to recursive ones.
hylo :: Functor f => (f b -> b) -> (a -> f a) -> a -> b Source
Hylomorphism is anamorphism followed by catamorphism.
Monadic recursion
Type f
should be a Traversable
.
cataM :: (Applicative m, Monad m, Traversable t) => (t a -> m a) -> Fix t -> m a Source
Monadic catamorphism.
anaM :: (Applicative m, Monad m, Traversable t) => (a -> m (t a)) -> a -> m (Fix t) Source
Monadic anamorphism.
hyloM :: (Applicative m, Monad m, Traversable t) => (t b -> m b) -> (a -> m (t a)) -> a -> m b Source
Monadic hylomorphism.