variant-1.0: Variant and EADT
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Variant.Functor

Description

Functor and recursion schemes

Simple API is intended to be easier to understand (e.g. they don't use xxmorphism and xxxalgebra jargon but tree-traversal-like terms).

Synopsis

Simple API

type BottomUpT a f = f a -> a Source #

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

Bottom-up traversal (catamorphism)

type BottomUpOrigT t a f = f (t, a) -> a Source #

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

Bottom-up traversal with original value (paramorphism)

type TopDownStopT a f = f a -> Either (f a) a Source #

topDownStop :: (Recursive t, Corecursive t) => (Base t t -> Either (Base t t) t) -> t -> t Source #

Perform a top-down traversal

Right: stop the traversal ("right" value obtained) Left: continue the traversal recursively on the new value

Recursion schemes

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

A recursive datatype which can be rolled up one recursion layer at a time.

For example, a value of type ListF a [a] can be rolled up into a [a]. This [a] can then be used in a Cons to construct another ListF a [a], which can be rolled up as well, and so on.

Typically, Corecursive types also have a Recursive instance, in which case embed and project are inverses.

Minimal complete definition

Nothing

Methods

embed :: Base t t -> t #

Roll up a single recursion layer.

>>> embed (Cons 1 [2,3])
[1,2,3]

ana #

Arguments

:: (a -> Base t a)

a (Base t)-coalgebra

-> a

seed

-> t

resulting fixed point

An alias for unfold.

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

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

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 #

A generalized postpromorphism

Instances

Instances details
Corecursive Natural 
Instance details

Defined in Data.Functor.Foldable

Methods

embed :: Base Natural Natural -> Natural #

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

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

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

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 #

Corecursive (NonEmpty a) 
Instance details

Defined in Data.Functor.Foldable

Methods

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

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

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

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

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 #

Corecursive (Tree a) 
Instance details

Defined in Data.Functor.Foldable

Methods

embed :: Base (Tree a) (Tree a) -> Tree a #

ana :: (a0 -> Base (Tree a) a0) -> a0 -> Tree a #

apo :: (a0 -> Base (Tree a) (Either (Tree a) a0)) -> a0 -> Tree a #

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

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

Functor f => Corecursive (Fix f) 
Instance details

Defined in Data.Functor.Foldable

Methods

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

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

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

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

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 #

Functor f => Corecursive (Mu f) 
Instance details

Defined in Data.Functor.Foldable

Methods

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

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

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

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

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 #

Functor f => Corecursive (Nu f) 
Instance details

Defined in Data.Functor.Foldable

Methods

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

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

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

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

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 #

Functor (VariantF fs) => Corecursive (EADT fs) Source # 
Instance details

Defined in Data.Variant.EADT

Methods

embed :: Base (EADT fs) (EADT fs) -> EADT fs #

ana :: (a -> Base (EADT fs) a) -> a -> EADT fs #

apo :: (a -> Base (EADT fs) (Either (EADT fs) a)) -> a -> EADT fs #

postpro :: Recursive (EADT fs) => (forall b. Base (EADT fs) b -> Base (EADT fs) b) -> (a -> Base (EADT fs) a) -> a -> EADT fs #

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

Corecursive (Maybe a) 
Instance details

Defined in Data.Functor.Foldable

Methods

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

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

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

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

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 #

Corecursive [a] 
Instance details

Defined in Data.Functor.Foldable

Methods

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

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

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

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

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

Corecursive (Either a b) 
Instance details

Defined in Data.Functor.Foldable

Methods

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

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

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

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 #

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 #

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

Defined in Data.Functor.Foldable

Methods

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

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

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

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 #

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 #

Functor f => Corecursive (Free f a)

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 #

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

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

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 #

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 #

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

Defined in Data.Functor.Foldable

Methods

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

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

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

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 #

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 #

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

Defined in Data.Functor.Foldable

Methods

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

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

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

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 #

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 #

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

Defined in Data.Functor.Foldable

Methods

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

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

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

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 #

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 #

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

A recursive datatype which can be unrolled one recursion layer at a time.

For example, a value of type [a] can be unrolled into a ListF a [a]. If that unrolled value is a Cons, it contains another [a] which can be unrolled as well, and so on.

Typically, Recursive types also have a Corecursive instance, in which case project and embed are inverses.

Minimal complete definition

Nothing

Methods

project :: t -> Base t t #

Unroll a single recursion layer.

>>> project [1,2,3]
Cons 1 [2,3]

cata :: (Base t a -> a) -> t -> a #

An alias for fold.

fold is by far the most common recursion-scheme, because working one layer at a time is the most common strategy for writing a recursive function. But there are also other, rarer strategies. Researchers have given names to the most common strategies, and their name for fold is "catamorphism". They also give its Base t a -> a argument a special name, "(Base t)-algebra". More generally, a function of the form f a -> a is called an "f-algebra".

The names might seem intimidating at first, but using the standard nomenclature has benefits. If you program with others, it can be useful to have a shared vocabulary to refer to those recursion patterns. For example, you can discuss which type of recursion is the most appropriate for the problem at hand. Names can also help to structure your thoughts while writing recursive functions.

The rest of this module lists a few of the other recursion-schemes which are common enough to have a name. In this section, we restrict our attention to those which fold a recursive structure down to a value. In the examples all functions will be of type Tree Int -> String.

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

A variant of cata in which recursive positions also include the original sub-tree, in addition to the result of folding that sub-tree.

For our running example, let's add a number to each node indicating how many children are below it. To do so, we will need to count those nodes from the original sub-tree.

>>> :{
let pprint4 :: Tree Int -> String
    pprint4 = flip runReader 0 . para go
      where
        go :: TreeF Int (Tree Int, Reader Int String)
           -> Reader Int String
        go (NodeF i trss) = do
          -- trss :: [(Tree Int, Reader Int String)]
          -- ts   :: [Tree Int]
          -- rss  :: [Reader Int String]
          -- ss   :: [String]
          let (ts, rss) = unzip trss
          let count = sum $ fmap length ts
          ss <- local (+ 2) $ sequence rss
          indent <- ask
          let s = replicate indent ' '
               ++ "* " ++ show i
               ++ " (" ++ show count ++ ")"
          pure $ intercalate "\n" (s : ss)
:}
>>> putStrLn $ pprint4 myTree
* 0 (7)
  * 1 (0)
  * 2 (0)
  * 3 (4)
    * 31 (3)
      * 311 (2)
        * 3111 (0)
        * 3112 (0)

One common use for para is to construct a new tree which reuses most of the sub-trees from the original. In the following example, we insert a new node under the leftmost leaf. This requires allocating new nodes along a path from the root to that leaf, while keeping every other sub-tree untouched.

>>> :{
let insertLeftmost :: Int -> Tree Int -> Tree Int
    insertLeftmost new = para go
      where
        go :: TreeF Int (Tree Int, Tree Int)
           -> Tree Int
        go (NodeF i []) = Node i [Node new []]
        go (NodeF i ((_orig, recur) : tts))
            -- tts :: [(Tree Int, Tree Int)]
          = let (origs, _recurs) = unzip tts
            in Node i (recur : origs)
:}
>>> putStrLn $ pprint4 $ insertLeftmost 999 myTree
* 0 (8)
  * 1 (1)
    * 999 (0)
  * 2 (0)
  * 3 (4)
    * 31 (3)
      * 311 (2)
        * 3111 (0)
        * 3112 (0)

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

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

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 #

Instances

Instances details
Recursive Natural 
Instance details

Defined in Data.Functor.Foldable

Methods

project :: Natural -> Base Natural Natural #

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

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

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

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

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 #

Recursive (NonEmpty a) 
Instance details

Defined in Data.Functor.Foldable

Methods

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

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

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

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 #

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

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 #

Recursive (Tree a) 
Instance details

Defined in Data.Functor.Foldable

Methods

project :: Tree a -> Base (Tree a) (Tree a) #

cata :: (Base (Tree a) a0 -> a0) -> Tree a -> a0 #

para :: (Base (Tree a) (Tree a, a0) -> a0) -> Tree a -> a0 #

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

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

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

Functor f => Recursive (Fix f) 
Instance details

Defined in Data.Functor.Foldable

Methods

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

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

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

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 #

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

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 #

Functor f => Recursive (Mu f) 
Instance details

Defined in Data.Functor.Foldable

Methods

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

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

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

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 #

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

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 #

Functor f => Recursive (Nu f) 
Instance details

Defined in Data.Functor.Foldable

Methods

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

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

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

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 #

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

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 #

Functor (VariantF fs) => Recursive (EADT fs) Source # 
Instance details

Defined in Data.Variant.EADT

Methods

project :: EADT fs -> Base (EADT fs) (EADT fs) #

cata :: (Base (EADT fs) a -> a) -> EADT fs -> a #

para :: (Base (EADT fs) (EADT fs, a) -> a) -> EADT fs -> a #

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

prepro :: Corecursive (EADT fs) => (forall b. Base (EADT fs) b -> Base (EADT fs) b) -> (Base (EADT fs) a -> a) -> EADT fs -> a #

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

Recursive (Maybe a) 
Instance details

Defined in Data.Functor.Foldable

Methods

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

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

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

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 #

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

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 #

Recursive [a] 
Instance details

Defined in Data.Functor.Foldable

Methods

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

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

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

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

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

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 #

Recursive (Either a b) 
Instance details

Defined in Data.Functor.Foldable

Methods

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

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

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

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 #

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 #

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 #

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

Defined in Data.Functor.Foldable

Methods

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

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

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

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 #

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 #

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 #

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

Defined in Data.Functor.Foldable

Methods

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

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

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

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 #

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 #

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 #

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

Defined in Data.Functor.Foldable

Methods

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

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

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

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 #

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 #

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 #

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

Defined in Data.Functor.Foldable

Methods

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

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

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

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 #

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 #

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 #

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

Defined in Data.Functor.Foldable

Methods

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

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

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

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 #

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 #

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 #

type family Base t :: Type -> Type #

Obtain the base functor for a recursive datatype.

The core idea of this library is that instead of writing recursive functions on a recursive datatype, we prefer to write non-recursive functions on a related, non-recursive datatype we call the "base functor".

For example, [a] is a recursive type, and its corresponding base functor is ListF a:

data ListF a b = Nil | Cons a b
type instance Base [a] = ListF a

The relationship between those two types is that if we replace b with ListF a, we obtain a type which is isomorphic to [a].

Instances

Instances details
type Base Natural 
Instance details

Defined in Data.Functor.Foldable

type Base (NonEmpty a) 
Instance details

Defined in Data.Functor.Foldable

type Base (NonEmpty a) = NonEmptyF a
type Base (Tree a) 
Instance details

Defined in Data.Functor.Foldable

type Base (Tree a) = TreeF a
type Base (Fix f) 
Instance details

Defined in Data.Functor.Foldable

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

Defined in Data.Functor.Foldable

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

Defined in Data.Functor.Foldable

type Base (Nu f) = f
type Base (EADT fs) Source # 
Instance details

Defined in Data.Variant.EADT

type Base (EADT fs) = VariantF fs
type Base (Maybe a)

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 [a] 
Instance details

Defined in Data.Functor.Foldable

type Base [a] = ListF a
type Base (Either a b)

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)

Cofree comonads are Recursive/Corecursive

Instance details

Defined in Data.Functor.Foldable

type Base (Cofree f a) = CofreeF f a
type Base (Free f a)

Free monads are Recursive/Corecursive

Instance details

Defined in Data.Functor.Foldable

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

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 (CofreeT f w a)

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)
type Base (FreeT f m a)

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 (VariantF xs a) Source # 
Instance details

Defined in Data.Variant.VariantF

type Base (VariantF xs a) = VariantF xs

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

Folds a recursive type down to a value, one layer at a time.

>>> :{
let mySum :: [Int] -> Int
    mySum = fold $ \case
      Nil -> 0
      Cons x sumXs -> x + sumXs
:}
>>> mySum [10,11,12]
33

In our running example, one layer consists of an Int and a list of recursive positions. In Tree Int, those recursive positions contain sub-trees of type Tree Int. Since we are working one layer at a time, the Base t a -> a function is not given a Tree Int, but a TreeF Int String. That is, each recursive position contains the String resulting from recursively folding the corresponding sub-tree.

>>> :{
let pprint1 :: Tree Int -> String
    pprint1 = fold $ \case
      NodeF i [] -> show i
      NodeF i ss -> show i ++ ": [" ++ intercalate ", " ss ++ "]"
:}
>>> putStrLn $ pprint1 myTree
0: [1, 2, 3: [31: [311: [3111, 3112]]]]

More generally, the t argument is the recursive value, the a is the final result, and the Base t a -> a function explains how to reduce a single layer full of recursive results down to a result.

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

A generalization of unfoldr. The starting seed is expanded into a base functor whose recursive positions contain more seeds, which are themselves expanded, and so on.

>>> :{
>>> let ourEnumFromTo :: Int -> Int -> [Int]
>>> ourEnumFromTo lo hi = ana go lo where
>>> go i = if i > hi then Nil else Cons i (i + 1)
>>> :}
>>> ourEnumFromTo 1 4
[1,2,3,4]

gunfold #

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 #

An optimized version of fold f . unfold g.

Useful when your recursion structure is shaped like a particular recursive datatype, but you're neither consuming nor producing that recursive datatype. For example, the recursion structure of quick sort is a binary tree, but its input and output is a list, not a binary tree.

>>> data BinTreeF a b = Tip | Branch b a b deriving (Functor)
>>> :{
>>> let quicksort :: Ord a => [a] -> [a]
>>> quicksort = refold merge split where
>>> split []     = Tip
>>> split (x:xs) = let (l, r) = partition (<x) xs in Branch l x r
>>> 
>>> merge Tip            = []
>>> merge (Branch l x r) = l ++ [x] ++ r
>>> :}
>>> quicksort [1,5,2,8,4,9,8]
[1,2,4,5,8,8,9]

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

An alias for refold.

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

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

gcata #

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

gfold #

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

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

gana #

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

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

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 #

A generalized hylomorphism

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 #

A generalized hylomorphism

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

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 #

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

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

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

Convert from one recursive type to another.

>>> showTree $ hoist (\(NonEmptyF h t) -> NodeF [h] (maybeToList t)) ( 'a' :| "bcd")
(a (b (c d)))

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

Convert from one recursive representation to another.

>>> refix ["foo", "bar"] :: Fix (ListF String)
Fix (Cons "foo" (Fix (Cons "bar" (Fix Nil))))

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

distZygo #

Arguments

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

A distributive for semi-mutual recursion

-> (b, f a) 

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 #

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

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

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

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

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

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

A variant of cata which includes the results of all the descendents, not just the direct children.

Like para, a sub-tree is provided for each recursive position. Each node in that sub-tree is annotated with the result for that descendent. The Cofree type is used to add those annotations.

For our running example, let's recreate GitHub's directory compression algorithm. Notice that in the repository for this package, GitHub displays src/Data/Functor, not src:

GitHub does this because src only contains one entry: Data. Similarly, Data only contains one entry: Functor. Functor contains several entries, so the compression stops there. This helps users get to the interesting folders more quickly.

Before we use histo, we need to define a helper function rollup. It collects nodes until it reaches a node which doesn't have exactly one child. It also returns the labels of that node's children.

>>> :{
let rollup :: [Cofree (TreeF node) label]
           -> ([node], [label])
    rollup [_ :< NodeF node cofrees] =
      let (nodes, label) = rollup cofrees
      in (node : nodes, label)
    rollup cofrees =
      ([], fmap extract cofrees)
:}
>>> let foobar xs = 1 :< NodeF "foo" [2 :< NodeF "bar" xs]
>>> rollup [foobar []]
(["foo","bar"],[])
>>> rollup [foobar [3 :< NodeF "baz" [], 4 :< NodeF "quux" []]]
(["foo","bar"],[3,4])

The value foobar [] can be interpreted as the tree NodeF "foo" [NodeF "bar" []], plus two annotations. The "foo" node is annotated with 1, while the "bar" node is annotated with 2. When we call histo below, those annotations are recursive results of type Int -> String.

>>> :{
let pprint5 :: Tree Int -> String
    pprint5 t = histo go t 0
      where
        go :: TreeF Int (Cofree (TreeF Int) (Int -> String))
           -> Int -> String
        go (NodeF node cofrees) indent
            -- cofrees :: [Cofree (TreeF Int) (Int -> String)]
            -- fs :: [Int -> String]
          = let indent' = indent + 2
                (nodes, fs) = rollup cofrees
                ss = map (\f -> f indent') fs
                s = replicate indent ' '
                 ++ "* " ++ intercalate " / " (fmap show (node : nodes))
            in intercalate "\n" (s : ss)
:}
>>> putStrLn $ pprint5 myTree
* 0
  * 1
  * 2
  * 3 / 31 / 311
    * 3111
    * 3112

One common use for histo is to cache the value computed for smaller sub-trees. In the Fibonacci example below, the recursive type is Natural, which is isomorphic to [()]. Our annotated sub-tree is thus isomorphic to a list of annotations. In our case, each annotation is the result which was computed for a smaller number. We thus have access to a list which caches all the Fibonacci numbers we have computed so far.

>>> :{
let fib :: Natural -> Integer
    fib = histo go
      where
        go :: Maybe (Cofree Maybe Integer) -> Integer
        go Nothing = 1
        go (Just (_ :< Nothing)) = 1
        go (Just (fibNMinus1 :< Just (fibNMinus2 :< _)))
          = fibNMinus1 + fibNMinus2
:}
>>> fmap fib [0..10]
[1,1,2,3,5,8,13,21,34,55,89]

In general, Cofree f a can be thought of as a cache that has the same shape as the recursive structure which was given as input.

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 #

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

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

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

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 #

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

Mendler-style iteration

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

Mendler-style recursion

Since: recursion-schemes-5.2.2

mzygo :: (forall y. (y -> b) -> f y -> b) -> (forall y. (y -> c) -> (y -> b) -> f y -> c) -> Fix f -> c #

Mendler-style semi-mutual recursion

Since: recursion-schemes-5.2.2

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

Mendler-style course-of-value iteration

mana :: (forall y. (x -> y) -> x -> f y) -> x -> Fix f #

Mendler-style coiteration

Since: recursion-schemes-5.2.2

mapo :: (forall y. (Fix f -> y) -> (x -> y) -> x -> f y) -> x -> Fix f #

Mendler-style corecursion

Since: recursion-schemes-5.2.2

mfutu :: (forall y. (f y -> y) -> (x -> y) -> x -> f y) -> x -> Fix f #

Mendler-style course-of-values coiteration

Since: recursion-schemes-5.2.2

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

Elgot algebras

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

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 #

Zygohistomorphic prepromorphisms:

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

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

A specialization of cata for effectful folds.

cataA is the same as cata, but with a more specialized type. The only reason it exists is to make it easier to discover how to use this library with effects.

For our running example, let's improve the output format of our pretty-printer by using indentation. To do so, we will need to keep track of the current indentation level. We will do so using a Reader Int effect. Our recursive positions will thus contain Reader Int String actions, not Strings. This means we need to run those actions in order to get the results.

>>> :{
let pprint2 :: Tree Int -> String
    pprint2 = flip runReader 0 . cataA go
      where
        go :: TreeF Int (Reader Int String)
           -> Reader Int String
        go (NodeF i rss) = do
          -- rss :: [Reader Int String]
          -- ss  :: [String]
          ss <- local (+ 2) $ sequence rss
          indent <- ask
          let s = replicate indent ' ' ++ "* " ++ show i
          pure $ intercalate "\n" (s : ss)
:}
>>> putStrLn $ pprint2 myTree
* 0
  * 1
  * 2
  * 3
    * 31
      * 311
        * 3111
        * 3112

The fact that the recursive positions contain Reader actions instead of Strings gives us some flexibility. Here, we are able to increase the indentation by running those actions inside a local block. More generally, we can control the order of their side-effects, interleave them with other effects, etc.

A similar technique is to specialize cata so that the result is a function. This makes it possible for data to flow down in addition to up. In this modified version of our running example, the indentation level flows down from the root to the leaves, while the resulting strings flow up from the leaves to the root.

>>> :{
let pprint3 :: Tree Int -> String
    pprint3 t = cataA go t 0
      where
        go :: TreeF Int (Int -> String)
           -> Int -> String
        go (NodeF i fs) indent
            -- fs :: [Int -> String]
          = let indent' = indent + 2
                ss = map (\f -> f indent') fs
                s = replicate indent ' ' ++ "* " ++ show i
            in intercalate "\n" (s : ss)
:}
>>> putStrLn $ pprint3 myTree
* 0
  * 1
  * 2
  * 3
    * 31
      * 311
        * 3111
        * 3112

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

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 #

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' :: forall a b. (a -> a -> b) -> [a] -> [a] -> [b]
    zipWith' f xs ys = cotransverse g (Pair xs ys) where
      g :: Pair (ListF a c) -> ListF b (Pair c)
      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]

type Algebra f a = f a -> a Source #

type CoAlgebra f a = a -> f a Source #

type RAlgebra f t a = f (t, a) -> a Source #

type RCoAlgebra f t a = a -> f (Either t a) Source #

Higher-order recursion schemes

type (~>) f g = forall a. f a -> g a Source #

type NatM m f g = forall a. f a -> m (g a) Source #

type family HBase (h :: k -> Type) :: (k -> Type) -> k -> Type Source #

Instances

Instances details
type HBase (EGADT xs :: k -> Type) Source # 
Instance details

Defined in Data.Variant.EGADT

type HBase (EGADT xs :: k -> Type) = HVariantF xs

type HAlgebra h f = h f ~> f Source #

type HAlgebraM m h f = NatM m (h f) f Source #

type HGAlgebra w h a = h (w a) ~> a Source #

type HGAlgebraM w m h a = NatM m (h (w a)) a Source #

type HCoalgebra h f = f ~> h f Source #

type HCoalgebraM m h f = NatM m f (h f) Source #

type HGCoalgebra m h a = a ~> h (m a) Source #

type HGCoalgebraM n m h a = NatM m a (h (n a)) Source #

class HFunctor (h :: (k -> Type) -> k -> Type) where Source #

Methods

hfmap :: (f ~> g) -> h f ~> h g Source #

class HFunctor h => HFoldable (h :: (k -> Type) -> k -> Type) where Source #

Methods

hfoldMap :: Monoid m => (forall b. f b -> m) -> h f a -> m Source #

class HFoldable h => HTraversable (h :: (k -> Type) -> k -> Type) where Source #

Methods

htraverse :: Applicative e => NatM e f g -> NatM e (h f) (h g) Source #

class HFunctor (HBase h) => HRecursive (h :: k -> Type) where Source #

Minimal complete definition

hproject

Methods

hproject :: HCoalgebra (HBase h) h Source #

hcata :: HAlgebra (HBase h) f -> h ~> f Source #

Instances

Instances details
HFunctor (HVariantF xs) => HRecursive (EGADT xs :: k -> Type) Source # 
Instance details

Defined in Data.Variant.EGADT

Methods

hproject :: HCoalgebra (HBase (EGADT xs)) (EGADT xs) Source #

hcata :: forall (f :: k0 -> Type). HAlgebra (HBase (EGADT xs)) f -> EGADT xs ~> f Source #

class HFunctor (HBase h) => HCorecursive (h :: k -> Type) where Source #

Minimal complete definition

hembed

Methods

hembed :: HAlgebra (HBase h) h Source #

hana :: HCoalgebra (HBase h) f -> f ~> h Source #

Instances

Instances details
HFunctor (HVariantF xs) => HCorecursive (EGADT xs :: k -> Type) Source # 
Instance details

Defined in Data.Variant.EGADT

Methods

hembed :: HAlgebra (HBase (EGADT xs)) (EGADT xs) Source #

hana :: forall (f :: k0 -> Type). HCoalgebra (HBase (EGADT xs)) f -> f ~> EGADT xs Source #

hhylo :: HFunctor f => HAlgebra f b -> HCoalgebra f a -> a ~> b Source #

hcataM :: (Monad m, HTraversable (HBase h), HRecursive h) => HAlgebraM m (HBase h) f -> h a -> m (f a) Source #

hpara :: (HFunctor (HBase h), HRecursive h) => HGAlgebra (Product h) (HBase h) a -> h ~> a Source #

hparaM :: (HTraversable (HBase h), HRecursive h, Monad m) => HGAlgebraM (Product h) m (HBase h) a -> NatM m h a Source #

hanaM :: (Monad m, HTraversable (HBase h), HCorecursive h) => HCoalgebraM m (HBase h) f -> f a -> m (h a) Source #

hapo :: HCorecursive h => HGCoalgebra (Sum h) (HBase h) a -> a ~> h Source #

hapoM :: (HCorecursive h, HTraversable (HBase h), Monad m) => HGCoalgebraM (Sum h) m (HBase h) a -> NatM m a h Source #

hhyloM :: (HTraversable t, Monad m) => HAlgebraM m t h -> HCoalgebraM m t f -> f a -> m (h a) Source #