yaya-unsafe-0.2.0.0: Non-total extensions to the Yaya recursion scheme library.

Safe HaskellNone
LanguageHaskell2010

Yaya.Unsafe.Fold.Instances

Contents

Description

Type class instances that use direct recursion in a potentially partial way. This is separated from the rest of Fold because you can neither control nor qualify the import of instances. Therefore this module is _extra_ dangerous, as having these instances available applies to the entire module they’re imported into.

This contains instances that you might _expect_ to see, but which aren’t actually total. For example, folding a lazy list `[a]` is _not_ guaranteed to terminate.

Documentation

seqFreeT :: (Functor f, Functor h) => DistributiveLaw (->) h f -> DistributiveLaw (->) (Free h) f Source #

Orphan instances

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

Methods

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

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

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

Methods

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

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

(Functor f, Show1 f) => Show (Fix f) Source # 
Instance details

Methods

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

show :: Fix f -> String #

showList :: [Fix f] -> ShowS #

(Functor f, Show1 f) => Show (Nu f) Source # 
Instance details

Methods

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

show :: Nu f -> String #

showList :: [Nu f] -> ShowS #

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

Methods

cata :: Algebra (->) f a -> Fix f -> a #

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

Methods

cata :: Algebra (->) f a -> Nu f -> a #

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

Methods

ana :: Coalgebra (->) f a -> a -> Mu f #

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

Methods

cata :: Algebra (->) (XNor a) a0 -> [a] -> a0 #

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

Methods

cata :: Algebra (->) (AndMaybe a) a0 -> NonEmpty a -> a0 #

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

Methods

cata :: Algebra (->) (EnvT a f) a0 -> Cofree f a -> a0 #

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

Methods

cata :: Algebra (->) (FreeF f a) a0 -> Free f a -> a0 #