yaya-unsafe-0.4.0.0: Non-total extensions to the Yaya recursion scheme library.
Safe HaskellSafe
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.

corecursivePrism :: (Steppable (->) t f, Recursive (->) t f, Traversable f) => CoalgebraPrism f a -> Prism' a t Source #

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

ghylo :: (Comonad w, Monad m, Functor f) => DistributiveLaw (->) f w -> DistributiveLaw (->) m f -> GAlgebra (->) w f b -> GCoalgebra (->) m f a -> a -> 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 #

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

Fusion of an ana and cata.

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

stream' :: (Projectable (->) t f, Steppable (->) u g, Functor g) => CoalgebraM (->) Maybe g b -> (b -> (Pair (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 (->) (Pair (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.

NB: See https://gist.github.com/sellout/4709e723cb649110af00217486c4466b for some commentary and explanation.

streamGApo :: (Projectable (->) t f, Steppable (->) u g, Corecursive (->) u g, Functor g) => Coalgebra (->) g b -> CoalgebraM (->) Maybe g b -> (f t -> Maybe (Pair (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.

NB: See https://gist.github.com/sellout/4709e723cb649110af00217486c4466b for some commentary and explanation.

unsafeAna :: (Steppable (->) t f, Functor f) => Coalgebra (->) f a -> a -> t Source #

Instances leak transitively, so while Yaya.Unsafe.Fold.Instances exists, it should only be used when it is unavoidable. If you are explicitly folding a structure unsafely, use this function instead of importing that module.

unsafeCata :: (Projectable (->) t f, Functor f) => Algebra (->) f a -> t -> a Source #

Instances leak transitively, so while Yaya.Unsafe.Fold.Instances exists, it should only be used when it is unavoidable. If you are explicitly unfolding a structure unsafely, use this function instead of importing that module.

Should one prefer unsafeAna or unsafeCata in cases where both are applicable? - one may provide weaker constraints than the other in certain cases (e.g., on its own, unsafeCata only requires Projectable on the source, but unsafeAna requires Steppable on the target. Depending on what other constraints already exist on the function, either one may ultimately be less constrained. - they may fail differently: unsafeCata (folding a potentially-infinite structure) is likely to result in non-termination, whereas unsafeAna (building a potentially-infinite structure strictly) is likely to use up the memory or overflow the stack.