recursion-schemes-5.1.3: Representing common recursion patterns as higher-order functions

Copyright(C) 2008-2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
Maintainer"Samuel Gélineau" <gelisam@gmail.com>, "Oleg Grenrus" <oleg.grenrus@iki.fi>, "Ryan Scott" <ryan.gl.scott@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell98

Data.Functor.Foldable

Contents

Description

 
Synopsis

Base functors for fixed points

type family Base t :: * -> * Source #

Instances
type Base Natural Source # 
Instance details

Defined in Data.Functor.Foldable

type Base [a] Source # 
Instance details

Defined in Data.Functor.Foldable

type Base [a] = ListF a
type Base (Maybe a) Source #

Example boring stub for non-recursive data types

Instance details

Defined in Data.Functor.Foldable

type Base (Maybe a) = (Const (Maybe a) :: Type -> Type)
type Base (NonEmpty a) Source # 
Instance details

Defined in Data.Functor.Foldable

type Base (NonEmpty a) = NonEmptyF a
type Base (Nu f) Source # 
Instance details

Defined in Data.Functor.Foldable

type Base (Nu f) = f
type Base (Mu f) Source # 
Instance details

Defined in Data.Functor.Foldable

type Base (Mu f) = f
type Base (Fix f) Source # 
Instance details

Defined in Data.Functor.Foldable

type Base (Fix f) = f
type Base (Either a b) Source #

Example boring stub for non-recursive data types

Instance details

Defined in Data.Functor.Foldable

type Base (Either a b) = (Const (Either a b) :: Type -> Type)
type Base (Cofree f a) Source #

Cofree comonads are Recursive/Corecursive

Instance details

Defined in Data.Functor.Foldable

type Base (Cofree f a) = CofreeF f a
type Base (F f a) Source #

Church encoded free monads are Recursive/Corecursive, in the same way that Mu is.

Instance details

Defined in Data.Functor.Foldable

type Base (F f a) = FreeF f a
type Base (Free f a) Source #

Free monads are Recursive/Corecursive

Instance details

Defined in Data.Functor.Foldable

type Base (Free f a) = FreeF f a
type Base (FreeT f m a) Source #

Free transformations of monads are Recursive/Corecursive

Instance details

Defined in Data.Functor.Foldable

type Base (FreeT f m a) = Compose m (FreeF f a)
type Base (CofreeT f w a) Source #

Cofree tranformations of comonads are Recursive/Corecusive

Instance details

Defined in Data.Functor.Foldable

type Base (CofreeT f w a) = Compose w (CofreeF f a)

data ListF a b Source #

Base functor of [].

Constructors

Nil 
Cons a b 
Instances
Bitraversable ListF Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> ListF a b -> f (ListF c d) #

Bifoldable ListF Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

bifold :: Monoid m => ListF m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> ListF a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> ListF a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> ListF a b -> c #

Bifunctor ListF Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

bimap :: (a -> b) -> (c -> d) -> ListF a c -> ListF b d #

first :: (a -> b) -> ListF a c -> ListF b c #

second :: (b -> c) -> ListF a b -> ListF a c #

Eq2 ListF Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> ListF a c -> ListF b d -> Bool #

Ord2 ListF Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> ListF a c -> ListF b d -> Ordering #

Read2 ListF Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (ListF a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [ListF a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (ListF a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [ListF a b] #

Show2 ListF Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> ListF a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [ListF a b] -> ShowS #

Functor (ListF a) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

fmap :: (a0 -> b) -> ListF a a0 -> ListF a b #

(<$) :: a0 -> ListF a b -> ListF a a0 #

Foldable (ListF a) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

fold :: Monoid m => ListF a m -> m #

foldMap :: Monoid m => (a0 -> m) -> ListF a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> ListF a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> ListF a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> ListF a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> ListF a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> ListF a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> ListF a a0 -> a0 #

toList :: ListF a a0 -> [a0] #

null :: ListF a a0 -> Bool #

length :: ListF a a0 -> Int #

elem :: Eq a0 => a0 -> ListF a a0 -> Bool #

maximum :: Ord a0 => ListF a a0 -> a0 #

minimum :: Ord a0 => ListF a a0 -> a0 #

sum :: Num a0 => ListF a a0 -> a0 #

product :: Num a0 => ListF a a0 -> a0 #

Traversable (ListF a) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

traverse :: Applicative f => (a0 -> f b) -> ListF a a0 -> f (ListF a b) #

sequenceA :: Applicative f => ListF a (f a0) -> f (ListF a a0) #

mapM :: Monad m => (a0 -> m b) -> ListF a a0 -> m (ListF a b) #

sequence :: Monad m => ListF a (m a0) -> m (ListF a a0) #

Eq a => Eq1 (ListF a) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

liftEq :: (a0 -> b -> Bool) -> ListF a a0 -> ListF a b -> Bool #

Ord a => Ord1 (ListF a) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

liftCompare :: (a0 -> b -> Ordering) -> ListF a a0 -> ListF a b -> Ordering #

Read a => Read1 (ListF a) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (ListF a a0) #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [ListF a a0] #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (ListF a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [ListF a a0] #

Show a => Show1 (ListF a) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> ListF a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [ListF a a0] -> ShowS #

Generic1 (ListF a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Foldable

Associated Types

type Rep1 (ListF a) :: k -> Type #

Methods

from1 :: ListF a a0 -> Rep1 (ListF a) a0 #

to1 :: Rep1 (ListF a) a0 -> ListF a a0 #

(Eq a, Eq b) => Eq (ListF a b) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

(==) :: ListF a b -> ListF a b -> Bool #

(/=) :: ListF a b -> ListF a b -> Bool #

(Ord a, Ord b) => Ord (ListF a b) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

compare :: ListF a b -> ListF a b -> Ordering #

(<) :: ListF a b -> ListF a b -> Bool #

(<=) :: ListF a b -> ListF a b -> Bool #

(>) :: ListF a b -> ListF a b -> Bool #

(>=) :: ListF a b -> ListF a b -> Bool #

max :: ListF a b -> ListF a b -> ListF a b #

min :: ListF a b -> ListF a b -> ListF a b #

(Read a, Read b) => Read (ListF a b) Source # 
Instance details

Defined in Data.Functor.Foldable

(Show a, Show b) => Show (ListF a b) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

showsPrec :: Int -> ListF a b -> ShowS #

show :: ListF a b -> String #

showList :: [ListF a b] -> ShowS #

Generic (ListF a b) Source # 
Instance details

Defined in Data.Functor.Foldable

Associated Types

type Rep (ListF a b) :: Type -> Type #

Methods

from :: ListF a b -> Rep (ListF a b) x #

to :: Rep (ListF a b) x -> ListF a b #

type Rep1 (ListF a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Foldable

type Rep1 (ListF a :: Type -> Type) = D1 (MetaData "ListF" "Data.Functor.Foldable" "recursion-schemes-5.1.3-JhnH2ykCSmS1gpM95h5C6h" False) (C1 (MetaCons "Nil" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Cons" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep (ListF a b) Source # 
Instance details

Defined in Data.Functor.Foldable

type Rep (ListF a b) = D1 (MetaData "ListF" "Data.Functor.Foldable" "recursion-schemes-5.1.3-JhnH2ykCSmS1gpM95h5C6h" False) (C1 (MetaCons "Nil" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Cons" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 b)))

Fixed points

newtype Fix f Source #

Constructors

Fix (f (Fix f)) 
Instances
Eq1 f => Eq (Fix f) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

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

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

(Typeable f, Data (f (Fix f))) => Data (Fix f) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Fix f -> c (Fix f) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Fix f) #

toConstr :: Fix f -> Constr #

dataTypeOf :: Fix f -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Fix f)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Fix f)) #

gmapT :: (forall b. Data b => b -> b) -> Fix f -> Fix f #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Fix f -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Fix f -> r #

gmapQ :: (forall d. Data d => d -> u) -> Fix f -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Fix f -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Fix f -> m (Fix f) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Fix f -> m (Fix f) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Fix f -> m (Fix f) #

Ord1 f => Ord (Fix f) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

compare :: Fix f -> Fix f -> Ordering #

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

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

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

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

max :: Fix f -> Fix f -> Fix f #

min :: Fix f -> Fix f -> Fix f #

Read1 f => Read (Fix f) Source # 
Instance details

Defined in Data.Functor.Foldable

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

Defined in Data.Functor.Foldable

Methods

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

show :: Fix f -> String #

showList :: [Fix f] -> ShowS #

Functor f => Corecursive (Fix f) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

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

ana :: (a -> Base (Fix f) a) -> a -> Fix f Source #

apo :: (a -> Base (Fix f) (Either (Fix f) a)) -> a -> Fix f Source #

postpro :: Recursive (Fix f) => (forall b. Base (Fix f) b -> Base (Fix f) b) -> (a -> Base (Fix f) a) -> a -> Fix f Source #

gpostpro :: (Recursive (Fix f), Monad m) => (forall b. m (Base (Fix f) b) -> Base (Fix f) (m b)) -> (forall c. Base (Fix f) c -> Base (Fix f) c) -> (a -> Base (Fix f) (m a)) -> a -> Fix f Source #

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

Defined in Data.Functor.Foldable

Methods

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

cata :: (Base (Fix f) a -> a) -> Fix f -> a Source #

para :: (Base (Fix f) (Fix f, a) -> a) -> Fix f -> a Source #

gpara :: (Corecursive (Fix f), Comonad w) => (forall b. Base (Fix f) (w b) -> w (Base (Fix f) b)) -> (Base (Fix f) (EnvT (Fix f) w a) -> a) -> Fix f -> a Source #

prepro :: Corecursive (Fix f) => (forall b. Base (Fix f) b -> Base (Fix f) b) -> (Base (Fix f) a -> a) -> Fix f -> a Source #

gprepro :: (Corecursive (Fix f), Comonad w) => (forall b. Base (Fix f) (w b) -> w (Base (Fix f) b)) -> (forall c. Base (Fix f) c -> Base (Fix f) c) -> (Base (Fix f) (w a) -> a) -> Fix f -> a Source #

type Base (Fix f) Source # 
Instance details

Defined in Data.Functor.Foldable

type Base (Fix f) = f

unfix :: Fix f -> f (Fix f) Source #

newtype Mu f Source #

Constructors

Mu (forall a. (f a -> a) -> a) 
Instances
(Functor f, Eq1 f) => Eq (Mu f) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

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

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

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

Defined in Data.Functor.Foldable

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 #

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

Defined in Data.Functor.Foldable

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

Defined in Data.Functor.Foldable

Methods

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

show :: Mu f -> String #

showList :: [Mu f] -> ShowS #

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

Defined in Data.Functor.Foldable

Methods

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

ana :: (a -> Base (Mu f) a) -> a -> Mu f Source #

apo :: (a -> Base (Mu f) (Either (Mu f) a)) -> a -> Mu f Source #

postpro :: Recursive (Mu f) => (forall b. Base (Mu f) b -> Base (Mu f) b) -> (a -> Base (Mu f) a) -> a -> Mu f Source #

gpostpro :: (Recursive (Mu f), Monad m) => (forall b. m (Base (Mu f) b) -> Base (Mu f) (m b)) -> (forall c. Base (Mu f) c -> Base (Mu f) c) -> (a -> Base (Mu f) (m a)) -> a -> Mu f Source #

Functor f => Recursive (Mu f) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

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

cata :: (Base (Mu f) a -> a) -> Mu f -> a Source #

para :: (Base (Mu f) (Mu f, a) -> a) -> Mu f -> a Source #

gpara :: (Corecursive (Mu f), Comonad w) => (forall b. Base (Mu f) (w b) -> w (Base (Mu f) b)) -> (Base (Mu f) (EnvT (Mu f) w a) -> a) -> Mu f -> a Source #

prepro :: Corecursive (Mu f) => (forall b. Base (Mu f) b -> Base (Mu f) b) -> (Base (Mu f) a -> a) -> Mu f -> a Source #

gprepro :: (Corecursive (Mu f), Comonad w) => (forall b. Base (Mu f) (w b) -> w (Base (Mu f) b)) -> (forall c. Base (Mu f) c -> Base (Mu f) c) -> (Base (Mu f) (w a) -> a) -> Mu f -> a Source #

type Base (Mu f) Source # 
Instance details

Defined in Data.Functor.Foldable

type Base (Mu f) = f

hoistMu :: (forall a. f a -> g a) -> Mu f -> Mu g Source #

A specialized, faster version of hoist for Mu.

data Nu f where Source #

Constructors

Nu :: (a -> f a) -> a -> Nu f 
Instances
(Functor f, Eq1 f) => Eq (Nu f) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

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

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

(Functor f, Ord1 f) => Ord (Nu f) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

compare :: Nu f -> Nu f -> Ordering #

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

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

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

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

max :: Nu f -> Nu f -> Nu f #

min :: Nu f -> Nu f -> Nu f #

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

Defined in Data.Functor.Foldable

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

Defined in Data.Functor.Foldable

Methods

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

show :: Nu f -> String #

showList :: [Nu f] -> ShowS #

Functor f => Corecursive (Nu f) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

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

ana :: (a -> Base (Nu f) a) -> a -> Nu f Source #

apo :: (a -> Base (Nu f) (Either (Nu f) a)) -> a -> Nu f Source #

postpro :: Recursive (Nu f) => (forall b. Base (Nu f) b -> Base (Nu f) b) -> (a -> Base (Nu f) a) -> a -> Nu f Source #

gpostpro :: (Recursive (Nu f), Monad m) => (forall b. m (Base (Nu f) b) -> Base (Nu f) (m b)) -> (forall c. Base (Nu f) c -> Base (Nu f) c) -> (a -> Base (Nu f) (m a)) -> a -> Nu f Source #

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

Defined in Data.Functor.Foldable

Methods

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

cata :: (Base (Nu f) a -> a) -> Nu f -> a Source #

para :: (Base (Nu f) (Nu f, a) -> a) -> Nu f -> a Source #

gpara :: (Corecursive (Nu f), Comonad w) => (forall b. Base (Nu f) (w b) -> w (Base (Nu f) b)) -> (Base (Nu f) (EnvT (Nu f) w a) -> a) -> Nu f -> a Source #

prepro :: Corecursive (Nu f) => (forall b. Base (Nu f) b -> Base (Nu f) b) -> (Base (Nu f) a -> a) -> Nu f -> a Source #

gprepro :: (Corecursive (Nu f), Comonad w) => (forall b. Base (Nu f) (w b) -> w (Base (Nu f) b)) -> (forall c. Base (Nu f) c -> Base (Nu f) c) -> (Base (Nu f) (w a) -> a) -> Nu f -> a Source #

type Base (Nu f) Source # 
Instance details

Defined in Data.Functor.Foldable

type Base (Nu f) = f

hoistNu :: (forall a. f a -> g a) -> Nu f -> Nu g Source #

A specialized, faster version of hoist for Nu.

Folding

class Functor (Base t) => Recursive t where Source #

Minimal complete definition

Nothing

Methods

project :: t -> Base t t Source #

project :: (Generic t, Generic (Base t t), GCoerce (Rep t) (Rep (Base t t))) => t -> Base t t Source #

cata Source #

Arguments

:: (Base t a -> a)

a (Base t)-algebra

-> t

fixed point

-> a

result

para :: (Base t (t, a) -> a) -> t -> a Source #

gpara :: (Corecursive t, Comonad w) => (forall b. Base t (w b) -> w (Base t b)) -> (Base t (EnvT t w a) -> a) -> t -> a Source #

prepro :: Corecursive t => (forall b. Base t b -> Base t b) -> (Base t a -> a) -> t -> a Source #

Fokkinga's prepromorphism

gprepro :: (Corecursive t, Comonad w) => (forall b. Base t (w b) -> w (Base t b)) -> (forall c. Base t c -> Base t c) -> (Base t (w a) -> a) -> t -> a Source #

Instances
Recursive Natural Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

project :: Natural -> Base Natural Natural Source #

cata :: (Base Natural a -> a) -> Natural -> a Source #

para :: (Base Natural (Natural, a) -> a) -> Natural -> a Source #

gpara :: (Corecursive Natural, Comonad w) => (forall b. Base Natural (w b) -> w (Base Natural b)) -> (Base Natural (EnvT Natural w a) -> a) -> Natural -> a Source #

prepro :: Corecursive Natural => (forall b. Base Natural b -> Base Natural b) -> (Base Natural a -> a) -> Natural -> a Source #

gprepro :: (Corecursive Natural, Comonad w) => (forall b. Base Natural (w b) -> w (Base Natural b)) -> (forall c. Base Natural c -> Base Natural c) -> (Base Natural (w a) -> a) -> Natural -> a Source #

Recursive [a] Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

project :: [a] -> Base [a] [a] Source #

cata :: (Base [a] a0 -> a0) -> [a] -> a0 Source #

para :: (Base [a] ([a], a0) -> a0) -> [a] -> a0 Source #

gpara :: (Corecursive [a], Comonad w) => (forall b. Base [a] (w b) -> w (Base [a] b)) -> (Base [a] (EnvT [a] w a0) -> a0) -> [a] -> a0 Source #

prepro :: Corecursive [a] => (forall b. Base [a] b -> Base [a] b) -> (Base [a] a0 -> a0) -> [a] -> a0 Source #

gprepro :: (Corecursive [a], Comonad w) => (forall b. Base [a] (w b) -> w (Base [a] b)) -> (forall c. Base [a] c -> Base [a] c) -> (Base [a] (w a0) -> a0) -> [a] -> a0 Source #

Recursive (Maybe a) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

project :: Maybe a -> Base (Maybe a) (Maybe a) Source #

cata :: (Base (Maybe a) a0 -> a0) -> Maybe a -> a0 Source #

para :: (Base (Maybe a) (Maybe a, a0) -> a0) -> Maybe a -> a0 Source #

gpara :: (Corecursive (Maybe a), Comonad w) => (forall b. Base (Maybe a) (w b) -> w (Base (Maybe a) b)) -> (Base (Maybe a) (EnvT (Maybe a) w a0) -> a0) -> Maybe a -> a0 Source #

prepro :: Corecursive (Maybe a) => (forall b. Base (Maybe a) b -> Base (Maybe a) b) -> (Base (Maybe a) a0 -> a0) -> Maybe a -> a0 Source #

gprepro :: (Corecursive (Maybe a), Comonad w) => (forall b. Base (Maybe a) (w b) -> w (Base (Maybe a) b)) -> (forall c. Base (Maybe a) c -> Base (Maybe a) c) -> (Base (Maybe a) (w a0) -> a0) -> Maybe a -> a0 Source #

Recursive (NonEmpty a) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

project :: NonEmpty a -> Base (NonEmpty a) (NonEmpty a) Source #

cata :: (Base (NonEmpty a) a0 -> a0) -> NonEmpty a -> a0 Source #

para :: (Base (NonEmpty a) (NonEmpty a, a0) -> a0) -> NonEmpty a -> a0 Source #

gpara :: (Corecursive (NonEmpty a), Comonad w) => (forall b. Base (NonEmpty a) (w b) -> w (Base (NonEmpty a) b)) -> (Base (NonEmpty a) (EnvT (NonEmpty a) w a0) -> a0) -> NonEmpty a -> a0 Source #

prepro :: Corecursive (NonEmpty a) => (forall b. Base (NonEmpty a) b -> Base (NonEmpty a) b) -> (Base (NonEmpty a) a0 -> a0) -> NonEmpty a -> a0 Source #

gprepro :: (Corecursive (NonEmpty a), Comonad w) => (forall b. Base (NonEmpty a) (w b) -> w (Base (NonEmpty a) b)) -> (forall c. Base (NonEmpty a) c -> Base (NonEmpty a) c) -> (Base (NonEmpty a) (w a0) -> a0) -> NonEmpty a -> a0 Source #

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

Defined in Data.Functor.Foldable

Methods

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

cata :: (Base (Nu f) a -> a) -> Nu f -> a Source #

para :: (Base (Nu f) (Nu f, a) -> a) -> Nu f -> a Source #

gpara :: (Corecursive (Nu f), Comonad w) => (forall b. Base (Nu f) (w b) -> w (Base (Nu f) b)) -> (Base (Nu f) (EnvT (Nu f) w a) -> a) -> Nu f -> a Source #

prepro :: Corecursive (Nu f) => (forall b. Base (Nu f) b -> Base (Nu f) b) -> (Base (Nu f) a -> a) -> Nu f -> a Source #

gprepro :: (Corecursive (Nu f), Comonad w) => (forall b. Base (Nu f) (w b) -> w (Base (Nu f) b)) -> (forall c. Base (Nu f) c -> Base (Nu f) c) -> (Base (Nu f) (w a) -> a) -> Nu f -> a Source #

Functor f => Recursive (Mu f) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

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

cata :: (Base (Mu f) a -> a) -> Mu f -> a Source #

para :: (Base (Mu f) (Mu f, a) -> a) -> Mu f -> a Source #

gpara :: (Corecursive (Mu f), Comonad w) => (forall b. Base (Mu f) (w b) -> w (Base (Mu f) b)) -> (Base (Mu f) (EnvT (Mu f) w a) -> a) -> Mu f -> a Source #

prepro :: Corecursive (Mu f) => (forall b. Base (Mu f) b -> Base (Mu f) b) -> (Base (Mu f) a -> a) -> Mu f -> a Source #

gprepro :: (Corecursive (Mu f), Comonad w) => (forall b. Base (Mu f) (w b) -> w (Base (Mu f) b)) -> (forall c. Base (Mu f) c -> Base (Mu f) c) -> (Base (Mu f) (w a) -> a) -> Mu f -> a Source #

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

Defined in Data.Functor.Foldable

Methods

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

cata :: (Base (Fix f) a -> a) -> Fix f -> a Source #

para :: (Base (Fix f) (Fix f, a) -> a) -> Fix f -> a Source #

gpara :: (Corecursive (Fix f), Comonad w) => (forall b. Base (Fix f) (w b) -> w (Base (Fix f) b)) -> (Base (Fix f) (EnvT (Fix f) w a) -> a) -> Fix f -> a Source #

prepro :: Corecursive (Fix f) => (forall b. Base (Fix f) b -> Base (Fix f) b) -> (Base (Fix f) a -> a) -> Fix f -> a Source #

gprepro :: (Corecursive (Fix f), Comonad w) => (forall b. Base (Fix f) (w b) -> w (Base (Fix f) b)) -> (forall c. Base (Fix f) c -> Base (Fix f) c) -> (Base (Fix f) (w a) -> a) -> Fix f -> a Source #

Recursive (Either a b) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

project :: Either a b -> Base (Either a b) (Either a b) Source #

cata :: (Base (Either a b) a0 -> a0) -> Either a b -> a0 Source #

para :: (Base (Either a b) (Either a b, a0) -> a0) -> Either a b -> a0 Source #

gpara :: (Corecursive (Either a b), Comonad w) => (forall b0. Base (Either a b) (w b0) -> w (Base (Either a b) b0)) -> (Base (Either a b) (EnvT (Either a b) w a0) -> a0) -> Either a b -> a0 Source #

prepro :: Corecursive (Either a b) => (forall b0. Base (Either a b) b0 -> Base (Either a b) b0) -> (Base (Either a b) a0 -> a0) -> Either a b -> a0 Source #

gprepro :: (Corecursive (Either a b), Comonad w) => (forall b0. Base (Either a b) (w b0) -> w (Base (Either a b) b0)) -> (forall c. Base (Either a b) c -> Base (Either a b) c) -> (Base (Either a b) (w a0) -> a0) -> Either a b -> a0 Source #

Functor f => Recursive (Cofree f a) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

project :: Cofree f a -> Base (Cofree f a) (Cofree f a) Source #

cata :: (Base (Cofree f a) a0 -> a0) -> Cofree f a -> a0 Source #

para :: (Base (Cofree f a) (Cofree f a, a0) -> a0) -> Cofree f a -> a0 Source #

gpara :: (Corecursive (Cofree f a), Comonad w) => (forall b. Base (Cofree f a) (w b) -> w (Base (Cofree f a) b)) -> (Base (Cofree f a) (EnvT (Cofree f a) w a0) -> a0) -> Cofree f a -> a0 Source #

prepro :: Corecursive (Cofree f a) => (forall b. Base (Cofree f a) b -> Base (Cofree f a) b) -> (Base (Cofree f a) a0 -> a0) -> Cofree f a -> a0 Source #

gprepro :: (Corecursive (Cofree f a), Comonad w) => (forall b. Base (Cofree f a) (w b) -> w (Base (Cofree f a) b)) -> (forall c. Base (Cofree f a) c -> Base (Cofree f a) c) -> (Base (Cofree f a) (w a0) -> a0) -> Cofree f a -> a0 Source #

Functor f => Recursive (F f a) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

project :: F f a -> Base (F f a) (F f a) Source #

cata :: (Base (F f a) a0 -> a0) -> F f a -> a0 Source #

para :: (Base (F f a) (F f a, a0) -> a0) -> F f a -> a0 Source #

gpara :: (Corecursive (F f a), Comonad w) => (forall b. Base (F f a) (w b) -> w (Base (F f a) b)) -> (Base (F f a) (EnvT (F f a) w a0) -> a0) -> F f a -> a0 Source #

prepro :: Corecursive (F f a) => (forall b. Base (F f a) b -> Base (F f a) b) -> (Base (F f a) a0 -> a0) -> F f a -> a0 Source #

gprepro :: (Corecursive (F f a), Comonad w) => (forall b. Base (F f a) (w b) -> w (Base (F f a) b)) -> (forall c. Base (F f a) c -> Base (F f a) c) -> (Base (F f a) (w a0) -> a0) -> F f a -> a0 Source #

Functor f => Recursive (Free f a) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

project :: Free f a -> Base (Free f a) (Free f a) Source #

cata :: (Base (Free f a) a0 -> a0) -> Free f a -> a0 Source #

para :: (Base (Free f a) (Free f a, a0) -> a0) -> Free f a -> a0 Source #

gpara :: (Corecursive (Free f a), Comonad w) => (forall b. Base (Free f a) (w b) -> w (Base (Free f a) b)) -> (Base (Free f a) (EnvT (Free f a) w a0) -> a0) -> Free f a -> a0 Source #

prepro :: Corecursive (Free f a) => (forall b. Base (Free f a) b -> Base (Free f a) b) -> (Base (Free f a) a0 -> a0) -> Free f a -> a0 Source #

gprepro :: (Corecursive (Free f a), Comonad w) => (forall b. Base (Free f a) (w b) -> w (Base (Free f a) b)) -> (forall c. Base (Free f a) c -> Base (Free f a) c) -> (Base (Free f a) (w a0) -> a0) -> Free f a -> a0 Source #

(Functor m, Functor f) => Recursive (FreeT f m a) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

project :: FreeT f m a -> Base (FreeT f m a) (FreeT f m a) Source #

cata :: (Base (FreeT f m a) a0 -> a0) -> FreeT f m a -> a0 Source #

para :: (Base (FreeT f m a) (FreeT f m a, a0) -> a0) -> FreeT f m a -> a0 Source #

gpara :: (Corecursive (FreeT f m a), Comonad w) => (forall b. Base (FreeT f m a) (w b) -> w (Base (FreeT f m a) b)) -> (Base (FreeT f m a) (EnvT (FreeT f m a) w a0) -> a0) -> FreeT f m a -> a0 Source #

prepro :: Corecursive (FreeT f m a) => (forall b. Base (FreeT f m a) b -> Base (FreeT f m a) b) -> (Base (FreeT f m a) a0 -> a0) -> FreeT f m a -> a0 Source #

gprepro :: (Corecursive (FreeT f m a), Comonad w) => (forall b. Base (FreeT f m a) (w b) -> w (Base (FreeT f m a) b)) -> (forall c. Base (FreeT f m a) c -> Base (FreeT f m a) c) -> (Base (FreeT f m a) (w a0) -> a0) -> FreeT f m a -> a0 Source #

(Functor w, Functor f) => Recursive (CofreeT f w a) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

project :: CofreeT f w a -> Base (CofreeT f w a) (CofreeT f w a) Source #

cata :: (Base (CofreeT f w a) a0 -> a0) -> CofreeT f w a -> a0 Source #

para :: (Base (CofreeT f w a) (CofreeT f w a, a0) -> a0) -> CofreeT f w a -> a0 Source #

gpara :: (Corecursive (CofreeT f w a), Comonad w0) => (forall b. Base (CofreeT f w a) (w0 b) -> w0 (Base (CofreeT f w a) b)) -> (Base (CofreeT f w a) (EnvT (CofreeT f w a) w0 a0) -> a0) -> CofreeT f w a -> a0 Source #

prepro :: Corecursive (CofreeT f w a) => (forall b. Base (CofreeT f w a) b -> Base (CofreeT f w a) b) -> (Base (CofreeT f w a) a0 -> a0) -> CofreeT f w a -> a0 Source #

gprepro :: (Corecursive (CofreeT f w a), Comonad w0) => (forall b. Base (CofreeT f w a) (w0 b) -> w0 (Base (CofreeT f w a) b)) -> (forall c. Base (CofreeT f w a) c -> Base (CofreeT f w a) c) -> (Base (CofreeT f w a) (w0 a0) -> a0) -> CofreeT f w a -> a0 Source #

Combinators

gapo :: Corecursive t => (b -> Base t b) -> (a -> Base t (Either b a)) -> a -> t Source #

gcata Source #

Arguments

:: (Recursive t, Comonad w) 
=> (forall b. Base t (w b) -> w (Base t b))

a distributive law

-> (Base t (w a) -> a)

a (Base t)-w-algebra

-> t

fixed point

-> a 

A generalized catamorphism

zygo :: Recursive t => (Base t b -> b) -> (Base t (b, a) -> a) -> t -> a Source #

gzygo :: (Recursive t, Comonad w) => (Base t b -> b) -> (forall c. Base t (w c) -> w (Base t c)) -> (Base t (EnvT b w a) -> a) -> t -> a Source #

histo :: Recursive t => (Base t (Cofree (Base t) a) -> a) -> t -> a Source #

Course-of-value iteration

ghisto :: (Recursive t, Comonad w) => (forall b. Base t (w b) -> w (Base t b)) -> (Base t (CofreeT (Base t) w a) -> a) -> t -> a Source #

futu :: Corecursive t => (a -> Base t (Free (Base t) a)) -> a -> t Source #

gfutu :: (Corecursive t, Functor m, Monad m) => (forall b. m (Base t b) -> Base t (m b)) -> (a -> Base t (FreeT (Base t) m a)) -> a -> t Source #

chrono :: Functor f => (f (Cofree f b) -> b) -> (a -> f (Free f a)) -> a -> b Source #

gchrono :: (Functor f, Functor w, Functor m, Comonad w, Monad m) => (forall c. f (w c) -> w (f c)) -> (forall c. m (f c) -> f (m c)) -> (f (CofreeT f w b) -> b) -> (a -> f (FreeT f m a)) -> a -> b Source #

Distributive laws

distCata :: Functor f => f (Identity a) -> Identity (f a) Source #

distPara :: Corecursive t => Base t (t, a) -> (t, Base t a) Source #

distParaT :: (Corecursive t, Comonad w) => (forall b. Base t (w b) -> w (Base t b)) -> Base t (EnvT t w a) -> EnvT t w (Base t a) Source #

distZygo Source #

Arguments

:: Functor f 
=> (f b -> b) 
-> f (b, a) -> (b, f a)

A distributive for semi-mutual recursion

distZygoT :: (Functor f, Comonad w) => (f b -> b) -> (forall c. f (w c) -> w (f c)) -> f (EnvT b w a) -> EnvT b w (f a) Source #

distHisto :: Functor f => f (Cofree f a) -> Cofree f (f a) Source #

distGHisto :: (Functor f, Functor h) => (forall b. f (h b) -> h (f b)) -> f (CofreeT f h a) -> CofreeT f h (f a) Source #

distFutu :: Functor f => Free f (f a) -> f (Free f a) Source #

distGFutu :: (Functor f, Functor h) => (forall b. h (f b) -> f (h b)) -> FreeT f h (f a) -> f (FreeT f h a) Source #

Unfolding

class Functor (Base t) => Corecursive t where Source #

Minimal complete definition

Nothing

Methods

embed :: Base t t -> t Source #

embed :: (Generic t, Generic (Base t t), GCoerce (Rep (Base t t)) (Rep t)) => Base t t -> t Source #

ana Source #

Arguments

:: (a -> Base t a)

a (Base t)-coalgebra

-> a

seed

-> t

resulting fixed point

apo :: (a -> Base t (Either t a)) -> a -> t Source #

postpro :: Recursive t => (forall b. Base t b -> Base t b) -> (a -> Base t a) -> a -> t Source #

Fokkinga's postpromorphism

gpostpro :: (Recursive t, Monad m) => (forall b. m (Base t b) -> Base t (m b)) -> (forall c. Base t c -> Base t c) -> (a -> Base t (m a)) -> a -> t Source #

A generalized postpromorphism

Instances
Corecursive Natural Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

embed :: Base Natural Natural -> Natural Source #

ana :: (a -> Base Natural a) -> a -> Natural Source #

apo :: (a -> Base Natural (Either Natural a)) -> a -> Natural Source #

postpro :: Recursive Natural => (forall b. Base Natural b -> Base Natural b) -> (a -> Base Natural a) -> a -> Natural Source #

gpostpro :: (Recursive Natural, Monad m) => (forall b. m (Base Natural b) -> Base Natural (m b)) -> (forall c. Base Natural c -> Base Natural c) -> (a -> Base Natural (m a)) -> a -> Natural Source #

Corecursive [a] Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

embed :: Base [a] [a] -> [a] Source #

ana :: (a0 -> Base [a] a0) -> a0 -> [a] Source #

apo :: (a0 -> Base [a] (Either [a] a0)) -> a0 -> [a] Source #

postpro :: Recursive [a] => (forall b. Base [a] b -> Base [a] b) -> (a0 -> Base [a] a0) -> a0 -> [a] Source #

gpostpro :: (Recursive [a], Monad m) => (forall b. m (Base [a] b) -> Base [a] (m b)) -> (forall c. Base [a] c -> Base [a] c) -> (a0 -> Base [a] (m a0)) -> a0 -> [a] Source #

Corecursive (Maybe a) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

embed :: Base (Maybe a) (Maybe a) -> Maybe a Source #

ana :: (a0 -> Base (Maybe a) a0) -> a0 -> Maybe a Source #

apo :: (a0 -> Base (Maybe a) (Either (Maybe a) a0)) -> a0 -> Maybe a Source #

postpro :: Recursive (Maybe a) => (forall b. Base (Maybe a) b -> Base (Maybe a) b) -> (a0 -> Base (Maybe a) a0) -> a0 -> Maybe a Source #

gpostpro :: (Recursive (Maybe a), Monad m) => (forall b. m (Base (Maybe a) b) -> Base (Maybe a) (m b)) -> (forall c. Base (Maybe a) c -> Base (Maybe a) c) -> (a0 -> Base (Maybe a) (m a0)) -> a0 -> Maybe a Source #

Corecursive (NonEmpty a) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

embed :: Base (NonEmpty a) (NonEmpty a) -> NonEmpty a Source #

ana :: (a0 -> Base (NonEmpty a) a0) -> a0 -> NonEmpty a Source #

apo :: (a0 -> Base (NonEmpty a) (Either (NonEmpty a) a0)) -> a0 -> NonEmpty a Source #

postpro :: Recursive (NonEmpty a) => (forall b. Base (NonEmpty a) b -> Base (NonEmpty a) b) -> (a0 -> Base (NonEmpty a) a0) -> a0 -> NonEmpty a Source #

gpostpro :: (Recursive (NonEmpty a), Monad m) => (forall b. m (Base (NonEmpty a) b) -> Base (NonEmpty a) (m b)) -> (forall c. Base (NonEmpty a) c -> Base (NonEmpty a) c) -> (a0 -> Base (NonEmpty a) (m a0)) -> a0 -> NonEmpty a Source #

Functor f => Corecursive (Nu f) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

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

ana :: (a -> Base (Nu f) a) -> a -> Nu f Source #

apo :: (a -> Base (Nu f) (Either (Nu f) a)) -> a -> Nu f Source #

postpro :: Recursive (Nu f) => (forall b. Base (Nu f) b -> Base (Nu f) b) -> (a -> Base (Nu f) a) -> a -> Nu f Source #

gpostpro :: (Recursive (Nu f), Monad m) => (forall b. m (Base (Nu f) b) -> Base (Nu f) (m b)) -> (forall c. Base (Nu f) c -> Base (Nu f) c) -> (a -> Base (Nu f) (m a)) -> a -> Nu f Source #

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

Defined in Data.Functor.Foldable

Methods

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

ana :: (a -> Base (Mu f) a) -> a -> Mu f Source #

apo :: (a -> Base (Mu f) (Either (Mu f) a)) -> a -> Mu f Source #

postpro :: Recursive (Mu f) => (forall b. Base (Mu f) b -> Base (Mu f) b) -> (a -> Base (Mu f) a) -> a -> Mu f Source #

gpostpro :: (Recursive (Mu f), Monad m) => (forall b. m (Base (Mu f) b) -> Base (Mu f) (m b)) -> (forall c. Base (Mu f) c -> Base (Mu f) c) -> (a -> Base (Mu f) (m a)) -> a -> Mu f Source #

Functor f => Corecursive (Fix f) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

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

ana :: (a -> Base (Fix f) a) -> a -> Fix f Source #

apo :: (a -> Base (Fix f) (Either (Fix f) a)) -> a -> Fix f Source #

postpro :: Recursive (Fix f) => (forall b. Base (Fix f) b -> Base (Fix f) b) -> (a -> Base (Fix f) a) -> a -> Fix f Source #

gpostpro :: (Recursive (Fix f), Monad m) => (forall b. m (Base (Fix f) b) -> Base (Fix f) (m b)) -> (forall c. Base (Fix f) c -> Base (Fix f) c) -> (a -> Base (Fix f) (m a)) -> a -> Fix f Source #

Corecursive (Either a b) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

embed :: Base (Either a b) (Either a b) -> Either a b Source #

ana :: (a0 -> Base (Either a b) a0) -> a0 -> Either a b Source #

apo :: (a0 -> Base (Either a b) (Either (Either a b) a0)) -> a0 -> Either a b Source #

postpro :: Recursive (Either a b) => (forall b0. Base (Either a b) b0 -> Base (Either a b) b0) -> (a0 -> Base (Either a b) a0) -> a0 -> Either a b Source #

gpostpro :: (Recursive (Either a b), Monad m) => (forall b0. m (Base (Either a b) b0) -> Base (Either a b) (m b0)) -> (forall c. Base (Either a b) c -> Base (Either a b) c) -> (a0 -> Base (Either a b) (m a0)) -> a0 -> Either a b Source #

Functor f => Corecursive (Cofree f a) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

embed :: Base (Cofree f a) (Cofree f a) -> Cofree f a Source #

ana :: (a0 -> Base (Cofree f a) a0) -> a0 -> Cofree f a Source #

apo :: (a0 -> Base (Cofree f a) (Either (Cofree f a) a0)) -> a0 -> Cofree f a Source #

postpro :: Recursive (Cofree f a) => (forall b. Base (Cofree f a) b -> Base (Cofree f a) b) -> (a0 -> Base (Cofree f a) a0) -> a0 -> Cofree f a Source #

gpostpro :: (Recursive (Cofree f a), Monad m) => (forall b. m (Base (Cofree f a) b) -> Base (Cofree f a) (m b)) -> (forall c. Base (Cofree f a) c -> Base (Cofree f a) c) -> (a0 -> Base (Cofree f a) (m a0)) -> a0 -> Cofree f a Source #

Functor f => Corecursive (F f a) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

embed :: Base (F f a) (F f a) -> F f a Source #

ana :: (a0 -> Base (F f a) a0) -> a0 -> F f a Source #

apo :: (a0 -> Base (F f a) (Either (F f a) a0)) -> a0 -> F f a Source #

postpro :: Recursive (F f a) => (forall b. Base (F f a) b -> Base (F f a) b) -> (a0 -> Base (F f a) a0) -> a0 -> F f a Source #

gpostpro :: (Recursive (F f a), Monad m) => (forall b. m (Base (F f a) b) -> Base (F f a) (m b)) -> (forall c. Base (F f a) c -> Base (F f a) c) -> (a0 -> Base (F f a) (m a0)) -> a0 -> F f a Source #

Functor f => Corecursive (Free f a) Source #

It may be better to work with the instance for F directly.

Instance details

Defined in Data.Functor.Foldable

Methods

embed :: Base (Free f a) (Free f a) -> Free f a Source #

ana :: (a0 -> Base (Free f a) a0) -> a0 -> Free f a Source #

apo :: (a0 -> Base (Free f a) (Either (Free f a) a0)) -> a0 -> Free f a Source #

postpro :: Recursive (Free f a) => (forall b. Base (Free f a) b -> Base (Free f a) b) -> (a0 -> Base (Free f a) a0) -> a0 -> Free f a Source #

gpostpro :: (Recursive (Free f a), Monad m) => (forall b. m (Base (Free f a) b) -> Base (Free f a) (m b)) -> (forall c. Base (Free f a) c -> Base (Free f a) c) -> (a0 -> Base (Free f a) (m a0)) -> a0 -> Free f a Source #

(Functor m, Functor f) => Corecursive (FreeT f m a) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

embed :: Base (FreeT f m a) (FreeT f m a) -> FreeT f m a Source #

ana :: (a0 -> Base (FreeT f m a) a0) -> a0 -> FreeT f m a Source #

apo :: (a0 -> Base (FreeT f m a) (Either (FreeT f m a) a0)) -> a0 -> FreeT f m a Source #

postpro :: Recursive (FreeT f m a) => (forall b. Base (FreeT f m a) b -> Base (FreeT f m a) b) -> (a0 -> Base (FreeT f m a) a0) -> a0 -> FreeT f m a Source #

gpostpro :: (Recursive (FreeT f m a), Monad m0) => (forall b. m0 (Base (FreeT f m a) b) -> Base (FreeT f m a) (m0 b)) -> (forall c. Base (FreeT f m a) c -> Base (FreeT f m a) c) -> (a0 -> Base (FreeT f m a) (m0 a0)) -> a0 -> FreeT f m a Source #

(Functor w, Functor f) => Corecursive (CofreeT f w a) Source # 
Instance details

Defined in Data.Functor.Foldable

Methods

embed :: Base (CofreeT f w a) (CofreeT f w a) -> CofreeT f w a Source #

ana :: (a0 -> Base (CofreeT f w a) a0) -> a0 -> CofreeT f w a Source #

apo :: (a0 -> Base (CofreeT f w a) (Either (CofreeT f w a) a0)) -> a0 -> CofreeT f w a Source #

postpro :: Recursive (CofreeT f w a) => (forall b. Base (CofreeT f w a) b -> Base (CofreeT f w a) b) -> (a0 -> Base (CofreeT f w a) a0) -> a0 -> CofreeT f w a Source #

gpostpro :: (Recursive (CofreeT f w a), Monad m) => (forall b. m (Base (CofreeT f w a) b) -> Base (CofreeT f w a) (m b)) -> (forall c. Base (CofreeT f w a) c -> Base (CofreeT f w a) c) -> (a0 -> Base (CofreeT f w a) (m a0)) -> a0 -> CofreeT f w a Source #

Combinators

gana Source #

Arguments

:: (Corecursive t, Monad m) 
=> (forall b. m (Base t b) -> Base t (m b))

a distributive law

-> (a -> Base t (m a))

a (Base t)-m-coalgebra

-> a

seed

-> t 

A generalized anamorphism

Distributive laws

distAna :: Functor f => Identity (f a) -> f (Identity a) Source #

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

distGApo :: Functor f => (b -> f b) -> Either b (f a) -> f (Either b a) Source #

distGApoT :: (Functor f, Functor m) => (b -> f b) -> (forall c. m (f c) -> f (m c)) -> ExceptT b m (f a) -> f (ExceptT b m a) Source #

Refolding

hylo :: Functor f => (f b -> b) -> (a -> f a) -> a -> b Source #

ghylo :: (Comonad w, Functor f, Monad m) => (forall c. f (w c) -> w (f c)) -> (forall d. m (f d) -> f (m d)) -> (f (w b) -> b) -> (a -> f (m a)) -> a -> b Source #

A generalized hylomorphism

Changing representation

hoist :: (Recursive s, Corecursive t) => (forall a. Base s a -> Base t a) -> s -> t Source #

refix :: (Recursive s, Corecursive t, Base s ~ Base t) => s -> t Source #

Common names

fold :: Recursive t => (Base t a -> a) -> t -> a Source #

gfold Source #

Arguments

:: (Recursive t, Comonad w) 
=> (forall b. Base t (w b) -> w (Base t b))

a distributive law

-> (Base t (w a) -> a)

a (Base t)-w-algebra

-> t

fixed point

-> a 

A generalized catamorphism

unfold :: Corecursive t => (a -> Base t a) -> a -> t Source #

gunfold Source #

Arguments

:: (Corecursive t, Monad m) 
=> (forall b. m (Base t b) -> Base t (m b))

a distributive law

-> (a -> Base t (m a))

a (Base t)-m-coalgebra

-> a

seed

-> t 

A generalized anamorphism

refold :: Functor f => (f b -> b) -> (a -> f a) -> a -> b Source #

grefold :: (Comonad w, Functor f, Monad m) => (forall c. f (w c) -> w (f c)) -> (forall d. m (f d) -> f (m d)) -> (f (w b) -> b) -> (a -> f (m a)) -> a -> b Source #

A generalized hylomorphism

Mendler-style

mcata :: (forall y. (y -> c) -> f y -> c) -> Fix f -> c Source #

Mendler-style iteration

mhisto :: (forall y. (y -> c) -> (y -> f y) -> f y -> c) -> Fix f -> c Source #

Mendler-style course-of-value iteration

Elgot (co)algebras

elgot :: Functor f => (f a -> a) -> (b -> Either a (f b)) -> b -> a Source #

Elgot algebras

coelgot :: Functor f => ((a, f b) -> b) -> (a -> f a) -> a -> b Source #

Zygohistomorphic prepromorphisms

zygoHistoPrepro :: (Corecursive t, Recursive t) => (Base t b -> b) -> (forall c. Base t c -> Base t c) -> (Base t (EnvT b (Cofree (Base t)) a) -> a) -> t -> a Source #

Zygohistomorphic prepromorphisms:

A corrected and modernized version of http://www.haskell.org/haskellwiki/Zygohistomorphic_prepromorphisms

Effectful combinators

cataA :: Recursive t => (Base t (f a) -> f a) -> t -> f a Source #

Effectful fold.

This is a type specialisation of cata.

An example terminating a recursion immediately:

>>> cataA (\alg -> case alg of { Nil -> pure (); Cons a _ -> Const [a] })  "hello"
Const "h"

transverse :: (Recursive s, Corecursive t, Functor f) => (forall a. Base s (f a) -> f (Base t a)) -> s -> f t Source #

An effectful version of hoist.

Properties:

transverse sequenceA = pure

Examples:

The weird type of first argument allows user to decide an order of sequencing:

>>> transverse (\x -> print (void x) *> sequence x) "foo" :: IO String
Cons 'f' ()
Cons 'o' ()
Cons 'o' ()
Nil
"foo"
>>> transverse (\x -> sequence x <* print (void x)) "foo" :: IO String
Nil
Cons 'o' ()
Cons 'o' ()
Cons 'f' ()
"foo"

cotransverse :: (Recursive s, Corecursive t, Functor f) => (forall a. f (Base s a) -> Base t (f a)) -> f s -> t Source #

A coeffectful version of hoist.

Properties:

cotransverse distAna = runIdentity

Examples:

Stateful transformations:

>>> :{
cotransverse
  (\(u, b) -> case b of
    Nil -> Nil
    Cons x a -> Cons (if u then toUpper x else x) (not u, a))
  (True, "foobar") :: String
:}
"FoObAr"

We can implement a variant of zipWith

>>> data Pair a = Pair a a deriving Functor
>>> :{
let zipWith' :: (a -> a -> b) -> [a] -> [a] -> [b]
    zipWith' f xs ys = cotransverse g (Pair xs ys) where
      g (Pair Nil        _)          = Nil
      g (Pair _          Nil)        = Nil
      g (Pair (Cons x a) (Cons y b)) = Cons (f x y) (Pair a b)
    :}
>>> zipWith' (*) [1,2,3] [4,5,6]
[4,10,18]
>>> zipWith' (*) [1,2,3] [4,5,6,8]
[4,10,18]
>>> zipWith' (*) [1,2,3,3] [4,5,6]
[4,10,18]