yaya-0.4.2.1: Total recursion schemes.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Yaya.Fold.Native

Description

Uses of recursion schemes that use Haskell’s built-in recursion in a total manner.

Synopsis

Documentation

newtype Fix f Source #

A fixed-point constructor that uses Haskell's built-in recursion. This is lazy/corecursive.

Constructors

Fix 

Fields

Instances

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

Defined in Yaya.Fold.Native

Methods

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

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

Defined in Yaya.Fold.Native

Methods

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

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

Defined in Yaya.Fold.Native

Methods

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

Orphan instances

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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