multirec-0.2: Generic programming with systems of recursive datatypesSource codeContentsIndex
Generics.MultiRec.FoldK
Portabilitynon-portable
Stabilityexperimental
Maintainergenerics@haskell.org
Contents
Generic fold and unfold
Creating an algebra
Description
Variant of Generics.MultiRec.Fold where the result type is independent of the index.
Synopsis
type Algebra' s f r = forall ix. Ix s ix => s ix -> f s (K0 r) ix -> r
type Algebra s r = Algebra' s (PF s) r
type AlgebraF' s f g r = forall ix. Ix s ix => s ix -> f s (K0 r) ix -> g r
type AlgebraF s g r = AlgebraF' s (PF s) g r
fold :: (Ix s ix, HFunctor (PF s)) => Algebra s r -> ix -> r
foldM :: (Ix s ix, HFunctor (PF s), Monad m) => AlgebraF s m r -> ix -> m r
type CoAlgebra' s f r = forall ix. Ix s ix => s ix -> r -> f s (K0 r) ix
type CoAlgebra s r = CoAlgebra' s (PF s) r
type CoAlgebraF' s f g r = forall ix. Ix s ix => s ix -> r -> g (f s (K0 r) ix)
type CoAlgebraF s g r = CoAlgebraF' s (PF s) g r
unfold :: (Ix s ix, HFunctor (PF s)) => CoAlgebra s r -> r -> ix
unfoldM :: (Ix s ix, HFunctor (PF s), Monad m) => CoAlgebraF s m r -> r -> m ix
type ParaAlgebra' s f r = forall ix. Ix s ix => s ix -> f s (K0 r) ix -> ix -> r
type ParaAlgebra s r = ParaAlgebra' s (PF s) r
type ParaAlgebraF' s f g r = forall ix. Ix s ix => s ix -> f s (K0 r) ix -> ix -> g r
type ParaAlgebraF s g r = ParaAlgebraF' s (PF s) g r
para :: (Ix s ix, HFunctor (PF s)) => ParaAlgebra s r -> ix -> r
paraM :: (Ix s ix, HFunctor (PF s), Monad m) => ParaAlgebraF s m r -> ix -> m r
type AlgPart a s b ix = a s (K0 b) ix -> b
type :-> f g s b ix = f s b ix -> g s b ix
(&) :: (AlgPart a :-> (AlgPart b :-> AlgPart (a :+: b))) s c ix
tag :: AlgPart a s c ix -> AlgPart (a :>: ix) s c ix'
con :: AlgPart a s b ix -> AlgPart (C c a) s b ix
Generic fold and unfold
type Algebra' s f r = forall ix. Ix s ix => s ix -> f s (K0 r) ix -> rSource
type Algebra s r = Algebra' s (PF s) rSource
type AlgebraF' s f g r = forall ix. Ix s ix => s ix -> f s (K0 r) ix -> g rSource
type AlgebraF s g r = AlgebraF' s (PF s) g rSource
fold :: (Ix s ix, HFunctor (PF s)) => Algebra s r -> ix -> rSource
foldM :: (Ix s ix, HFunctor (PF s), Monad m) => AlgebraF s m r -> ix -> m rSource
type CoAlgebra' s f r = forall ix. Ix s ix => s ix -> r -> f s (K0 r) ixSource
type CoAlgebra s r = CoAlgebra' s (PF s) rSource
type CoAlgebraF' s f g r = forall ix. Ix s ix => s ix -> r -> g (f s (K0 r) ix)Source
type CoAlgebraF s g r = CoAlgebraF' s (PF s) g rSource
unfold :: (Ix s ix, HFunctor (PF s)) => CoAlgebra s r -> r -> ixSource
unfoldM :: (Ix s ix, HFunctor (PF s), Monad m) => CoAlgebraF s m r -> r -> m ixSource
type ParaAlgebra' s f r = forall ix. Ix s ix => s ix -> f s (K0 r) ix -> ix -> rSource
type ParaAlgebra s r = ParaAlgebra' s (PF s) rSource
type ParaAlgebraF' s f g r = forall ix. Ix s ix => s ix -> f s (K0 r) ix -> ix -> g rSource
type ParaAlgebraF s g r = ParaAlgebraF' s (PF s) g rSource
para :: (Ix s ix, HFunctor (PF s)) => ParaAlgebra s r -> ix -> rSource
paraM :: (Ix s ix, HFunctor (PF s), Monad m) => ParaAlgebraF s m r -> ix -> m rSource
Creating an algebra
type AlgPart a s b ix = a s (K0 b) ix -> bSource
type :-> f g s b ix = f s b ix -> g s b ixSource
(&) :: (AlgPart a :-> (AlgPart b :-> AlgPart (a :+: b))) s c ixSource
tag :: AlgPart a s c ix -> AlgPart (a :>: ix) s c ix'Source
con :: AlgPart a s b ix -> AlgPart (C c a) s b ixSource
Produced by Haddock version 2.4.2