monadic-recursion-schemes-0.1.13.2: Recursion Schemes for Monadic version.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Functor.Foldable.Monadic

Synopsis

Folding

cataM Source #

Arguments

:: (Monad m, Traversable (Base t), Recursive t) 
=> (Base t a -> m a)

algebra

-> t 
-> m a 

catamorphism

preproM Source #

Arguments

:: (Monad m, Traversable (Base t), Recursive t, Corecursive t) 
=> (Base t t -> m (Base t t))

monadic natural transformation

-> (Base t a -> m a)

algebra

-> t 
-> m a 

prepromorphism

paraM Source #

Arguments

:: (Monad m, Traversable (Base t), Recursive t) 
=> (Base t (t, a) -> m a)

algebra

-> t 
-> m a 

paramorphism

zygoM Source #

Arguments

:: (Monad m, Traversable (Base t), Recursive t) 
=> (Base t a -> m a)

algebra for fst

-> (Base t (a, b) -> m b)

algebra for snd from product

-> t 
-> m b 

zygomorphism

histoM Source #

Arguments

:: (Monad m, Traversable (Base t), Recursive t) 
=> (Base t (Cofree (Base t) a) -> m a)

algebra

-> t 
-> m a 

histomorphism on anamorphism variant

histoM' Source #

Arguments

:: (Monad m, Traversable (Base t), Recursive t) 
=> (Base t (Cofree (Base t) a) -> m a)

algebra

-> t 
-> m a 

histomorphism on catamorphism variant

dynaM Source #

Arguments

:: (Monad m, Traversable (Base t), Recursive t, Corecursive t) 
=> (Base t (Cofree (Base t) b) -> m b)

algebra

-> (a -> m (Base t a))

coalgebra

-> a 
-> m b 

dynamorphism on recursive variant over chronomorphism

dynaM' Source #

Arguments

:: forall m t a c. (Monad m, Traversable (Base t), Recursive t, Corecursive t) 
=> (Base t (Cofree (Base t) c) -> m c)

algebra

-> (a -> m (Base t a))

coalgebra

-> a 
-> m c 

dynamorphism on combination variant of ana to histo

dynaM'' Source #

Arguments

:: (Monad m, Traversable t) 
=> (t (Cofree t c) -> m c)

algebra

-> (a -> m (t a))

coalgebra

-> a 
-> m c 

dynamorphism on recursive variant over hylomorphism

Unfolding

anaM Source #

Arguments

:: (Monad m, Traversable (Base t), Corecursive t) 
=> (a -> m (Base t a))

coalgebra

-> a 
-> m t 

anamorphism

postproM Source #

Arguments

:: (Monad m, Traversable (Base t), Recursive t, Corecursive t) 
=> (Base t t -> m (Base t t))

monadic natural transformation

-> (a -> m (Base t a))

coalgebra

-> a 
-> m t 

postpromorphism

apoM Source #

Arguments

:: (Monad m, Traversable (Base t), Corecursive t) 
=> (a -> m (Base t (Either t a)))

coalgebra

-> a 
-> m t 

apomorphism

cozygoM Source #

Arguments

:: (Monad m, Traversable (Base t), Corecursive t) 
=> (a -> m (Base t a))

coalgebra for fst

-> (b -> m (Base t (Either a b)))

coalgebra for snd to coproduct

-> b 
-> m t 

cozygomorphism

futuM Source #

Arguments

:: (Monad m, Traversable (Base t), Corecursive t) 
=> (a -> m (Base t (Free (Base t) a)))

coalgebra

-> a 
-> m t 

futumorphism on catamorphism variant

futuM' Source #

Arguments

:: (Monad m, Traversable (Base t), Corecursive t) 
=> (a -> m (Base t (Free (Base t) a)))

coalgebra

-> a 
-> m t 

futumorphism on anamorphism variant

codynaM Source #

Arguments

:: (Monad m, Traversable t) 
=> (t b -> m b)

algebra

-> (a -> m (t (Free t a)))

coalgebra

-> a 
-> m b 

codynamorphism on recursive variant over chronomorphism

codynaM' Source #

Arguments

:: (Monad m, Corecursive c, Traversable (Base c), Traversable (Base t), Recursive t) 
=> (Base t (Cofree (Base t) a) -> m a)

algebra

-> (a -> m (Base c a))

coalgebra

-> t 
-> m c 

codynamorphism on combination variant of histo to ana

codynaM'' Source #

Arguments

:: (Monad m, Traversable t) 
=> (t b -> m b)

algebra

-> (a -> m (t (Free t a)))

coalgebra

-> a 
-> m b 

codynamorphism on recursive variant over hylomorphism

Refolding

hyloM Source #

Arguments

:: (Monad m, Traversable t) 
=> (t b -> m b)

algebra

-> (a -> m (t a))

coalgebra

-> a 
-> m b 

hylomorphism on recursive variant

metaM Source #

Arguments

:: (Monad m, Traversable (Base t), Recursive s, Corecursive t, Base s ~ Base t) 
=> (Base t t -> m t)

algebra

-> (s -> m (Base s s))

coalgebra

-> s 
-> m t 

metamorphism on recursive variant

hyloM' Source #

Arguments

:: forall m t a b. (Monad m, Traversable (Base t), Recursive t, Corecursive t) 
=> (Base t b -> m b)

algebra

-> (a -> m (Base t a))

coalgebra

-> a 
-> m b 

hylomorphism on combination variant of ana to cata

metaM' Source #

Arguments

:: (Monad m, Corecursive c, Traversable (Base c), Traversable (Base t), Recursive t) 
=> (Base t a -> m a)

algebra

-> (a -> m (Base c a))

coalgebra

-> t 
-> m c 

metamorphism on combination variant of cata to ana

chronoM Source #

Arguments

:: forall m t a b. (Monad m, Traversable (Base t), Recursive t, Corecursive t) 
=> (Base t (Cofree (Base t) b) -> m b)

algebra

-> (a -> m (Base t (Free (Base t) a)))

coalgebra

-> a 
-> m b 

chronomorphism on combination variant of futu to hist

cochronoM Source #

Arguments

:: (Monad m, Corecursive c, Traversable (Base c), Traversable (Base t), Recursive t) 
=> (Base t (Cofree (Base t) a) -> m a)

algebra

-> (a -> m (Base c (Free (Base c) a)))

coalgebra

-> t 
-> m c 

cochronomorphism on combination variant of histo to futu

chronoM' Source #

Arguments

:: (Monad m, Traversable t) 
=> (t (Cofree t b) -> m b)

algebra

-> (a -> m (t (Free t a)))

coalgebra

-> a 
-> m b 

chronomorphism on recursive variant over hylomorphism

Generalized Folding

gcataM Source #

Arguments

:: (Monad m, Comonad w, Traversable w, Traversable (Base t), Recursive t, b ~ w a) 
=> (Base t (w b) -> m (w (Base t b)))

Distributive (Base t) w b

-> (Base t (w a) -> m a)

algebra

-> t 
-> m a 

generalized catamorphism

gcataM' Source #

Arguments

:: (Monad m, Comonad w, Traversable w, Traversable (Base t), Recursive t, b ~ w a) 
=> (Base t (w b) -> m (w (Base t b)))

Distributive (Base t) w b

-> (Base t (w a) -> m a)

algebra

-> t 
-> m a 

generalized catamorphism variant

Others

mutuM Source #

Arguments

:: (Monad m, Traversable (Base t), Recursive t) 
=> (Base t (a, b) -> m b)

algebra

-> (Base t (a, b) -> m a)

algebra

-> t 
-> m b 

mutumorphism on mutual recursive

comutuM Source #

Arguments

:: (Monad m, Traversable (Base t), Corecursive t) 
=> (b -> m (Base t (Either a b)))

coalgebra

-> (a -> m (Base t (Either a b)))

coalgebra

-> b 
-> m t 

comutumorphism on comutual recursive

mutuM' Source #

Arguments

:: (Monad m, Traversable (Base t), Recursive t) 
=> (a -> b)

project

-> (Base t a -> m a)

algebra

-> t 
-> m b 

mutumorphism on recursive variant over catamorphism

comutuM' Source #

Arguments

:: (Monad m, Traversable (Base t), Corecursive t) 
=> (b -> a)

embed

-> (a -> m (Base t a))

coalgebra

-> b 
-> m t 

comutumorphism on recursive variant over anamorphism

cascadeM Source #

Arguments

:: (Monad m, Corecursive (f a), Traversable (Base (f a)), Traversable f, Recursive (f a)) 
=> (a -> m a)

pre-operator

-> f a 
-> m (f a) 

cascade (a.k.a supermap)

iterateM Source #

Arguments

:: (Monad m, Corecursive (f a), Traversable (Base (f a)), Traversable f, Recursive (f a)) 
=> (a -> m a)

post-operator

-> f a 
-> m (f a) 

iterate