yaya-unsafe-0.1.1.2: Non-total extensions to the Yaya recursion scheme library.

Safe HaskellNone
LanguageHaskell2010

Yaya.Unsafe.Fold

Description

Definitions and instances that use direct recursion, which (because of laziness) can lead to non-termination.

Synopsis

Documentation

anaM :: (Monad m, Steppable t f, Traversable f) => CoalgebraM m f a -> a -> m t Source #

This can’t be implemented in a total fashion. There is a _similar_ approach that can be total – with `ψ :: CoalgebraM m f a`, `ana (Compose . ψ)` results in something like `Nu (Compose m f)` which is akin to an effectful stream.

ganaM :: (Monad m, Monad n, Traversable n, Steppable t f, Traversable f) => DistributiveLaw n f -> GCoalgebraM m n f a -> a -> m t Source #

hylo :: Functor f => Algebra f b -> Coalgebra f a -> a -> b Source #

Fusion of an ana and cata.

ghylo :: (Comonad w, Monad m, Functor f) => DistributiveLaw f w -> DistributiveLaw m f -> GAlgebra w f b -> GCoalgebra m f a -> a -> b Source #

hyloM :: (Monad m, Traversable f) => AlgebraM m f b -> CoalgebraM m f a -> a -> m b Source #

ghyloM :: (Comonad w, Traversable w, Monad m, Traversable f, Monad n, Traversable n) => DistributiveLaw f w -> DistributiveLaw n f -> GAlgebraM m w f b -> GCoalgebraM m n f a -> a -> m b Source #

stream' :: (Projectable t f, Steppable u g, Functor g) => CoalgebraM Maybe g b -> (b -> ((b -> b, t) -> u) -> f t -> u) -> b -> t -> u Source #

streamAna :: (Projectable t f, Steppable u g, Functor g) => CoalgebraM Maybe g b -> AlgebraM ((,) (b -> b)) f t -> b -> t -> u Source #

Gibbons’ metamorphism. It lazily folds a (necessarily infinite) value, incrementally re-expanding that value into some new representation.

streamGApo :: (Projectable t f, Steppable u g, Corecursive u g, Functor g) => Coalgebra g b -> CoalgebraM Maybe g b -> (f t -> Maybe (b -> b, t)) -> b -> t -> u Source #

Another form of Gibbons’ metamorphism. This one can be applied to non- infinite inputs and takes an additional “flushing” coalgebra to be applied after all the input has been consumed.