multirec-0.7.1: Generic programming for families of recursive datatypes

Portabilitynon-portable
Stabilityexperimental
Maintainergenerics@haskell.org

Generics.MultiRec.Fold

Contents

Description

The definition of generic fold, unfold, paramorphisms. In addition, some combinators that facilitate the construction of algebras.

There are several variants of fold in other modules that are probably easier to use:

Synopsis

Generic fold and unfold

type Algebra' phi f r = forall ix. phi ix -> f r ix -> r ixSource

type Algebra phi r = Algebra' phi (PF phi) rSource

type AlgebraF' phi f g r = forall ix. phi ix -> f r ix -> g (r ix)Source

type AlgebraF phi g r = AlgebraF' phi (PF phi) g rSource

fold :: (Fam phi, HFunctor phi (PF phi)) => Algebra phi r -> phi ix -> ix -> r ixSource

foldM :: (Fam phi, HFunctor phi (PF phi), Monad m) => AlgebraF phi m r -> phi ix -> ix -> m (r ix)Source

type CoAlgebra' phi f r = forall ix. phi ix -> r ix -> f r ixSource

type CoAlgebra phi r = CoAlgebra' phi (PF phi) rSource

type CoAlgebraF' phi f g r = forall ix. phi ix -> r ix -> g (f r ix)Source

type CoAlgebraF phi g r = CoAlgebraF' phi (PF phi) g rSource

unfold :: (Fam phi, HFunctor phi (PF phi)) => CoAlgebra phi r -> phi ix -> r ix -> ixSource

unfoldM :: (Fam phi, HFunctor phi (PF phi), Monad m) => CoAlgebraF phi m r -> phi ix -> r ix -> m ixSource

type ParaAlgebra' phi f r = forall ix. phi ix -> f r ix -> ix -> r ixSource

type ParaAlgebra phi r = ParaAlgebra' phi (PF phi) rSource

type ParaAlgebraF' phi f g r = forall ix. phi ix -> f r ix -> ix -> g (r ix)Source

type ParaAlgebraF phi g r = ParaAlgebraF' phi (PF phi) g rSource

para :: (Fam phi, HFunctor phi (PF phi)) => ParaAlgebra phi r -> phi ix -> ix -> r ixSource

paraM :: (Fam phi, HFunctor phi (PF phi), Monad m) => ParaAlgebraF phi m r -> phi ix -> ix -> m (r ix)Source

Creating an algebra

type AlgPart f r ix = f r ix -> r ixSource

type :-> f g r ix = f r ix -> g r ixSource

(&) :: (AlgPart a :-> (AlgPart b :-> AlgPart (a :+: b))) r ixSource

tag :: AlgPart a r ix -> AlgPart (a :>: ix) r ix'Source

con :: AlgPart a r ix -> AlgPart (C c a) r ixSource