yaya-0.2.1.0: Total recursion schemes.

Safe HaskellSafe
LanguageHaskell2010

Yaya.Fold.Common

Contents

Description

Common algebras that are useful when folding.

Synopsis

Documentation

lowerMonoid :: Monoid m => (a -> m) -> XNor a m -> m Source #

Converts the free monoid (a list) into some other monoid.

lowerSemigroup :: Semigroup m => (a -> m) -> AndMaybe a m -> m Source #

Converts the free semigroup (a non-empty list) into some other semigroup.

lowerMonad :: Monad m => (forall a. f a -> m a) -> FreeF f a (m a) -> m a Source #

equal :: (Functor f, Foldable f, Eq1 f) => Day f f Bool -> Bool Source #

height :: Foldable f => f Integer -> Integer Source #

When folded, returns the height of the data structure.

size :: Foldable f => f Natural -> Natural Source #

When folded, returns the number ef nodes in the data structure.

while :: (a -> Maybe a) -> a -> Either a a Source #

Returns the last Just result.

takeAnother :: Day Maybe ((,) a) b -> XNor a b Source #

truncate' :: Functor f => Day Maybe f a -> FreeF f () a Source #

split :: a -> (a, a) Source #

Converts a single value into a tuple with the same value on both sides. > x &&& y = (x *** y) . split

sequence generators

unarySequence :: (a -> b) -> a -> (a, b) Source #

binarySequence :: (a -> b -> c) -> (a, b) -> (a, (b, c)) Source #

ternarySequence :: (a -> b -> c -> d) -> (a, b, c) -> (a, (b, c, d)) Source #

lucasSequence' :: Integral i => i -> i -> (i, i) -> (i, (i, i)) Source #