{-# LANGUAGE CPP, TypeFamilies, Rank2Types, FlexibleContexts, FlexibleInstances, GADTs, StandaloneDeriving, UndecidableInstances #-}
#include "recursion-schemes-common.h"
#ifdef __GLASGOW_HASKELL__
{-# LANGUAGE DeriveDataTypeable #-}
#if __GLASGOW_HASKELL__ >= 800
{-# LANGUAGE ConstrainedClassMethods #-}
#endif
#if HAS_GENERIC
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ScopedTypeVariables, DefaultSignatures, MultiParamTypeClasses, TypeOperators #-}
#endif
#endif
module Data.Functor.Foldable
(
Base
, ListF(..)
, Recursive(project)
, Corecursive(embed)
, fold
, cata
, cataA
, para
, histo
, zygo
, unfold
, ana
, apo
, futu
, refold
, hylo
, chrono
, refix
, hoist
, transverse
, cotransverse
, mcata
, mpara
, mhisto
, mzygo
, mana
, mapo
, mfutu
, prepro
, postpro
, elgot
, coelgot
, gfold
, gcata
, gpara
, ghisto
, gzygo
, gunfold
, gana
, gapo
, gfutu
, grefold
, ghylo
, gchrono
, gprepro
, gpostpro
, distCata
, distPara
, distParaT
, distHisto
, distGHisto
, distZygo
, distZygoT
, distAna
, distApo
, distGApo
, distGApoT
, distFutu
, distGFutu
, zygoHistoPrepro
) where
import Control.Applicative
import Control.Comonad
import Control.Comonad.Trans.Class
import Control.Comonad.Trans.Env (EnvT(..))
import qualified Control.Comonad.Cofree as Cofree
import Control.Comonad.Cofree (Cofree(..))
import Control.Comonad.Trans.Cofree (CofreeF, CofreeT(..))
import qualified Control.Comonad.Trans.Cofree as CCTC
import Control.Monad (liftM, join)
import Control.Monad.Free (Free(..))
import qualified Control.Monad.Free.Church as CMFC
import Control.Monad.Trans.Except (ExceptT(..), runExceptT)
import Control.Monad.Trans.Free (FreeF, FreeT(..))
import qualified Control.Monad.Trans.Free as CMTF
import Data.Functor.Identity
import Control.Arrow
import Data.Functor.Compose (Compose(..))
import Data.List.NonEmpty(NonEmpty((:|)), nonEmpty, toList)
import Data.Tree (Tree (..))
#ifdef __GLASGOW_HASKELL__
#if HAS_GENERIC
import GHC.Generics (Generic (..), M1 (..), V1, U1, K1 (..), (:+:) (..), (:*:) (..))
#endif
#endif
import Numeric.Natural
import Prelude
import Data.Functor.Base hiding (head, tail)
import qualified Data.Functor.Base as NEF (NonEmptyF(..))
import Data.Fix (Fix (..), unFix, Mu (..), Nu (..))
type family Base t :: * -> *
class Functor (Base t) => Recursive t where
project :: t -> Base t t
#ifdef HAS_GENERIC
default project :: (Generic t, Generic (Base t t), GCoerce (Rep t) (Rep (Base t t))) => t -> Base t t
project = forall a x. Generic a => Rep a x -> a
to forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) (g :: * -> *) a. GCoerce f g => f a -> g a
gcoerce forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a x. Generic a => a -> Rep a x
from
#endif
cata :: (Base t a -> a) -> t -> a
cata Base t a -> a
f = t -> a
c where c :: t -> a
c = Base t a -> a
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap t -> a
c forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Recursive t => t -> Base t t
project
para :: (Base t (t, a) -> a) -> t -> a
para Base t (t, a) -> a
t = t -> a
p where p :: t -> a
p t
x = Base t (t, a) -> a
t forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((,) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> t -> a
p) forall a b. (a -> b) -> a -> b
$ forall t. Recursive t => t -> Base t t
project t
x
gpara :: (Corecursive t, Comonad w) => (forall b. Base t (w b) -> w (Base t b)) -> (Base t (EnvT t w a) -> a) -> t -> a
gpara forall b. Base t (w b) -> w (Base t b)
t = forall t (w :: * -> *) b a.
(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
gzygo forall t. Corecursive t => Base t t -> t
embed forall b. Base t (w b) -> w (Base t b)
t
prepro
:: Corecursive t
=> (forall b. Base t b -> Base t b)
-> (Base t a -> a)
-> t
-> a
prepro forall b. Base t b -> Base t b
e Base t a -> a
f = t -> a
c where c :: t -> a
c = Base t a -> a
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (t -> a
c forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s t.
(Recursive s, Corecursive t) =>
(forall a. Base s a -> Base t a) -> s -> t
hoist forall b. Base t b -> Base t b
e) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Recursive t => t -> Base t t
project
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
gprepro forall b. Base t (w b) -> w (Base t b)
k forall b. Base t b -> Base t b
e Base t (w a) -> a
f = forall (w :: * -> *) a. Comonad w => w a -> a
extract forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> w a
c where c :: t -> w a
c = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Base t (w a) -> a
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b. Base t (w b) -> w (Base t b)
k forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (w :: * -> *) a. Comonad w => w a -> w (w a)
duplicate forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> w a
c forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s t.
(Recursive s, Corecursive t) =>
(forall a. Base s a -> Base t a) -> s -> t
hoist forall b. Base t b -> Base t b
e) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Recursive t => t -> Base t t
project
distPara :: Corecursive t => Base t (t, a) -> (t, Base t a)
distPara :: forall t a. Corecursive t => Base t (t, a) -> (t, Base t a)
distPara = forall (f :: * -> *) b a.
Functor f =>
(f b -> b) -> f (b, a) -> (b, f a)
distZygo forall t. Corecursive t => Base t t -> t
embed
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)
distParaT :: forall t (w :: * -> *) a.
(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)
distParaT forall b. Base t (w b) -> w (Base t b)
t = forall (f :: * -> *) (w :: * -> *) b a.
(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)
distZygoT forall t. Corecursive t => Base t t -> t
embed forall b. Base t (w b) -> w (Base t b)
t
class Functor (Base t) => Corecursive t where
embed :: Base t t -> t
#ifdef HAS_GENERIC
default embed :: (Generic t, Generic (Base t t), GCoerce (Rep (Base t t)) (Rep t)) => Base t t -> t
embed = forall a x. Generic a => Rep a x -> a
to forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) (g :: * -> *) a. GCoerce f g => f a -> g a
gcoerce forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a x. Generic a => a -> Rep a x
from
#endif
ana
:: (a -> Base t a)
-> a
-> t
ana a -> Base t a
g = a -> t
a where a :: a -> t
a = forall t. Corecursive t => Base t t -> t
embed forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> t
a forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Base t a
g
apo :: (a -> Base t (Either t a)) -> a -> t
apo a -> Base t (Either t a)
g = a -> t
a where a :: a -> t
a = forall t. Corecursive t => Base t t -> t
embed forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall a. a -> a
id a -> t
a)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Base t (Either t a)
g
postpro
:: Recursive t
=> (forall b. Base t b -> Base t b)
-> (a -> Base t a)
-> a
-> t
postpro forall b. Base t b -> Base t b
e a -> Base t a
g = a -> t
a where a :: a -> t
a = forall t. Corecursive t => Base t t -> t
embed forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s t.
(Recursive s, Corecursive t) =>
(forall a. Base s a -> Base t a) -> s -> t
hoist forall b. Base t b -> Base t b
e forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> t
a) forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Base t a
g
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
gpostpro forall b. m (Base t b) -> Base t (m b)
k forall b. Base t b -> Base t b
e a -> Base t (m a)
g = m a -> t
a forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => a -> m a
return where a :: m a -> t
a = forall t. Corecursive t => Base t t -> t
embed forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall s t.
(Recursive s, Corecursive t) =>
(forall a. Base s a -> Base t a) -> s -> t
hoist forall b. Base t b -> Base t b
e forall b c a. (b -> c) -> (a -> b) -> a -> c
. m a -> t
a forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => m (m a) -> m a
join) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b. m (Base t b) -> Base t (m b)
k forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM a -> Base t (m a)
g
hylo :: Functor f => (f b -> b) -> (a -> f a) -> a -> b
hylo :: forall (f :: * -> *) b a.
Functor f =>
(f b -> b) -> (a -> f a) -> a -> b
hylo f b -> b
f a -> f a
g = a -> b
h where h :: a -> b
h = f b -> b
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
h forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> f a
g
fold :: Recursive t => (Base t a -> a) -> t -> a
fold :: forall t a. Recursive t => (Base t a -> a) -> t -> a
fold = forall t a. Recursive t => (Base t a -> a) -> t -> a
cata
unfold :: Corecursive t => (a -> Base t a) -> a -> t
unfold :: forall t a. Corecursive t => (a -> Base t a) -> a -> t
unfold = forall t a. Corecursive t => (a -> Base t a) -> a -> t
ana
refold :: Functor f => (f b -> b) -> (a -> f a) -> a -> b
refold :: forall (f :: * -> *) b a.
Functor f =>
(f b -> b) -> (a -> f a) -> a -> b
refold = forall (f :: * -> *) b a.
Functor f =>
(f b -> b) -> (a -> f a) -> a -> b
hylo
type instance Base [a] = ListF a
instance Recursive [a] where
project :: [a] -> Base [a] [a]
project (a
x:[a]
xs) = forall a b. a -> b -> ListF a b
Cons a
x [a]
xs
project [] = forall a b. ListF a b
Nil
para :: forall a. (Base [a] ([a], a) -> a) -> [a] -> a
para Base [a] ([a], a) -> a
f (a
x:[a]
xs) = Base [a] ([a], a) -> a
f (forall a b. a -> b -> ListF a b
Cons a
x ([a]
xs, forall t a. Recursive t => (Base t (t, a) -> a) -> t -> a
para Base [a] ([a], a) -> a
f [a]
xs))
para Base [a] ([a], a) -> a
f [] = Base [a] ([a], a) -> a
f forall a b. ListF a b
Nil
instance Corecursive [a] where
embed :: Base [a] [a] -> [a]
embed (Cons a
x [a]
xs) = a
xforall a. a -> [a] -> [a]
:[a]
xs
embed ListF a [a]
Base [a] [a]
Nil = []
apo :: forall a. (a -> Base [a] (Either [a] a)) -> a -> [a]
apo a -> Base [a] (Either [a] a)
f a
a = case a -> Base [a] (Either [a] a)
f a
a of
Cons a
x (Left [a]
xs) -> a
x forall a. a -> [a] -> [a]
: [a]
xs
Cons a
x (Right a
b) -> a
x forall a. a -> [a] -> [a]
: forall t a. Corecursive t => (a -> Base t (Either t a)) -> a -> t
apo a -> Base [a] (Either [a] a)
f a
b
ListF a (Either [a] a)
Base [a] (Either [a] a)
Nil -> []
type instance Base (NonEmpty a) = NonEmptyF a
instance Recursive (NonEmpty a) where
project :: NonEmpty a -> Base (NonEmpty a) (NonEmpty a)
project (a
x:|[a]
xs) = forall a b. a -> Maybe b -> NonEmptyF a b
NonEmptyF a
x forall a b. (a -> b) -> a -> b
$ forall a. [a] -> Maybe (NonEmpty a)
nonEmpty [a]
xs
instance Corecursive (NonEmpty a) where
embed :: Base (NonEmpty a) (NonEmpty a) -> NonEmpty a
embed = forall a. a -> [a] -> NonEmpty a
(:|) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b. NonEmptyF a b -> a
NEF.head forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] forall a. NonEmpty a -> [a]
toList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b. NonEmptyF a b -> Maybe b
NEF.tail)
type instance Base (Tree a) = TreeF a
instance Recursive (Tree a) where
project :: Tree a -> Base (Tree a) (Tree a)
project (Node a
x [Tree a]
xs) = forall a b. a -> ForestF a b -> TreeF a b
NodeF a
x [Tree a]
xs
instance Corecursive (Tree a) where
embed :: Base (Tree a) (Tree a) -> Tree a
embed (NodeF a
x ForestF a (Tree a)
xs) = forall a. a -> [Tree a] -> Tree a
Node a
x ForestF a (Tree a)
xs
type instance Base Natural = Maybe
instance Recursive Natural where
project :: Natural -> Base Natural Natural
project Natural
0 = forall a. Maybe a
Nothing
project Natural
n = forall a. a -> Maybe a
Just (Natural
n forall a. Num a => a -> a -> a
- Natural
1)
instance Corecursive Natural where
embed :: Base Natural Natural -> Natural
embed = forall b a. b -> (a -> b) -> Maybe a -> b
maybe Natural
0 (forall a. Num a => a -> a -> a
+Natural
1)
type instance Base (Cofree f a) = CofreeF f a
instance Functor f => Recursive (Cofree f a) where
project :: Cofree f a -> Base (Cofree f a) (Cofree f a)
project (a
x :< f (Cofree f a)
xs) = a
x forall (f :: * -> *) a b. a -> f b -> CofreeF f a b
CCTC.:< f (Cofree f a)
xs
instance Functor f => Corecursive (Cofree f a) where
embed :: Base (Cofree f a) (Cofree f a) -> Cofree f a
embed (a
x CCTC.:< f (Cofree f a)
xs) = a
x forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< f (Cofree f a)
xs
type instance Base (CofreeT f w a) = Compose w (CofreeF f a)
instance (Functor w, Functor f) => Recursive (CofreeT f w a) where
project :: CofreeT f w a -> Base (CofreeT f w a) (CofreeT f w a)
project = forall {k} {k1} (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) (w :: * -> *) a.
CofreeT f w a -> w (CofreeF f a (CofreeT f w a))
runCofreeT
instance (Functor w, Functor f) => Corecursive (CofreeT f w a) where
embed :: Base (CofreeT f w a) (CofreeT f w a) -> CofreeT f w a
embed = forall (f :: * -> *) (w :: * -> *) a.
w (CofreeF f a (CofreeT f w a)) -> CofreeT f w a
CofreeT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose
type instance Base (Free f a) = FreeF f a
instance Functor f => Recursive (Free f a) where
project :: Free f a -> Base (Free f a) (Free f a)
project (Pure a
a) = forall (f :: * -> *) a b. a -> FreeF f a b
CMTF.Pure a
a
project (Free f (Free f a)
f) = forall (f :: * -> *) a b. f b -> FreeF f a b
CMTF.Free f (Free f a)
f
improveF :: Functor f => CMFC.F f a -> Free f a
improveF :: forall (f :: * -> *) a. Functor f => F f a -> Free f a
improveF F f a
x = forall (f :: * -> *) a.
Functor f =>
(forall (m :: * -> *). MonadFree f m => m a) -> Free f a
CMFC.improve (forall (f :: * -> *) (m :: * -> *) a. MonadFree f m => F f a -> m a
CMFC.fromF F f a
x)
instance Functor f => Corecursive (Free f a) where
embed :: Base (Free f a) (Free f a) -> Free f a
embed (CMTF.Pure a
a) = forall (f :: * -> *) a. a -> Free f a
Pure a
a
embed (CMTF.Free f (Free f a)
f) = forall (f :: * -> *) a. f (Free f a) -> Free f a
Free f (Free f a)
f
ana :: forall a. (a -> Base (Free f a) a) -> a -> Free f a
ana a -> Base (Free f a) a
coalg = forall (f :: * -> *) a. Functor f => F f a -> Free f a
improveF forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t a. Corecursive t => (a -> Base t a) -> a -> t
ana a -> Base (Free f a) a
coalg
postpro :: forall a.
Recursive (Free f a) =>
(forall b. Base (Free f a) b -> Base (Free f a) b)
-> (a -> Base (Free f a) a) -> a -> Free f a
postpro forall b. Base (Free f a) b -> Base (Free f a) b
nat a -> Base (Free f a) a
coalg = forall (f :: * -> *) a. Functor f => F f a -> Free f a
improveF forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t a.
(Corecursive t, Recursive t) =>
(forall b. Base t b -> Base t b) -> (a -> Base t a) -> a -> t
postpro forall b. Base (Free f a) b -> Base (Free f a) b
nat a -> Base (Free f a) a
coalg
gpostpro :: forall (m :: * -> *) a.
(Recursive (Free f a), Monad m) =>
(forall b. m (Base (Free f a) b) -> Base (Free f a) (m b))
-> (forall b. Base (Free f a) b -> Base (Free f a) b)
-> (a -> Base (Free f a) (m a))
-> a
-> Free f a
gpostpro forall b. m (Base (Free f a) b) -> Base (Free f a) (m b)
dist forall b. Base (Free f a) b -> Base (Free f a) b
nat a -> Base (Free f a) (m a)
coalg = forall (f :: * -> *) a. Functor f => F f a -> Free f a
improveF forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t (m :: * -> *) a.
(Corecursive t, Recursive t, Monad m) =>
(forall b. m (Base t b) -> Base t (m b))
-> (forall b. Base t b -> Base t b)
-> (a -> Base t (m a))
-> a
-> t
gpostpro forall b. m (Base (Free f a) b) -> Base (Free f a) (m b)
dist forall b. Base (Free f a) b -> Base (Free f a) b
nat a -> Base (Free f a) (m a)
coalg
type instance Base (FreeT f m a) = Compose m (FreeF f a)
instance (Functor m, Functor f) => Recursive (FreeT f m a) where
project :: FreeT f m a -> Base (FreeT f m a) (FreeT f m a)
project = forall {k} {k1} (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) (m :: * -> *) a.
FreeT f m a -> m (FreeF f a (FreeT f m a))
runFreeT
instance (Functor m, Functor f) => Corecursive (FreeT f m a) where
embed :: Base (FreeT f m a) (FreeT f m a) -> FreeT f m a
embed = forall (f :: * -> *) (m :: * -> *) a.
m (FreeF f a (FreeT f m a)) -> FreeT f m a
FreeT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose
type instance Base (Maybe a) = Const (Maybe a)
instance Recursive (Maybe a) where project :: Maybe a -> Base (Maybe a) (Maybe a)
project = forall {k} a (b :: k). a -> Const a b
Const
instance Corecursive (Maybe a) where embed :: Base (Maybe a) (Maybe a) -> Maybe a
embed = forall {k} a (b :: k). Const a b -> a
getConst
type instance Base (Either a b) = Const (Either a b)
instance Recursive (Either a b) where project :: Either a b -> Base (Either a b) (Either a b)
project = forall {k} a (b :: k). a -> Const a b
Const
instance Corecursive (Either a b) where embed :: Base (Either a b) (Either a b) -> Either a b
embed = forall {k} a (b :: k). Const a b -> a
getConst
gfold, gcata
:: (Recursive t, Comonad w)
=> (forall b. Base t (w b) -> w (Base t b))
-> (Base t (w a) -> a)
-> t
-> a
gcata :: forall t (w :: * -> *) a.
(Recursive t, Comonad w) =>
(forall b. Base t (w b) -> w (Base t b))
-> (Base t (w a) -> a) -> t -> a
gcata forall b. Base t (w b) -> w (Base t b)
k Base t (w a) -> a
g = Base t (w a) -> a
g forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (w :: * -> *) a. Comonad w => w a -> a
extract forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> w (Base t (w a))
c where
c :: t -> w (Base t (w a))
c = forall b. Base t (w b) -> w (Base t b)
k forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (w :: * -> *) a. Comonad w => w a -> w (w a)
duplicate forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Base t (w a) -> a
g forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> w (Base t (w a))
c) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Recursive t => t -> Base t t
project
gfold :: forall t (w :: * -> *) a.
(Recursive t, Comonad w) =>
(forall b. Base t (w b) -> w (Base t b))
-> (Base t (w a) -> a) -> t -> a
gfold forall b. Base t (w b) -> w (Base t b)
k Base t (w a) -> a
g t
t = forall t (w :: * -> *) a.
(Recursive t, Comonad w) =>
(forall b. Base t (w b) -> w (Base t b))
-> (Base t (w a) -> a) -> t -> a
gcata forall b. Base t (w b) -> w (Base t b)
k Base t (w a) -> a
g t
t
distCata :: Functor f => f (Identity a) -> Identity (f a)
distCata :: forall (f :: * -> *) a.
Functor f =>
f (Identity a) -> Identity (f a)
distCata = forall a. a -> Identity a
Identity forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Identity a -> a
runIdentity
gunfold, gana
:: (Corecursive t, Monad m)
=> (forall b. m (Base t b) -> Base t (m b))
-> (a -> Base t (m a))
-> a
-> t
gana :: forall t (m :: * -> *) a.
(Corecursive t, Monad m) =>
(forall b. m (Base t b) -> Base t (m b))
-> (a -> Base t (m a)) -> a -> t
gana forall b. m (Base t b) -> Base t (m b)
k a -> Base t (m a)
f = m (Base t (m a)) -> t
a forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Base t (m a)
f where
a :: m (Base t (m a)) -> t
a = forall t. Corecursive t => Base t t -> t
embed forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (m (Base t (m a)) -> t
a forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM a -> Base t (m a)
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => m (m a) -> m a
join) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b. m (Base t b) -> Base t (m b)
k
gunfold :: forall t (m :: * -> *) a.
(Corecursive t, Monad m) =>
(forall b. m (Base t b) -> Base t (m b))
-> (a -> Base t (m a)) -> a -> t
gunfold forall b. m (Base t b) -> Base t (m b)
k a -> Base t (m a)
f a
t = forall t (m :: * -> *) a.
(Corecursive t, Monad m) =>
(forall b. m (Base t b) -> Base t (m b))
-> (a -> Base t (m a)) -> a -> t
gana forall b. m (Base t b) -> Base t (m b)
k a -> Base t (m a)
f a
t
distAna :: Functor f => Identity (f a) -> f (Identity a)
distAna :: forall (f :: * -> *) a.
Functor f =>
Identity (f a) -> f (Identity a)
distAna = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> Identity a
Identity forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Identity a -> a
runIdentity
grefold, 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
ghylo :: forall (w :: * -> *) (f :: * -> *) (m :: * -> *) b a.
(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
ghylo forall c. f (w c) -> w (f c)
w forall d. m (f d) -> f (m d)
m f (w b) -> b
f a -> f (m a)
g = f (w b) -> b
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (f :: * -> *) b a.
Functor f =>
(f b -> b) -> (a -> f a) -> a -> b
hylo f (w b) -> w b
alg m a -> f (m a)
coalg) forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> f (m a)
g where
coalg :: m a -> f (m a)
coalg = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (m :: * -> *) a. Monad m => m (m a) -> m a
join forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall d. m (f d) -> f (m d)
m forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM a -> f (m a)
g
alg :: f (w b) -> w b
alg = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f (w b) -> b
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. f (w c) -> w (f c)
w forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (w :: * -> *) a. Comonad w => w a -> w (w a)
duplicate
grefold :: forall (w :: * -> *) (f :: * -> *) (m :: * -> *) b a.
(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
grefold forall c. f (w c) -> w (f c)
w forall d. m (f d) -> f (m d)
m f (w b) -> b
f a -> f (m a)
g a
a = forall (w :: * -> *) (f :: * -> *) (m :: * -> *) b a.
(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
ghylo forall c. f (w c) -> w (f c)
w forall d. m (f d) -> f (m d)
m f (w b) -> b
f a -> f (m a)
g a
a
futu :: Corecursive t => (a -> Base t (Free (Base t) a)) -> a -> t
futu :: forall t a.
Corecursive t =>
(a -> Base t (Free (Base t) a)) -> a -> t
futu = forall t (m :: * -> *) a.
(Corecursive t, Monad m) =>
(forall b. m (Base t b) -> Base t (m b))
-> (a -> Base t (m a)) -> a -> t
gana forall (f :: * -> *) a. Functor f => Free f (f a) -> f (Free f a)
distFutu
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
gfutu :: forall t (m :: * -> *) a.
(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
gfutu forall b. m (Base t b) -> Base t (m b)
g = forall t (m :: * -> *) a.
(Corecursive t, Monad m) =>
(forall b. m (Base t b) -> Base t (m b))
-> (a -> Base t (m a)) -> a -> t
gana (forall (f :: * -> *) (h :: * -> *) a.
(Functor f, Functor h) =>
(forall b. h (f b) -> f (h b))
-> FreeT f h (f a) -> f (FreeT f h a)
distGFutu forall b. m (Base t b) -> Base t (m b)
g)
distFutu :: Functor f => Free f (f a) -> f (Free f a)
distFutu :: forall (f :: * -> *) a. Functor f => Free f (f a) -> f (Free f a)
distFutu (Pure f a
fx) = forall (f :: * -> *) a. a -> Free f a
Pure forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f a
fx
distFutu (Free f (Free f (f a))
ff) = forall (f :: * -> *) a. f (Free f a) -> Free f a
Free forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Functor f => Free f (f a) -> f (Free f a)
distFutu forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f (Free f (f a))
ff
distGFutu :: (Functor f, Functor h) => (forall b. h (f b) -> f (h b)) -> FreeT f h (f a) -> f (FreeT f h a)
distGFutu :: forall (f :: * -> *) (h :: * -> *) a.
(Functor f, Functor h) =>
(forall b. h (f b) -> f (h b))
-> FreeT f h (f a) -> f (FreeT f h a)
distGFutu forall b. h (f b) -> f (h b)
k = FreeT f h (f a) -> f (FreeT f h a)
d where
d :: FreeT f h (f a) -> f (FreeT f h a)
d = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (f :: * -> *) (m :: * -> *) a.
m (FreeF f a (FreeT f m a)) -> FreeT f m a
FreeT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b. h (f b) -> f (h b)
k forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FreeF f (f a) (FreeT f h (f a)) -> f (FreeF f a (FreeT f h a))
d' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) (m :: * -> *) a.
FreeT f m a -> m (FreeF f a (FreeT f m a))
runFreeT
d' :: FreeF f (f a) (FreeT f h (f a)) -> f (FreeF f a (FreeT f h a))
d' (CMTF.Pure f a
ff) = forall (f :: * -> *) a b. a -> FreeF f a b
CMTF.Pure forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f a
ff
d' (CMTF.Free f (FreeT f h (f a))
ff) = forall (f :: * -> *) a b. f b -> FreeF f a b
CMTF.Free forall b c a. (b -> c) -> (a -> b) -> a -> c
. FreeT f h (f a) -> f (FreeT f h a)
d forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f (FreeT f h (f a))
ff
type instance Base (Fix f) = f
instance Functor f => Recursive (Fix f) where
project :: Fix f -> Base (Fix f) (Fix f)
project (Fix f (Fix f)
a) = f (Fix f)
a
instance Functor f => Corecursive (Fix f) where
embed :: Base (Fix f) (Fix f) -> Fix f
embed = forall (f :: * -> *). f (Fix f) -> Fix f
Fix
hoist :: (Recursive s, Corecursive t)
=> (forall a. Base s a -> Base t a) -> s -> t
hoist :: forall s t.
(Recursive s, Corecursive t) =>
(forall a. Base s a -> Base t a) -> s -> t
hoist forall a. Base s a -> Base t a
n = forall t a. Recursive t => (Base t a -> a) -> t -> a
cata (forall t. Corecursive t => Base t t -> t
embed forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Base s a -> Base t a
n)
refix :: (Recursive s, Corecursive t, Base s ~ Base t) => s -> t
refix :: forall s t. (Recursive s, Corecursive t, Base s ~ Base t) => s -> t
refix = forall t a. Recursive t => (Base t a -> a) -> t -> a
cata forall t. Corecursive t => Base t t -> t
embed
lambek :: (Recursive t, Corecursive t) => (t -> Base t t)
lambek :: forall t. (Recursive t, Corecursive t) => t -> Base t t
lambek = forall t a. Recursive t => (Base t a -> a) -> t -> a
cata (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall t. Corecursive t => Base t t -> t
embed)
colambek :: (Recursive t, Corecursive t) => (Base t t -> t)
colambek :: forall t. (Recursive t, Corecursive t) => Base t t -> t
colambek = forall t a. Corecursive t => (a -> Base t a) -> a -> t
ana (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall t. Recursive t => t -> Base t t
project)
type instance Base (Mu f) = f
instance Functor f => Recursive (Mu f) where
project :: Mu f -> Base (Mu f) (Mu f)
project = forall t. (Recursive t, Corecursive t) => t -> Base t t
lambek
cata :: forall a. (Base (Mu f) a -> a) -> Mu f -> a
cata Base (Mu f) a -> a
f (Mu forall a. (f a -> a) -> a
g) = forall a. (f a -> a) -> a
g Base (Mu f) a -> a
f
instance Functor f => Corecursive (Mu f) where
embed :: Base (Mu f) (Mu f) -> Mu f
embed Base (Mu f) (Mu f)
m = forall (f :: * -> *). (forall a. (f a -> a) -> a) -> Mu f
Mu (\f a -> a
f -> f a -> a
f (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall t a. Recursive t => (Base t a -> a) -> t -> a
fold f a -> a
f) Base (Mu f) (Mu f)
m))
type instance Base (Nu f) = f
instance Functor f => Corecursive (Nu f) where
embed :: Base (Nu f) (Nu f) -> Nu f
embed = forall t. (Recursive t, Corecursive t) => Base t t -> t
colambek
ana :: forall a. (a -> Base (Nu f) a) -> a -> Nu f
ana = forall (f :: * -> *) a. (a -> f a) -> a -> Nu f
Nu
instance Functor f => Recursive (Nu f) where
project :: Nu f -> Base (Nu f) (Nu f)
project (Nu a -> f a
f a
a) = forall (f :: * -> *) a. (a -> f a) -> a -> Nu f
Nu a -> f a
f forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f a
f a
a
type instance Base (CMFC.F f a) = FreeF f a
cmfcCata :: (a -> r) -> (f r -> r) -> CMFC.F f a -> r
cmfcCata :: forall a r (f :: * -> *). (a -> r) -> (f r -> r) -> F f a -> r
cmfcCata a -> r
p f r -> r
f (CMFC.F forall r. (a -> r) -> (f r -> r) -> r
run) = forall r. (a -> r) -> (f r -> r) -> r
run a -> r
p f r -> r
f
instance Functor f => Recursive (CMFC.F f a) where
project :: F f a -> Base (F f a) (F f a)
project = forall t. (Recursive t, Corecursive t) => t -> Base t t
lambek
cata :: forall a. (Base (F f a) a -> a) -> F f a -> a
cata Base (F f a) a -> a
f = forall a r (f :: * -> *). (a -> r) -> (f r -> r) -> F f a -> r
cmfcCata (Base (F f a) a -> a
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. a -> FreeF f a b
CMTF.Pure) (Base (F f a) a -> a
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. f b -> FreeF f a b
CMTF.Free)
instance Functor f => Corecursive (CMFC.F f a) where
embed :: Base (F f a) (F f a) -> F f a
embed (CMTF.Pure a
a) = forall (f :: * -> *) a.
(forall r. (a -> r) -> (f r -> r) -> r) -> F f a
CMFC.F forall a b. (a -> b) -> a -> b
$ \a -> r
p f r -> r
_ -> a -> r
p a
a
embed (CMTF.Free f (F f a)
fr) = forall (f :: * -> *) a.
(forall r. (a -> r) -> (f r -> r) -> r) -> F f a
CMFC.F forall a b. (a -> b) -> a -> b
$ \a -> r
p f r -> r
f -> f r -> r
f forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a r (f :: * -> *). (a -> r) -> (f r -> r) -> F f a -> r
cmfcCata a -> r
p f r -> r
f) f (F f a)
fr
zygo :: Recursive t => (Base t b -> b) -> (Base t (b, a) -> a) -> t -> a
zygo :: forall t b a.
Recursive t =>
(Base t b -> b) -> (Base t (b, a) -> a) -> t -> a
zygo Base t b -> b
f = forall t (w :: * -> *) a.
(Recursive t, Comonad w) =>
(forall b. Base t (w b) -> w (Base t b))
-> (Base t (w a) -> a) -> t -> a
gfold (forall (f :: * -> *) b a.
Functor f =>
(f b -> b) -> f (b, a) -> (b, f a)
distZygo Base t b -> b
f)
distZygo
:: Functor f
=> (f b -> b)
-> (f (b, a) -> (b, f a))
distZygo :: forall (f :: * -> *) b a.
Functor f =>
(f b -> b) -> f (b, a) -> (b, f a)
distZygo f b -> b
g f (b, a)
m = (f b -> b
g (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (a, b) -> a
fst f (b, a)
m), forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (a, b) -> b
snd f (b, a)
m)
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
gzygo :: forall t (w :: * -> *) b a.
(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
gzygo Base t b -> b
f forall c. Base t (w c) -> w (Base t c)
w = forall t (w :: * -> *) a.
(Recursive t, Comonad w) =>
(forall b. Base t (w b) -> w (Base t b))
-> (Base t (w a) -> a) -> t -> a
gfold (forall (f :: * -> *) (w :: * -> *) b a.
(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)
distZygoT Base t b -> b
f forall c. Base t (w c) -> w (Base t c)
w)
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)
distZygoT :: forall (f :: * -> *) (w :: * -> *) b a.
(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)
distZygoT f b -> b
g forall c. f (w c) -> w (f c)
k f (EnvT b w a)
fe = forall e (w :: * -> *) a. e -> w a -> EnvT e w a
EnvT (f b -> b
g (forall {e} {w :: * -> *} {a}. EnvT e w a -> e
getEnv forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f (EnvT b w a)
fe)) (forall c. f (w c) -> w (f c)
k (forall (t :: (* -> *) -> * -> *) (w :: * -> *) a.
(ComonadTrans t, Comonad w) =>
t w a -> w a
lower forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f (EnvT b w a)
fe))
where getEnv :: EnvT e w a -> e
getEnv (EnvT e
e w a
_) = e
e
gapo :: Corecursive t => (b -> Base t b) -> (a -> Base t (Either b a)) -> a -> t
gapo :: forall t b a.
Corecursive t =>
(b -> Base t b) -> (a -> Base t (Either b a)) -> a -> t
gapo b -> Base t b
g = forall t (m :: * -> *) a.
(Corecursive t, Monad m) =>
(forall b. m (Base t b) -> Base t (m b))
-> (a -> Base t (m a)) -> a -> t
gunfold (forall (f :: * -> *) b a.
Functor f =>
(b -> f b) -> Either b (f a) -> f (Either b a)
distGApo b -> Base t b
g)
distApo :: Recursive t => Either t (Base t a) -> Base t (Either t a)
distApo :: forall t a.
Recursive t =>
Either t (Base t a) -> Base t (Either t a)
distApo = forall (f :: * -> *) b a.
Functor f =>
(b -> f b) -> Either b (f a) -> f (Either b a)
distGApo forall t. Recursive t => t -> Base t t
project
distGApo :: Functor f => (b -> f b) -> Either b (f a) -> f (Either b a)
distGApo :: forall (f :: * -> *) b a.
Functor f =>
(b -> f b) -> Either b (f a) -> f (Either b a)
distGApo b -> f b
f = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. a -> Either a b
Left forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> f b
f) (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. b -> Either a b
Right)
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)
distGApoT :: forall (f :: * -> *) (m :: * -> *) b a.
(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)
distGApoT b -> f b
g forall c. m (f c) -> f (m c)
k = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. m (f c) -> f (m c)
k forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (f :: * -> *) b a.
Functor f =>
(b -> f b) -> Either b (f a) -> f (Either b a)
distGApo b -> f b
g) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT
histo :: Recursive t => (Base t (Cofree (Base t) a) -> a) -> t -> a
histo :: forall t a.
Recursive t =>
(Base t (Cofree (Base t) a) -> a) -> t -> a
histo = forall t (w :: * -> *) a.
(Recursive t, Comonad w) =>
(forall b. Base t (w b) -> w (Base t b))
-> (Base t (w a) -> a) -> t -> a
gcata forall (f :: * -> *) a.
Functor f =>
f (Cofree f a) -> Cofree f (f a)
distHisto
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
ghisto :: forall t (w :: * -> *) a.
(Recursive t, Comonad w) =>
(forall b. Base t (w b) -> w (Base t b))
-> (Base t (CofreeT (Base t) w a) -> a) -> t -> a
ghisto forall b. Base t (w b) -> w (Base t b)
g = forall t (w :: * -> *) a.
(Recursive t, Comonad w) =>
(forall b. Base t (w b) -> w (Base t b))
-> (Base t (w a) -> a) -> t -> a
gcata (forall (f :: * -> *) (h :: * -> *) a.
(Functor f, Functor h) =>
(forall b. f (h b) -> h (f b))
-> f (CofreeT f h a) -> CofreeT f h (f a)
distGHisto forall b. Base t (w b) -> w (Base t b)
g)
distHisto :: Functor f => f (Cofree f a) -> Cofree f (f a)
distHisto :: forall (f :: * -> *) a.
Functor f =>
f (Cofree f a) -> Cofree f (f a)
distHisto f (Cofree f a)
fc = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (w :: * -> *) a. Comonad w => w a -> a
extract f (Cofree f a)
fc forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (f :: * -> *) a.
Functor f =>
f (Cofree f a) -> Cofree f (f a)
distHisto forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) (w :: * -> *) a.
ComonadCofree f w =>
w a -> f (w a)
Cofree.unwrap) f (Cofree f a)
fc
distGHisto :: (Functor f, Functor h) => (forall b. f (h b) -> h (f b)) -> f (CofreeT f h a) -> CofreeT f h (f a)
distGHisto :: forall (f :: * -> *) (h :: * -> *) a.
(Functor f, Functor h) =>
(forall b. f (h b) -> h (f b))
-> f (CofreeT f h a) -> CofreeT f h (f a)
distGHisto forall b. f (h b) -> h (f b)
k = f (CofreeT f h a) -> CofreeT f h (f a)
d where d :: f (CofreeT f h a) -> CofreeT f h (f a)
d = forall (f :: * -> *) (w :: * -> *) a.
w (CofreeF f a (CofreeT f w a)) -> CofreeT f w a
CofreeT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\f (CofreeF f a (CofreeT f h a))
fc -> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (f :: * -> *) a b. CofreeF f a b -> a
CCTC.headF f (CofreeF f a (CofreeT f h a))
fc forall (f :: * -> *) a b. a -> f b -> CofreeF f a b
CCTC.:< forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (f (CofreeT f h a) -> CofreeT f h (f a)
d forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. CofreeF f a b -> f b
CCTC.tailF) f (CofreeF f a (CofreeT f h a))
fc) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b. f (h b) -> h (f b)
k forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (f :: * -> *) (w :: * -> *) a.
CofreeT f w a -> w (CofreeF f a (CofreeT f w a))
runCofreeT
chrono :: Functor f => (f (Cofree f b) -> b) -> (a -> f (Free f a)) -> (a -> b)
chrono :: forall (f :: * -> *) b a.
Functor f =>
(f (Cofree f b) -> b) -> (a -> f (Free f a)) -> a -> b
chrono = forall (w :: * -> *) (f :: * -> *) (m :: * -> *) b a.
(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
ghylo forall (f :: * -> *) a.
Functor f =>
f (Cofree f a) -> Cofree f (f a)
distHisto forall (f :: * -> *) a. Functor f => Free f (f a) -> f (Free f a)
distFutu
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)
gchrono :: forall (f :: * -> *) (w :: * -> *) (m :: * -> *) b a.
(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
gchrono forall c. f (w c) -> w (f c)
w forall c. m (f c) -> f (m c)
m = forall (w :: * -> *) (f :: * -> *) (m :: * -> *) b a.
(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
ghylo (forall (f :: * -> *) (h :: * -> *) a.
(Functor f, Functor h) =>
(forall b. f (h b) -> h (f b))
-> f (CofreeT f h a) -> CofreeT f h (f a)
distGHisto forall c. f (w c) -> w (f c)
w) (forall (f :: * -> *) (h :: * -> *) a.
(Functor f, Functor h) =>
(forall b. h (f b) -> f (h b))
-> FreeT f h (f a) -> f (FreeT f h a)
distGFutu forall c. m (f c) -> f (m c)
m)
mcata :: (forall y. (y -> c) -> f y -> c) -> Fix f -> c
mcata :: forall c (f :: * -> *).
(forall y. (y -> c) -> f y -> c) -> Fix f -> c
mcata forall y. (y -> c) -> f y -> c
psi = Fix f -> c
c where c :: Fix f -> c
c = forall y. (y -> c) -> f y -> c
psi Fix f -> c
c forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *). Fix f -> f (Fix f)
unFix
mpara :: (forall y. (y -> c) -> (y -> Fix f) -> f y -> c) -> Fix f -> c
mpara :: forall c (f :: * -> *).
(forall y. (y -> c) -> (y -> Fix f) -> f y -> c) -> Fix f -> c
mpara forall y. (y -> c) -> (y -> Fix f) -> f y -> c
psi = Fix f -> c
c where c :: Fix f -> c
c = forall y. (y -> c) -> (y -> Fix f) -> f y -> c
psi Fix f -> c
c forall a. a -> a
id forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *). Fix f -> f (Fix f)
unFix
mzygo :: (forall y. (y -> b) -> f y -> b) -> (forall y. (y -> c) -> (y -> b) -> f y -> c) -> Fix f -> c
mzygo :: forall b (f :: * -> *) c.
(forall y. (y -> b) -> f y -> b)
-> (forall y. (y -> c) -> (y -> b) -> f y -> c) -> Fix f -> c
mzygo forall y. (y -> b) -> f y -> b
phi forall y. (y -> c) -> (y -> b) -> f y -> c
psi = Fix f -> c
c where c :: Fix f -> c
c = forall y. (y -> c) -> (y -> b) -> f y -> c
psi Fix f -> c
c (forall c (f :: * -> *).
(forall y. (y -> c) -> f y -> c) -> Fix f -> c
mcata forall y. (y -> b) -> f y -> b
phi) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *). Fix f -> f (Fix f)
unFix
mhisto :: (forall y. (y -> c) -> (y -> f y) -> f y -> c) -> Fix f -> c
mhisto :: forall c (f :: * -> *).
(forall y. (y -> c) -> (y -> f y) -> f y -> c) -> Fix f -> c
mhisto forall y. (y -> c) -> (y -> f y) -> f y -> c
psi = Fix f -> c
c where c :: Fix f -> c
c = forall y. (y -> c) -> (y -> f y) -> f y -> c
psi Fix f -> c
c forall (f :: * -> *). Fix f -> f (Fix f)
unFix forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *). Fix f -> f (Fix f)
unFix
mana :: (forall y. (x -> y) -> x -> f y) -> x -> Fix f
mana :: forall x (f :: * -> *).
(forall y. (x -> y) -> x -> f y) -> x -> Fix f
mana forall y. (x -> y) -> x -> f y
phi = x -> Fix f
c where c :: x -> Fix f
c = forall (f :: * -> *). f (Fix f) -> Fix f
Fix forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall y. (x -> y) -> x -> f y
phi x -> Fix f
c
mapo :: (forall y. (Fix f -> y) -> (x -> y) -> x -> f y) -> x -> Fix f
mapo :: forall (f :: * -> *) x.
(forall y. (Fix f -> y) -> (x -> y) -> x -> f y) -> x -> Fix f
mapo forall y. (Fix f -> y) -> (x -> y) -> x -> f y
phi = x -> Fix f
c where c :: x -> Fix f
c = forall (f :: * -> *). f (Fix f) -> Fix f
Fix forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall y. (Fix f -> y) -> (x -> y) -> x -> f y
phi forall a. a -> a
id x -> Fix f
c
mfutu :: (forall y. (f y -> y) -> (x -> y) -> x -> f y) -> x -> Fix f
mfutu :: forall (f :: * -> *) x.
(forall y. (f y -> y) -> (x -> y) -> x -> f y) -> x -> Fix f
mfutu forall y. (f y -> y) -> (x -> y) -> x -> f y
phi = x -> Fix f
c where c :: x -> Fix f
c = forall (f :: * -> *). f (Fix f) -> Fix f
Fix forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall y. (f y -> y) -> (x -> y) -> x -> f y
phi forall (f :: * -> *). f (Fix f) -> Fix f
Fix x -> Fix f
c
elgot :: Functor f => (f a -> a) -> (b -> Either a (f b)) -> b -> a
elgot :: forall (f :: * -> *) a b.
Functor f =>
(f a -> a) -> (b -> Either a (f b)) -> b -> a
elgot f a -> a
phi b -> Either a (f b)
psi = b -> a
h where h :: b -> a
h = (forall a. a -> a
id forall (a :: * -> * -> *) b d c.
ArrowChoice a =>
a b d -> a c d -> a (Either b c) d
||| f a -> a
phi forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap b -> a
h) forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Either a (f b)
psi
coelgot :: Functor f => ((a, f b) -> b) -> (a -> f a) -> a -> b
coelgot :: forall (f :: * -> *) a b.
Functor f =>
((a, f b) -> b) -> (a -> f a) -> a -> b
coelgot (a, f b) -> b
phi a -> f a
psi = a -> b
h where h :: a -> b
h = (a, f b) -> b
phi forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. a -> a
id forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
h forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> f a
psi)
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
zygoHistoPrepro :: forall t b a.
(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
zygoHistoPrepro Base t b -> b
f forall c. Base t c -> Base t c
g Base t (EnvT b (Cofree (Base t)) a) -> a
t = forall t (w :: * -> *) a.
(Recursive t, Corecursive t, Comonad w) =>
(forall b. Base t (w b) -> w (Base t b))
-> (forall b. Base t b -> Base t b)
-> (Base t (w a) -> a)
-> t
-> a
gprepro (forall (f :: * -> *) (w :: * -> *) b a.
(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)
distZygoT Base t b -> b
f forall (f :: * -> *) a.
Functor f =>
f (Cofree f a) -> Cofree f (f a)
distHisto) forall c. Base t c -> Base t c
g Base t (EnvT b (Cofree (Base t)) a) -> a
t
cataA :: (Recursive t) => (Base t (f a) -> f a) -> t -> f a
cataA :: forall t (f :: * -> *) a.
Recursive t =>
(Base t (f a) -> f a) -> t -> f a
cataA = forall t a. Recursive t => (Base t a -> a) -> t -> a
cata
transverse :: (Recursive s, Corecursive t, Functor f)
=> (forall a. Base s (f a) -> f (Base t a)) -> s -> f t
transverse :: forall s t (f :: * -> *).
(Recursive s, Corecursive t, Functor f) =>
(forall a. Base s (f a) -> f (Base t a)) -> s -> f t
transverse forall a. Base s (f a) -> f (Base t a)
n = forall t a. Recursive t => (Base t a -> a) -> t -> a
cata (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall t. Corecursive t => Base t t -> t
embed forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Base s (f a) -> f (Base t a)
n)
cotransverse :: (Recursive s, Corecursive t, Functor f)
=> (forall a. f (Base s a) -> Base t (f a)) -> f s -> t
cotransverse :: forall s t (f :: * -> *).
(Recursive s, Corecursive t, Functor f) =>
(forall a. f (Base s a) -> Base t (f a)) -> f s -> t
cotransverse forall a. f (Base s a) -> Base t (f a)
n = forall t a. Corecursive t => (a -> Base t a) -> a -> t
ana (forall a. f (Base s a) -> Base t (f a)
n forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall t. Recursive t => t -> Base t t
project)
class GCoerce f g where
gcoerce :: f a -> g a
instance GCoerce f g => GCoerce (M1 i c f) (M1 i c' g) where
gcoerce :: forall a. M1 i c f a -> M1 i c' g a
gcoerce (M1 f a
x) = forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (forall (f :: * -> *) (g :: * -> *) a. GCoerce f g => f a -> g a
gcoerce f a
x)
instance GCoerce (K1 i c) (K1 j c) where
gcoerce :: forall a. K1 i c a -> K1 j c a
gcoerce = forall k i c (p :: k). c -> K1 i c p
K1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k i c (p :: k). K1 i c p -> c
unK1
instance GCoerce U1 U1 where
gcoerce :: forall a. U1 a -> U1 a
gcoerce = forall a. a -> a
id
instance GCoerce V1 V1 where
gcoerce :: forall a. V1 a -> V1 a
gcoerce = forall a. a -> a
id
instance (GCoerce f g, GCoerce f' g') => GCoerce (f :*: f') (g :*: g') where
gcoerce :: forall a. (:*:) f f' a -> (:*:) g g' a
gcoerce (f a
x :*: f' a
y) = forall (f :: * -> *) (g :: * -> *) a. GCoerce f g => f a -> g a
gcoerce f a
x forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: forall (f :: * -> *) (g :: * -> *) a. GCoerce f g => f a -> g a
gcoerce f' a
y
instance (GCoerce f g, GCoerce f' g') => GCoerce (f :+: f') (g :+: g') where
gcoerce :: forall a. (:+:) f f' a -> (:+:) g g' a
gcoerce (L1 f a
x) = forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 (forall (f :: * -> *) (g :: * -> *) a. GCoerce f g => f a -> g a
gcoerce f a
x)
gcoerce (R1 f' a
x) = forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 (forall (f :: * -> *) (g :: * -> *) a. GCoerce f g => f a -> g a
gcoerce f' a
x)