yaya-0.6.2.0: Total recursion schemes.
Safe HaskellSafe
LanguageHaskell2010

Yaya.Applied

Synopsis

Documentation

absurd :: Recursive (->) t Identity => t -> a Source #

append :: (Recursive (->) t (XNor a), Steppable (->) u (XNor a)) => t -> u -> u Source #

at :: (Recursive (->) n Maybe, Projectable (->) s ((,) a)) => n -> s -> a Source #

Extracts the element at a finite index of an infinite sequence (a !! that can't fail).

atMay :: (Recursive (->) n Maybe, Projectable (->) s (XNor a)) => n -> s -> Maybe a Source #

Extracts the element at a finite index of a (co)list (a !! that fails with Nothing).

constantly :: Corecursive (->) t (Pair a) => a -> t Source #

Creates an infinite stream of the provided value.

drop' :: Projectable (->) t (XNor a) => Maybe (t -> t) -> t -> t Source #

drop :: (Recursive (->) n Maybe, Projectable (->) t (XNor a)) => n -> t -> t Source #

fibonacci :: Corecursive (->) t ((,) Int) => t Source #

fibonacciPolynomials :: (Integral i, Corecursive (->) t ((,) i)) => i -> t Source #

fromList :: Corecursive (->) t (XNor a) => [a] -> t Source #

An implementation of toList for Corecursive fixed-points of XNor.

fromListN :: Steppable (->) t (XNor a) => Int -> [a] -> t Source #

An implementation of fromListN for Steppable fixed-points of XNor.

This should return an empty structure if the Int is negative.

If the target structure isn’t Steppable or the target structure is Corecursive (i.e., unsafeFromList isn’t used), then the default definition for fromListN should suffice.

fromMaybe :: (Steppable (->) t (Either a), Corecursive (->) t (Either a)) => Maybe a -> t Source #

Converts exceptional divergence to non-termination.

height :: (Foldable f, Steppable (->) n Maybe, Ord n) => f n -> n Source #

jacobsthal :: (Integral i, Corecursive (->) t ((,) i)) => t Source #

length :: (Recursive (->) t (XNor a), Steppable (->) n Maybe, Ord n) => t -> n Source #

lucas :: Integral i => Corecursive (->) t ((,) i) => t Source #

lucasSequenceU :: (Integral i, Corecursive (->) t ((,) i)) => i -> i -> t Source #

lucasSequenceV :: (Integral i, Corecursive (->) t ((,) i)) => i -> i -> t Source #

maybeReify :: (Projectable (->) s f, Steppable (->) l (FreeF f s), Functor f) => Algebra (->) Maybe (s -> l) Source #

Turns part of a structure inductive, so it can be analyzed, without forcing the entire tree.

mersenne :: (Integral i, Corecursive (->) t ((,) i)) => t Source #

naturals :: (Steppable (->) n Maybe, Corecursive (->) t ((,) n)) => t Source #

now :: Steppable (->) t (Either a) => a -> t Source #

pell :: (Integral i, Corecursive (->) t ((,) i)) => t Source #

reifyUpTo :: (Recursive (->) n Maybe, Projectable (->) s f, Steppable (->) l (FreeF f s), Functor f) => n -> s -> l Source #

reverse' :: Steppable (->) t (XNor a) => XNor a (XNor a t -> XNor a t) -> XNor a t -> XNor a t Source #

reverse :: (Recursive (->) t (XNor a), Steppable (->) u (XNor a)) => t -> u Source #

runToEnd :: Recursive (->) t (Either a) => t -> a Source #

This will collapse all the intermediate steps to get to the value that must exist at the end.

succN :: Steppable (->) t Maybe => t -> t Source #

tail :: Projectable (->) t (XNor a) => t -> t Source #

take :: (Recursive (->) n Maybe, Projectable (->) s ((,) a), Steppable (->) l (XNor a)) => n -> s -> l Source #

Extracts _exactly_ n elements from the infinite stream s.

takeUpTo :: (Recursive (->) n Maybe, Projectable (->) s (XNor a), Steppable (->) l (XNor a)) => n -> s -> l Source #

Extracts _no more than_ n elements from the possibly-infinite sequence s.

toList :: Projectable (->) t (XNor a) => t -> [a] Source #

An implementation of toList for Projectable fixed-points of XNor.

truncate :: (Recursive (->) n Maybe, Projectable (->) t f, Steppable (->) u (FreeF f ()), Functor f) => n -> t -> u Source #

Lops off the branches of the tree below a certain depth, turning a potentially-infinite structure into a finite one. Like a generalized take.

vacuous :: (Functor f, Recursive (->) t Identity) => f t -> f a Source #

zeroN :: Steppable (->) t Maybe => t Source #

Orphan instances

Monoid (Mu (XNor a)) Source # 
Instance details

Methods

mempty :: Mu (XNor a) #

mappend :: Mu (XNor a) -> Mu (XNor a) -> Mu (XNor a) #

mconcat :: [Mu (XNor a)] -> Mu (XNor a) #

Monoid (Fix (XNor a)) Source # 
Instance details

Methods

mempty :: Fix (XNor a) #

mappend :: Fix (XNor a) -> Fix (XNor a) -> Fix (XNor a) #

mconcat :: [Fix (XNor a)] -> Fix (XNor a) #

Semigroup (Mu (XNor a)) Source # 
Instance details

Methods

(<>) :: Mu (XNor a) -> Mu (XNor a) -> Mu (XNor a) #

sconcat :: NonEmpty (Mu (XNor a)) -> Mu (XNor a) #

stimes :: Integral b => b -> Mu (XNor a) -> Mu (XNor a) #

Semigroup (Fix (XNor a)) Source # 
Instance details

Methods

(<>) :: Fix (XNor a) -> Fix (XNor a) -> Fix (XNor a) #

sconcat :: NonEmpty (Fix (XNor a)) -> Fix (XNor a) #

stimes :: Integral b => b -> Fix (XNor a) -> Fix (XNor a) #

IsList (Nu (XNor a)) Source #

This instance is safe, since both structures are lazy.

Instance details

Associated Types

type Item (Nu (XNor a)) #

Methods

fromList :: [Item (Nu (XNor a))] -> Nu (XNor a) #

fromListN :: Int -> [Item (Nu (XNor a))] -> Nu (XNor a) #

toList :: Nu (XNor a) -> [Item (Nu (XNor a))] #