yaya-0.6.2.0: Total recursion schemes.
Safe HaskellSafe
LanguageHaskell2010

Yaya.Fold

Synopsis

Documentation

type Algebra c f a = f a `c` a Source #

type AlgebraM c m f a = f a `c` m a Source #

type AlgebraPrism f a = Prism' (f a) a Source #

type BialgebraIso f a = Iso' (f a) a Source #

type Coalgebra c f a = a `c` f a Source #

type CoalgebraM c m f a = a `c` m (f a) Source #

Note that using a CoalgebraM “directly” is partial (e.g., with anaM). However, ana . Compose can accept a CoalgebraM and produce something like an effectful stream.

type CoalgebraPrism f a = Prism' a (f a) Source #

class Corecursive c t f | t -> f where Source #

Coinductive (potentially-infinite) structures that guarantee _productivity_ rather than termination.

Methods

ana :: Coalgebra c f a -> a `c` t Source #

Instances

Instances details
Corecursive (->) (Nu f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

ana :: forall (a :: k). Coalgebra (->) f a -> a -> Nu f Source #

Functor f => Corecursive (->) (Cofix f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold.Native.Internal

Methods

ana :: forall (a :: k). Coalgebra (->) f a -> a -> Cofix f Source #

Corecursive (->) (NonEmpty a :: Type) (AndMaybe a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

ana :: forall (a0 :: k). Coalgebra (->) (AndMaybe a) a0 -> a0 -> NonEmpty a Source #

Corecursive (->) ([a] :: Type) (XNor a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

ana :: forall (a0 :: k). Coalgebra (->) (XNor a) a0 -> a0 -> [a] Source #

Corecursive (->) (Maybe a :: Type) (Const (Maybe a) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

ana :: forall (a0 :: k). Coalgebra (->) (Const (Maybe a)) a0 -> a0 -> Maybe a Source #

Functor f => Corecursive (->) (Cofree f a :: Type) (EnvT a f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

ana :: forall (a0 :: k). Coalgebra (->) (EnvT a f) a0 -> a0 -> Cofree f a Source #

Functor f => Corecursive (->) (Free f a :: Type) (FreeF f a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

ana :: forall (a0 :: k). Coalgebra (->) (FreeF f a) a0 -> a0 -> Free f a Source #

Corecursive (->) (Either a b :: Type) (Const (Either a b) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

ana :: forall (a0 :: k). Coalgebra (->) (Const (Either a b)) a0 -> a0 -> Either a b Source #

type DistributiveLaw c f g = forall a. f (g a) `c` g (f a) Source #

There are a number of distributive laws, including sequenceA, distribute, and sequenceL. Yaya also provides others for specific recursion schemes.

type ElgotAlgebra c w f a = w (f a) `c` a Source #

type ElgotAlgebraM c m w f a = w (f a) `c` m a Source #

type ElgotCoalgebra c m f a = a `c` m (f a) Source #

type GAlgebra c w f a = f (w a) `c` a Source #

type GAlgebraM c m w f a = f (w a) `c` m a Source #

type GCoalgebra c m f a = a `c` f (m a) Source #

type GCoalgebraM c m n f a = a `c` m (f (n a)) Source #

newtype Mu f Source #

A fixed-point operator for inductive / finite data structures.

NB: This is only guaranteed to be finite when f a is strict in a (having strict functors won't prevent Nu from being lazy). Using -XStrictData can help with this a lot.

Constructors

Mu (forall a. Algebra (->) f a -> a) 

Instances

Instances details
DFunctor Mu Source # 
Instance details

Defined in Yaya.Fold

Methods

dmap :: (forall x. f x -> g x) -> Mu f -> Mu g Source #

Functor f => Projectable (->) (Mu f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (->) f (Mu f) Source #

Recursive (->) (Mu f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

cata :: forall (a :: k1). Algebra (->) f a -> Mu f -> a Source #

Functor f => Steppable (->) (Mu f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (->) f (Mu f) Source #

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

Defined in Yaya.Applied

Methods

mempty :: Mu (XNor a) #

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

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

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

Defined in Yaya.Applied

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) #

(Functor f, Read1 f) => Read (Mu f) Source #

Since: 0.6.1.0

Instance details

Defined in Yaya.Fold

Show1 f => Show (Mu f) Source # 
Instance details

Defined in Yaya.Fold

Methods

showsPrec :: Int -> Mu f -> ShowS #

show :: Mu f -> String #

showList :: [Mu f] -> ShowS #

(Functor f, Foldable f, Eq1 f) => Eq (Mu f) Source # 
Instance details

Defined in Yaya.Fold

Methods

(==) :: Mu f -> Mu f -> Bool #

(/=) :: Mu f -> Mu f -> Bool #

(Functor f, Foldable f, Ord1 f) => Ord (Mu f) Source #

Since: 0.6.1.0

Instance details

Defined in Yaya.Fold

Methods

compare :: Mu f -> Mu f -> Ordering #

(<) :: Mu f -> Mu f -> Bool #

(<=) :: Mu f -> Mu f -> Bool #

(>) :: Mu f -> Mu f -> Bool #

(>=) :: Mu f -> Mu f -> Bool #

max :: Mu f -> Mu f -> Mu f #

min :: Mu f -> Mu f -> Mu f #

data Nu f where Source #

A fixed-point operator for coinductive / potentially-infinite data structures.

Constructors

Nu :: Coalgebra (->) f a -> a -> Nu f 

Instances

Instances details
DFunctor Nu Source # 
Instance details

Defined in Yaya.Fold

Methods

dmap :: (forall x. f x -> g x) -> Nu f -> Nu g Source #

Corecursive (->) (Nu f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

ana :: forall (a :: k). Coalgebra (->) f a -> a -> Nu f Source #

Functor f => Projectable (->) (Nu f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (->) f (Nu f) Source #

Functor f => Steppable (->) (Nu f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (->) f (Nu f) Source #

IsList (Nu (XNor a)) Source #

This instance is safe, since both structures are lazy.

Instance details

Defined in Yaya.Applied

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))] #

(Functor f, Read1 f) => Read (Nu f) Source #

Since: 0.6.1.0

Instance details

Defined in Yaya.Fold

type Item (Nu (XNor a)) Source # 
Instance details

Defined in Yaya.Applied

type Item (Nu (XNor a)) = a

class Projectable c t f | t -> f where Source #

This type class is lawless on its own, but there exist types that can’t implement the corresponding embed operation. Laws are induced by implementing either Steppable (which extends this) or Corecursive (which doesn’t).

Methods

project :: Coalgebra c f t Source #

Instances

Instances details
Projectable (->) Void Identity Source # 
Instance details

Defined in Yaya.Fold

Projectable (->) Natural Maybe Source # 
Instance details

Defined in Yaya.Fold

Functor f => Projectable (->) (Mu f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (->) f (Mu f) Source #

Functor f => Projectable (->) (Nu f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (->) f (Nu f) Source #

Projectable (->) (Fix f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

project :: Coalgebra (->) f (Fix f) Source #

Projectable (->) (Cofix f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold.Native.Internal

Methods

project :: Coalgebra (->) f (Cofix f) Source #

Projectable (->) (NonEmpty a :: Type) (AndMaybe a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (->) (AndMaybe a) (NonEmpty a) Source #

Projectable (->) ([a] :: Type) (XNor a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (->) (XNor a) [a] Source #

Projectable (->) (Maybe a :: Type) (Const (Maybe a) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (->) (Const (Maybe a)) (Maybe a) Source #

Projectable (->) (Cofree f a :: Type) (EnvT a f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (->) (EnvT a f) (Cofree f a) Source #

Projectable (->) (Free f a :: Type) (FreeF f a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (->) (FreeF f a) (Free f a) Source #

Projectable (->) (Either a b :: Type) (Const (Either a b) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

project :: Coalgebra (->) (Const (Either a b)) (Either a b) Source #

class Recursive c t f | t -> f where Source #

Inductive structures that can be reasoned about in the way we usually do – with pattern matching.

Methods

cata :: Algebra c f a -> t `c` a Source #

Instances

Instances details
Recursive (->) Void Identity Source # 
Instance details

Defined in Yaya.Fold

Methods

cata :: forall (a :: k1). Algebra (->) Identity a -> Void -> a Source #

Recursive (->) Natural Maybe Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

cata :: forall (a :: k1). Algebra (->) Maybe a -> Natural -> a Source #

Recursive (->) (Mu f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

cata :: forall (a :: k1). Algebra (->) f a -> Mu f -> a Source #

Functor f => Recursive (->) (Fix f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

cata :: forall (a :: k1). Algebra (->) f a -> Fix f -> a Source #

Recursive (->) (Maybe a :: Type) (Const (Maybe a) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

cata :: forall (a0 :: k1). Algebra (->) (Const (Maybe a)) a0 -> Maybe a -> a0 Source #

Recursive (->) (Either a b :: Type) (Const (Either a b) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

cata :: forall (a0 :: k1). Algebra (->) (Const (Either a b)) a0 -> Either a b -> a0 Source #

class Projectable c t f => Steppable c t f | t -> f where Source #

Structures you can walk through step-by-step.

Methods

embed :: Algebra c f t Source #

Instances

Instances details
Steppable (->) Void Identity Source # 
Instance details

Defined in Yaya.Fold

Steppable (->) Natural Maybe Source # 
Instance details

Defined in Yaya.Fold

Functor f => Steppable (->) (Mu f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (->) f (Mu f) Source #

Functor f => Steppable (->) (Nu f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (->) f (Nu f) Source #

Steppable (->) (Fix f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold.Native

Methods

embed :: Algebra (->) f (Fix f) Source #

Steppable (->) (Cofix f :: Type) (f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold.Native.Internal

Methods

embed :: Algebra (->) f (Cofix f) Source #

Steppable (->) (NonEmpty a :: Type) (AndMaybe a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (->) (AndMaybe a) (NonEmpty a) Source #

Steppable (->) ([a] :: Type) (XNor a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (->) (XNor a) [a] Source #

Steppable (->) (Maybe a :: Type) (Const (Maybe a) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (->) (Const (Maybe a)) (Maybe a) Source #

Steppable (->) (Cofree f a :: Type) (EnvT a f :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (->) (EnvT a f) (Cofree f a) Source #

Steppable (->) (Free f a :: Type) (FreeF f a :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (->) (FreeF f a) (Free f a) Source #

Steppable (->) (Either a b :: Type) (Const (Either a b) :: Type -> Type) Source # 
Instance details

Defined in Yaya.Fold

Methods

embed :: Algebra (->) (Const (Either a b)) (Either a b) Source #

attributeAlgebra :: (Steppable (->) t (EnvT a f), Functor f) => Algebra (->) f a -> Algebra (->) f t Source #

Converts an Algebra to one that annotates the tree with the result for each node.

attributeCoalgebra :: Coalgebra (->) f a -> Coalgebra (->) (EnvT a f) a Source #

Converts a Coalgebra to one that annotates the tree with the seed that generated each node.

birecursiveIso :: (Recursive (->) t f, Corecursive (->) t f) => BialgebraIso f a -> Iso' t a Source #

cata2 :: (Recursive (->) t f, Projectable (->) u g) => Algebra (->) (Day f g) a -> t -> u -> a Source #

By analogy with liftA2 (which also relies on Day, at least conceptually).

colambek :: (Projectable (->) t f, Corecursive (->) t f, Functor f) => Algebra (->) f t Source #

constAna :: Coalgebra (->) (Const b) a -> a -> b Source #

constCata :: Algebra (->) (Const b) a -> b -> a Source #

distEnvT :: Functor f => Algebra (->) f a -> DistributiveLaw (->) f w -> DistributiveLaw (->) f (EnvT a w) Source #

distIdentity :: Functor f => DistributiveLaw (->) f Identity Source #

A less-constrained distribute for Identity.

distTuple :: Functor f => Algebra (->) f a -> DistributiveLaw (->) f (Pair a) Source #

elgotAna :: (Corecursive (->) t f, Functor f, Monad m) => DistributiveLaw (->) m f -> ElgotCoalgebra (->) m f a -> a -> t Source #

elgotCata :: (Recursive (->) t f, Functor f, Comonad w) => DistributiveLaw (->) f w -> ElgotAlgebra (->) w f a -> t -> a Source #

elgotCataM :: (Monad m, Recursive (->) t f, Traversable f, Comonad w, Traversable w) => DistributiveLaw (->) f w -> ElgotAlgebraM (->) m w f a -> t -> m a Source #

ezygoM :: (Monad m, Recursive (->) t f, Traversable f) => AlgebraM (->) m f b -> ElgotAlgebraM (->) m (Pair b) f a -> t -> m a Source #

gana :: (Corecursive (->) t f, Functor f, Monad m) => DistributiveLaw (->) m f -> GCoalgebra (->) m f a -> a -> t Source #

gcata :: (Recursive (->) t f, Functor f, Comonad w) => DistributiveLaw (->) f w -> GAlgebra (->) w f a -> t -> a Source #

gcataM :: (Monad m, Recursive (->) t f, Traversable f, Comonad w, Traversable w) => DistributiveLaw (->) f w -> GAlgebraM (->) m w f a -> t -> m a Source #

ignoringAttribute :: Algebra (->) f a -> Algebra (->) (EnvT b f) a Source #

This is just a more obvious name for composing lowerEnvT with your algebra directly.

lambek :: (Steppable (->) t f, Recursive (->) t f, Functor f) => Coalgebra (->) f t Source #

lowerAlgebra :: (Functor f, Comonad w) => DistributiveLaw (->) f w -> GAlgebra (->) w f a -> Algebra (->) f (w a) Source #

Makes it possible to provide a GAlgebra to cata.

lowerAlgebraM :: (Applicative m, Traversable f, Comonad w, Traversable w) => DistributiveLaw (->) f w -> GAlgebraM (->) m w f a -> AlgebraM (->) m f (w a) Source #

Makes it possible to provide a GAlgebraM to cataM.

lowerCoalgebra :: (Functor f, Monad m) => DistributiveLaw (->) m f -> GCoalgebra (->) m f a -> Coalgebra (->) f (m a) Source #

Makes it possible to provide a GCoalgebra to ana.

lowerCoalgebraM :: (Applicative m, Traversable f, Monad n, Traversable n) => DistributiveLaw (->) n f -> GCoalgebraM (->) m n f a -> CoalgebraM (->) m f (n a) Source #

Makes it possible to provide a GCoalgebraM to anaM.

lowerDay :: Projectable (->) t g => Algebra (->) (Day f g) a -> Algebra (->) f (t -> a) Source #

Algebras over Day convolution are convenient for binary operations, but aren’t directly handleable by cata.

recursiveCompare :: (Recursive (->) t f, Steppable (->) u f, Functor f, Foldable f, Ord1 f) => t -> u -> Ordering Source #

An implementation of == for any Recursive instance. Note that this is actually more general than Ord’s compare, as it can compare between different fixed-point representations of the same functor.

NB: Use recursiveCompare' if you need to use a custom comparator for f.

Since: 0.6.1.0

recursiveCompare' :: (Recursive (->) t f, Steppable (->) u f, Functor f, Foldable f) => (f () -> f () -> Ordering) -> t -> u -> Ordering Source #

Like recursiveCompare, but allows you to provide a custom comparator for f.

Since: 0.6.1.0

recursiveEq :: (Recursive (->) t f, Steppable (->) u f, Functor f, Foldable f, Eq1 f) => t -> u -> Bool Source #

An implementation of == for any Recursive instance. Note that this is actually more general than Eq’s ==, as it can compare between different fixed-point representations of the same functor.

NB: Use recursiveEq' if you need to use a custom comparator for f.

recursiveEq' :: (Recursive (->) t f, Steppable (->) u f, Functor f, Foldable f) => (f () -> f () -> Bool) -> t -> u -> Bool Source #

Like recursiveEq, but allows you to provide a custom comparator for f.

Since: 0.6.1.0

recursivePrism :: (Recursive (->) t f, Corecursive (->) t f, Traversable f) => AlgebraPrism f a -> Prism' t a Source #

recursiveShowsPrec :: (Recursive (->) t f, Show1 f) => Int -> t -> ShowS Source #

An implementation of showsPrec for any Recursive instance.

recursiveShowsPrec' :: Recursive (->) t f => Algebra (->) f (Int -> ShowS) -> Int -> t -> ShowS Source #

Like recursiveShowsPrec, but allows you to provide a custom display function for f.

Since: 0.6.1.0

seqEither :: Functor f => Coalgebra (->) f a -> DistributiveLaw (->) (Either a) f Source #

seqIdentity :: Functor f => DistributiveLaw (->) Identity f Source #

A less-constrained sequenceA for Identity.

steppableReadPrec :: (Steppable (->) t f, Read1 f) => ReadPrec t Source #

An implementation of readPrec for any Steppable instance.

NB: Use steppableReadPrec' if you need to use a custom parsing function for f.

NB: This only requires Steppable, but the inverse operation is recursiveShowsPrec, which requires Recursive instead.

Since: 0.6.1.0

steppableReadPrec' :: Steppable (->) t f => (ReadPrec t -> ReadPrec [t] -> ReadPrec (f t)) -> ReadPrec t Source #

Like steppableReadPrec, but allows you to provide a custom display function for f.

Since: 0.6.1.0

unFree :: Steppable (->) t f => Algebra (->) (FreeF f t) t Source #

It is somewhat common to have a natural transformation that looks like η :: forall a. f a -> Free g a. This maps naturally to a GCoalgebra (to pass to apo) with η . project, but the desired Algebra is more likely to be cata unFree . η than embed . η. See yaya-streams for some examples of this.

zipAlgebraMs :: (Applicative m, Functor f) => AlgebraM (->) m f a -> AlgebraM (->) m f b -> AlgebraM (->) m f (Pair a b) Source #

Combines two AlgebraMs with different carriers into a single tupled AlgebraM.

zipAlgebras :: Functor f => Algebra (->) f a -> Algebra (->) f b -> Algebra (->) f (Pair a b) Source #

Combines two Algebras with different carriers into a single tupled Algebra.