{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE StandaloneDeriving #-}
module Control.Comonad.Cofree
  ( Cofree(..)
  , ComonadCofree(..)
  , section
  , coiter
  , coiterW
  , unfold
  , unfoldM
  , hoistCofree
  
  , _extract
  , _unwrap
  , telescoped
  , telescoped_
  , shoots
  , leaves
  ) where
import Control.Applicative
import Control.Comonad
import Control.Comonad.Trans.Class
import Control.Comonad.Cofree.Class
import Control.Comonad.Env.Class
import Control.Comonad.Store.Class as Class
import Control.Comonad.Traced.Class
import Control.Comonad.Hoist.Class
import Control.Category
import Control.Monad(ap, (>=>), liftM)
import Control.Monad.Zip
import Data.Functor.Bind
import Data.Functor.Classes
import Data.Functor.Extend
import Data.Functor.WithIndex
import Data.Data
import Data.Distributive
import Data.Foldable
import Data.Foldable.WithIndex
import Data.Semigroup
import Data.Traversable
import Data.Traversable.WithIndex
import Data.Semigroup.Foldable
import Data.Semigroup.Traversable
import GHC.Generics hiding (Infix, Prefix)
import Prelude hiding (id,(.))
infixr 5 :<
data Cofree f a = a :< f (Cofree f a)
  deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) a x. Rep (Cofree f a) x -> Cofree f a
forall (f :: * -> *) a x. Cofree f a -> Rep (Cofree f a) x
$cto :: forall (f :: * -> *) a x. Rep (Cofree f a) x -> Cofree f a
$cfrom :: forall (f :: * -> *) a x. Cofree f a -> Rep (Cofree f a) x
Generic, forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
forall (f :: * -> *) a.
Functor f =>
Rep1 (Cofree f) a -> Cofree f a
forall (f :: * -> *) a.
Functor f =>
Cofree f a -> Rep1 (Cofree f) a
$cto1 :: forall (f :: * -> *) a.
Functor f =>
Rep1 (Cofree f) a -> Cofree f a
$cfrom1 :: forall (f :: * -> *) a.
Functor f =>
Cofree f a -> Rep1 (Cofree f) a
Generic1)
deriving instance (Typeable f, Data (f (Cofree f a)), Data a) => Data (Cofree f a)
coiter :: Functor f => (a -> f a) -> a -> Cofree f a
coiter :: forall (f :: * -> *) a. Functor f => (a -> f a) -> a -> Cofree f a
coiter a -> f a
psi a
a = a
a forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< (forall (f :: * -> *) a. Functor f => (a -> f a) -> a -> Cofree f a
coiter a -> f a
psi forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f a
psi a
a)
coiterW :: (Comonad w, Functor f) => (w a -> f (w a)) -> w a -> Cofree f a
coiterW :: forall (w :: * -> *) (f :: * -> *) a.
(Comonad w, Functor f) =>
(w a -> f (w a)) -> w a -> Cofree f a
coiterW w a -> f (w a)
psi w a
a = forall (w :: * -> *) a. Comonad w => w a -> a
extract w a
a forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< (forall (w :: * -> *) (f :: * -> *) a.
(Comonad w, Functor f) =>
(w a -> f (w a)) -> w a -> Cofree f a
coiterW w a -> f (w a)
psi forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> w a -> f (w a)
psi w a
a)
unfold :: Functor f => (b -> (a, f b)) -> b -> Cofree f a
unfold :: forall (f :: * -> *) b a.
Functor f =>
(b -> (a, f b)) -> b -> Cofree f a
unfold b -> (a, f b)
f b
c = case b -> (a, f b)
f b
c of
  (a
x, f b
d) -> a
x 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 :: * -> *) b a.
Functor f =>
(b -> (a, f b)) -> b -> Cofree f a
unfold b -> (a, f b)
f) f b
d
unfoldM :: (Traversable f, Monad m) => (b -> m (a, f b)) -> b -> m (Cofree f a)
unfoldM :: forall (f :: * -> *) (m :: * -> *) b a.
(Traversable f, Monad m) =>
(b -> m (a, f b)) -> b -> m (Cofree f a)
unfoldM b -> m (a, f b)
f = b -> m (a, f b)
f forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> \ (a
x, f b
t) -> (a
x forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:<) forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
Data.Traversable.mapM (forall (f :: * -> *) (m :: * -> *) b a.
(Traversable f, Monad m) =>
(b -> m (a, f b)) -> b -> m (Cofree f a)
unfoldM b -> m (a, f b)
f) f b
t
hoistCofree :: Functor f => (forall x . f x -> g x) -> Cofree f a -> Cofree g a
hoistCofree :: forall (f :: * -> *) (g :: * -> *) a.
Functor f =>
(forall x. f x -> g x) -> Cofree f a -> Cofree g a
hoistCofree forall x. f x -> g x
f (a
x :< f (Cofree f a)
y) = a
x forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< forall x. f x -> g x
f (forall (f :: * -> *) (g :: * -> *) a.
Functor f =>
(forall x. f x -> g x) -> Cofree f a -> Cofree g a
hoistCofree forall x. f x -> g x
f forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f (Cofree f a)
y)
instance Functor f => ComonadCofree f (Cofree f) where
  unwrap :: forall a. Cofree f a -> f (Cofree f a)
unwrap (a
_ :< f (Cofree f a)
as) = f (Cofree f a)
as
  {-# INLINE unwrap #-}
instance Distributive f => Distributive (Cofree f) where
  distribute :: forall (f :: * -> *) a.
Functor f =>
f (Cofree f a) -> Cofree f (f a)
distribute f (Cofree f a)
w = 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)
w 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 (g :: * -> *) (f :: * -> *) a.
(Distributive g, Functor f) =>
f (g a) -> g (f a)
distribute (forall (g :: * -> *) (f :: * -> *) a b.
(Distributive g, Functor f) =>
(a -> g b) -> f a -> g (f b)
collect forall (f :: * -> *) (w :: * -> *) a.
ComonadCofree f w =>
w a -> f (w a)
unwrap f (Cofree f a)
w)
instance Functor f => Functor (Cofree f) where
  fmap :: forall a b. (a -> b) -> Cofree f a -> Cofree f b
fmap a -> b
f (a
a :< f (Cofree f a)
as) = a -> b
f a
a 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 b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) f (Cofree f a)
as
  a
b <$ :: forall a b. a -> Cofree f b -> Cofree f a
<$ (b
_ :< f (Cofree f b)
as) = a
b forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a
b forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$) f (Cofree f b)
as
instance Functor f => Extend (Cofree f) where
  extended :: forall a b. (Cofree f a -> b) -> Cofree f a -> Cofree f b
extended = forall (w :: * -> *) a b. Comonad w => (w a -> b) -> w a -> w b
extend
  {-# INLINE extended #-}
  duplicated :: forall a. Cofree f a -> Cofree f (Cofree f a)
duplicated = forall (w :: * -> *) a. Comonad w => w a -> w (w a)
duplicate
  {-# INLINE duplicated #-}
instance Functor f => Comonad (Cofree f) where
  extend :: forall a b. (Cofree f a -> b) -> Cofree f a -> Cofree f b
extend Cofree f a -> b
f Cofree f a
w = Cofree f a -> b
f Cofree f a
w 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 (w :: * -> *) a b. Comonad w => (w a -> b) -> w a -> w b
extend Cofree f a -> b
f) (forall (f :: * -> *) (w :: * -> *) a.
ComonadCofree f w =>
w a -> f (w a)
unwrap Cofree f a
w)
  duplicate :: forall a. Cofree f a -> Cofree f (Cofree f a)
duplicate Cofree f a
w = Cofree f a
w 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 (w :: * -> *) a. Comonad w => w a -> w (w a)
duplicate (forall (f :: * -> *) (w :: * -> *) a.
ComonadCofree f w =>
w a -> f (w a)
unwrap Cofree f a
w)
  extract :: forall a. Cofree f a -> a
extract (a
a :< f (Cofree f a)
_) = a
a
  {-# INLINE extract #-}
instance ComonadTrans Cofree where
  lower :: forall (w :: * -> *) a. Comonad w => Cofree w a -> w a
lower (a
_ :< w (Cofree w a)
as) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (w :: * -> *) a. Comonad w => w a -> a
extract w (Cofree w a)
as
  {-# INLINE lower #-}
instance Alternative f => Monad (Cofree f) where
  return :: forall a. a -> Cofree f a
return = forall (f :: * -> *) a. Applicative f => a -> f a
pure
  {-# INLINE return #-}
  (a
a :< f (Cofree f a)
m) >>= :: forall a b. Cofree f a -> (a -> Cofree f b) -> Cofree f b
>>= a -> Cofree f b
k = case a -> Cofree f b
k a
a of
                     b
b :< f (Cofree f b)
n -> b
b forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< (f (Cofree f b)
n forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= a -> Cofree f b
k) f (Cofree f a)
m)
instance (Alternative f, MonadZip f) => MonadZip (Cofree f) where
  mzip :: forall a b. Cofree f a -> Cofree f b -> Cofree f (a, b)
mzip (a
a :< f (Cofree f a)
as) (b
b :< f (Cofree f b)
bs) = (a
a, b
b) 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 a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall (m :: * -> *) a b. MonadZip m => m a -> m b -> m (a, b)
mzip) (forall (m :: * -> *) a b. MonadZip m => m a -> m b -> m (a, b)
mzip f (Cofree f a)
as f (Cofree f b)
bs)
section :: Comonad f => f a -> Cofree f a
section :: forall (f :: * -> *) a. Comonad f => f a -> Cofree f a
section f a
as = forall (w :: * -> *) a. Comonad w => w a -> a
extract f a
as forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< forall (w :: * -> *) a b. Comonad w => (w a -> b) -> w a -> w b
extend forall (f :: * -> *) a. Comonad f => f a -> Cofree f a
section f a
as
instance Apply f => Apply (Cofree f) where
  (a -> b
f :< f (Cofree f (a -> b))
fs) <.> :: forall a b. Cofree f (a -> b) -> Cofree f a -> Cofree f b
<.> (a
a :< f (Cofree f a)
as) = a -> b
f a
a forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< (forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
(<.>) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f (Cofree f (a -> b))
fs forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
<.> f (Cofree f a)
as)
  {-# INLINE (<.>) #-}
  (a
f :< f (Cofree f a)
fs) <. :: forall a b. Cofree f a -> Cofree f b -> Cofree f a
<.  (b
_ :< f (Cofree f b)
as) = a
f forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< ((<. ) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f (Cofree f a)
fs forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
<.> f (Cofree f b)
as)
  {-# INLINE (<.) #-}
  (a
_ :< f (Cofree f a)
fs)  .> :: forall a b. Cofree f a -> Cofree f b -> Cofree f b
.> (b
a :< f (Cofree f b)
as) = b
a forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< (( .>) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f (Cofree f a)
fs forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
<.> f (Cofree f b)
as)
  {-# INLINE (.>) #-}
instance ComonadApply f => ComonadApply (Cofree f) where
  (a -> b
f :< f (Cofree f (a -> b))
fs) <@> :: forall a b. Cofree f (a -> b) -> Cofree f a -> Cofree f b
<@> (a
a :< f (Cofree f a)
as) = a -> b
f a
a forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< (forall (w :: * -> *) a b.
ComonadApply w =>
w (a -> b) -> w a -> w b
(<@>) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f (Cofree f (a -> b))
fs forall (w :: * -> *) a b.
ComonadApply w =>
w (a -> b) -> w a -> w b
<@> f (Cofree f a)
as)
  {-# INLINE (<@>) #-}
  (a
f :< f (Cofree f a)
fs) <@ :: forall a b. Cofree f a -> Cofree f b -> Cofree f a
<@  (b
_ :< f (Cofree f b)
as) = a
f forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< ((<@ ) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f (Cofree f a)
fs forall (w :: * -> *) a b.
ComonadApply w =>
w (a -> b) -> w a -> w b
<@> f (Cofree f b)
as)
  {-# INLINE (<@) #-}
  (a
_ :< f (Cofree f a)
fs)  @> :: forall a b. Cofree f a -> Cofree f b -> Cofree f b
@> (b
a :< f (Cofree f b)
as) = b
a forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< (( @>) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f (Cofree f a)
fs forall (w :: * -> *) a b.
ComonadApply w =>
w (a -> b) -> w a -> w b
<@> f (Cofree f b)
as)
  {-# INLINE (@>) #-}
instance Alternative f => Applicative (Cofree f) where
  pure :: forall a. a -> Cofree f a
pure a
x = a
x forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< forall (f :: * -> *) a. Alternative f => f a
empty
  {-# INLINE pure #-}
  <*> :: forall a b. Cofree f (a -> b) -> Cofree f a -> Cofree f b
(<*>) = forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
ap
  {-# INLINE (<*>) #-}
instance (Show1 f) => Show1 (Cofree f) where
  liftShowsPrec :: forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Cofree f a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl = Int -> Cofree f a -> ShowS
go
    where
      goList :: [Cofree f a] -> ShowS
goList = forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> [f a] -> ShowS
liftShowList Int -> a -> ShowS
sp [a] -> ShowS
sl
      go :: Int -> Cofree f a -> ShowS
go Int
d (a
a :< f (Cofree f a)
as) = Bool -> ShowS -> ShowS
showParen (Int
d forall a. Ord a => a -> a -> Bool
> Int
5) forall a b. (a -> b) -> a -> b
$
        Int -> a -> ShowS
sp Int
6 a
a forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> ShowS
showString String
" :< " forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
liftShowsPrec Int -> Cofree f a -> ShowS
go [Cofree f a] -> ShowS
goList Int
5 f (Cofree f a)
as
instance (Show1 f, Show a) => Show (Cofree f a) where
  showsPrec :: Int -> Cofree f a -> ShowS
showsPrec = forall (f :: * -> *) a. (Show1 f, Show a) => Int -> f a -> ShowS
showsPrec1
instance (Read1 f) => Read1 (Cofree f) where
  liftReadsPrec :: forall a.
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Cofree f a)
liftReadsPrec Int -> ReadS a
rp ReadS [a]
rl = Int -> ReadS (Cofree f a)
go
    where
      goList :: ReadS [Cofree f a]
goList = forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
liftReadList Int -> ReadS a
rp ReadS [a]
rl
      go :: Int -> ReadS (Cofree f a)
go Int
d String
r = forall a. Bool -> ReadS a -> ReadS a
readParen (Int
d forall a. Ord a => a -> a -> Bool
> Int
5)
        (\String
r' -> [(a
u forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< f (Cofree f a)
v, String
w) |
                (a
u, String
s) <- Int -> ReadS a
rp Int
6 String
r',
                (String
":<", String
t) <- ReadS String
lex String
s,
                (f (Cofree f a)
v, String
w) <- forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a)
liftReadsPrec Int -> ReadS (Cofree f a)
go ReadS [Cofree f a]
goList Int
5 String
t]) String
r
instance (Read1 f, Read a) => Read (Cofree f a) where
  readsPrec :: Int -> ReadS (Cofree f a)
readsPrec = forall (f :: * -> *) a. (Read1 f, Read a) => Int -> ReadS (f a)
readsPrec1
instance (Eq1 f, Eq a) => Eq (Cofree f a) where
  == :: Cofree f a -> Cofree f a -> Bool
(==) = forall (f :: * -> *) a. (Eq1 f, Eq a) => f a -> f a -> Bool
eq1
instance (Eq1 f) => Eq1 (Cofree f) where
  liftEq :: forall a b. (a -> b -> Bool) -> Cofree f a -> Cofree f b -> Bool
liftEq a -> b -> Bool
eq = forall {f :: * -> *}. Eq1 f => Cofree f a -> Cofree f b -> Bool
go
    where
      go :: Cofree f a -> Cofree f b -> Bool
go (a
a :< f (Cofree f a)
as) (b
b :< f (Cofree f b)
bs) = a -> b -> Bool
eq a
a b
b Bool -> Bool -> Bool
&& forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq Cofree f a -> Cofree f b -> Bool
go f (Cofree f a)
as f (Cofree f b)
bs
instance (Ord1 f, Ord a) => Ord (Cofree f a) where
  compare :: Cofree f a -> Cofree f a -> Ordering
compare = forall (f :: * -> *) a. (Ord1 f, Ord a) => f a -> f a -> Ordering
compare1
instance (Ord1 f) => Ord1 (Cofree f) where
  liftCompare :: forall a b.
(a -> b -> Ordering) -> Cofree f a -> Cofree f b -> Ordering
liftCompare a -> b -> Ordering
cmp = forall {f :: * -> *}.
Ord1 f =>
Cofree f a -> Cofree f b -> Ordering
go
    where
      go :: Cofree f a -> Cofree f b -> Ordering
go (a
a :< f (Cofree f a)
as) (b
b :< f (Cofree f b)
bs) = a -> b -> Ordering
cmp a
a b
b forall a. Monoid a => a -> a -> a
`mappend` forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare Cofree f a -> Cofree f b -> Ordering
go f (Cofree f a)
as f (Cofree f b)
bs
instance Foldable f => Foldable (Cofree f) where
  foldMap :: forall m a. Monoid m => (a -> m) -> Cofree f a -> m
foldMap a -> m
f = forall {t :: * -> *}. Foldable t => Cofree t a -> m
go where
    go :: Cofree t a -> m
go (a
a :< t (Cofree t a)
as) = a -> m
f a
a forall a. Monoid a => a -> a -> a
`mappend` forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Cofree t a -> m
go t (Cofree t a)
as
  {-# INLINE foldMap #-}
  length :: forall a. Cofree f a -> Int
length = forall {t :: * -> *} {b} {a}.
(Foldable t, Num b) =>
b -> Cofree t a -> b
go Int
0 where
    go :: b -> Cofree t a -> b
go b
s (a
_ :< t (Cofree t a)
as) = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' b -> Cofree t a -> b
go (b
s forall a. Num a => a -> a -> a
+ b
1) t (Cofree t a)
as
instance Foldable1 f => Foldable1 (Cofree f) where
  foldMap1 :: forall m a. Semigroup m => (a -> m) -> Cofree f a -> m
foldMap1 a -> m
f = forall {t :: * -> *}. Foldable1 t => Cofree t a -> m
go where
    go :: Cofree t a -> m
go (a
a :< t (Cofree t a)
as) = a -> m
f a
a forall a. Semigroup a => a -> a -> a
<> forall (t :: * -> *) m a.
(Foldable1 t, Semigroup m) =>
(a -> m) -> t a -> m
foldMap1 Cofree t a -> m
go t (Cofree t a)
as
  {-# INLINE foldMap1 #-}
instance Traversable f => Traversable (Cofree f) where
  traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Cofree f a -> f (Cofree f b)
traverse a -> f b
f = forall {f :: * -> *}. Traversable f => Cofree f a -> f (Cofree f b)
go where
    go :: Cofree f a -> f (Cofree f b)
go (a
a :< f (Cofree f a)
as) = forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
(:<) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Cofree f a -> f (Cofree f b)
go f (Cofree f a)
as
  {-# INLINE traverse #-}
instance Traversable1 f => Traversable1 (Cofree f) where
  traverse1 :: forall (f :: * -> *) a b.
Apply f =>
(a -> f b) -> Cofree f a -> f (Cofree f b)
traverse1 a -> f b
f = forall {f :: * -> *}.
Traversable1 f =>
Cofree f a -> f (Cofree f b)
go where
    go :: Cofree f a -> f (Cofree f b)
go (a
a :< f (Cofree f a)
as) = forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
(:<) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
<.> forall (t :: * -> *) (f :: * -> *) a b.
(Traversable1 t, Apply f) =>
(a -> f b) -> t a -> f (t b)
traverse1 Cofree f a -> f (Cofree f b)
go f (Cofree f a)
as
  {-# INLINE traverse1 #-}
instance FunctorWithIndex i f => FunctorWithIndex [i] (Cofree f) where
  imap :: forall a b. ([i] -> a -> b) -> Cofree f a -> Cofree f b
imap [i] -> a -> b
f (a
a :< f (Cofree f a)
as) = [i] -> a -> b
f [] a
a forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< forall i (f :: * -> *) a b.
FunctorWithIndex i f =>
(i -> a -> b) -> f a -> f b
imap (\i
i -> forall i (f :: * -> *) a b.
FunctorWithIndex i f =>
(i -> a -> b) -> f a -> f b
imap ([i] -> a -> b
f forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (:) i
i)) f (Cofree f a)
as
  {-# INLINE imap #-}
instance FoldableWithIndex i f => FoldableWithIndex [i] (Cofree f) where
  ifoldMap :: forall m a. Monoid m => ([i] -> a -> m) -> Cofree f a -> m
ifoldMap [i] -> a -> m
f (a
a :< f (Cofree f a)
as) = [i] -> a -> m
f [] a
a forall a. Monoid a => a -> a -> a
`mappend` forall i (f :: * -> *) m a.
(FoldableWithIndex i f, Monoid m) =>
(i -> a -> m) -> f a -> m
ifoldMap (\i
i -> forall i (f :: * -> *) m a.
(FoldableWithIndex i f, Monoid m) =>
(i -> a -> m) -> f a -> m
ifoldMap ([i] -> a -> m
f forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (:) i
i)) f (Cofree f a)
as
  {-# INLINE ifoldMap #-}
instance TraversableWithIndex i f => TraversableWithIndex [i] (Cofree f) where
  itraverse :: forall (f :: * -> *) a b.
Applicative f =>
([i] -> a -> f b) -> Cofree f a -> f (Cofree f b)
itraverse [i] -> a -> f b
f (a
a :< f (Cofree f a)
as) = forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
(:<) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [i] -> a -> f b
f [] a
a forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall i (t :: * -> *) (f :: * -> *) a b.
(TraversableWithIndex i t, Applicative f) =>
(i -> a -> f b) -> t a -> f (t b)
itraverse (\i
i -> forall i (t :: * -> *) (f :: * -> *) a b.
(TraversableWithIndex i t, Applicative f) =>
(i -> a -> f b) -> t a -> f (t b)
itraverse ([i] -> a -> f b
f forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (:) i
i)) f (Cofree f a)
as
  {-# INLINE itraverse #-}
instance ComonadHoist Cofree where
  cohoist :: forall (w :: * -> *) (v :: * -> *) a.
(Comonad w, Comonad v) =>
(forall x. w x -> v x) -> Cofree w a -> Cofree v a
cohoist = forall (f :: * -> *) (g :: * -> *) a.
Functor f =>
(forall x. f x -> g x) -> Cofree f a -> Cofree g a
hoistCofree
instance ComonadEnv e w => ComonadEnv e (Cofree w) where
  ask :: forall a. Cofree w a -> e
ask = forall e (w :: * -> *) a. ComonadEnv e w => w a -> e
ask forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall (t :: (* -> *) -> * -> *) (w :: * -> *) a.
(ComonadTrans t, Comonad w) =>
t w a -> w a
lower
  {-# INLINE ask #-}
instance ComonadStore s w => ComonadStore s (Cofree w) where
  pos :: forall a. Cofree w a -> s
pos (a
_ :< w (Cofree w a)
as) = forall s (w :: * -> *) a. ComonadStore s w => w a -> s
Class.pos w (Cofree w a)
as
  {-# INLINE pos #-}
  peek :: forall a. s -> Cofree w a -> a
peek s
s (a
_ :< w (Cofree w a)
as) = forall (w :: * -> *) a. Comonad w => w a -> a
extract (forall s (w :: * -> *) a. ComonadStore s w => s -> w a -> a
Class.peek s
s w (Cofree w a)
as)
  {-# INLINE peek #-}
instance ComonadTraced m w => ComonadTraced m (Cofree w) where
  trace :: forall a. m -> Cofree w a -> a
trace m
m = forall m (w :: * -> *) a. ComonadTraced m w => m -> w a -> a
trace m
m forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall (t :: (* -> *) -> * -> *) (w :: * -> *) a.
(ComonadTrans t, Comonad w) =>
t w a -> w a
lower
  {-# INLINE trace #-}
_extract :: Functor f => (a -> f a) -> Cofree g a -> f (Cofree g a)
 a -> f a
f (a
a :< g (Cofree g a)
as) = (forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< g (Cofree g a)
as) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f a
f a
a
{-# INLINE _extract #-}
_unwrap :: Functor f => (g (Cofree g a) -> f (g (Cofree g a))) -> Cofree g a -> f (Cofree g a)
_unwrap :: forall (f :: * -> *) (g :: * -> *) a.
Functor f =>
(g (Cofree g a) -> f (g (Cofree g a)))
-> Cofree g a -> f (Cofree g a)
_unwrap  g (Cofree g a) -> f (g (Cofree g a))
f (a
a :< g (Cofree g a)
as) = (a
a forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:<) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> g (Cofree g a) -> f (g (Cofree g a))
f g (Cofree g a)
as
{-# INLINE _unwrap #-}
telescoped :: Functor f =>
             [(Cofree g a -> f (Cofree g a)) -> g (Cofree g a) -> f (g (Cofree g a))] ->
              (a -> f a) -> Cofree g a -> f (Cofree g a)
telescoped :: forall (f :: * -> *) (g :: * -> *) a.
Functor f =>
[(Cofree g a -> f (Cofree g a))
 -> g (Cofree g a) -> f (g (Cofree g a))]
-> (a -> f a) -> Cofree g a -> f (Cofree g a)
telescoped = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
Prelude.foldr (\(Cofree g a -> f (Cofree g a))
-> g (Cofree g a) -> f (g (Cofree g a))
l (a -> f a) -> Cofree g a -> f (Cofree g a)
r -> forall (f :: * -> *) (g :: * -> *) a.
Functor f =>
(g (Cofree g a) -> f (g (Cofree g a)))
-> Cofree g a -> f (Cofree g a)
_unwrap forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Cofree g a -> f (Cofree g a))
-> g (Cofree g a) -> f (g (Cofree g a))
l forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (a -> f a) -> Cofree g a -> f (Cofree g a)
r) forall (f :: * -> *) a (g :: * -> *).
Functor f =>
(a -> f a) -> Cofree g a -> f (Cofree g a)
_extract
{-# INLINE telescoped #-}
telescoped_ :: Functor f =>
              [(Cofree g a -> f (Cofree g a)) -> g (Cofree g a) -> f (g (Cofree g a))] ->
              (Cofree g a -> f (Cofree g a)) -> Cofree g a -> f (Cofree g a)
telescoped_ :: forall (f :: * -> *) (g :: * -> *) a.
Functor f =>
[(Cofree g a -> f (Cofree g a))
 -> g (Cofree g a) -> f (g (Cofree g a))]
-> (Cofree g a -> f (Cofree g a)) -> Cofree g a -> f (Cofree g a)
telescoped_ = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
Prelude.foldr (\(Cofree g a -> f (Cofree g a))
-> g (Cofree g a) -> f (g (Cofree g a))
l (Cofree g a -> f (Cofree g a)) -> Cofree g a -> f (Cofree g a)
r -> forall (f :: * -> *) (g :: * -> *) a.
Functor f =>
(g (Cofree g a) -> f (g (Cofree g a)))
-> Cofree g a -> f (Cofree g a)
_unwrap forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Cofree g a -> f (Cofree g a))
-> g (Cofree g a) -> f (g (Cofree g a))
l forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Cofree g a -> f (Cofree g a)) -> Cofree g a -> f (Cofree g a)
r) forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
{-# INLINE telescoped_ #-}
shoots :: (Applicative f, Traversable g) => (a -> f a) -> Cofree g a -> f (Cofree g a)
shoots :: forall (f :: * -> *) (g :: * -> *) a.
(Applicative f, Traversable g) =>
(a -> f a) -> Cofree g a -> f (Cofree g a)
shoots a -> f a
f = forall {t :: * -> *}. Traversable t => Cofree t a -> f (Cofree t a)
go
  where
    go :: Cofree t a -> f (Cofree t a)
go xxs :: Cofree t a
xxs@(a
x :< t (Cofree t a)
xs) | forall (t :: * -> *) a. Foldable t => t a -> Bool
null t (Cofree t a)
xs          = forall (f :: * -> *) a. Applicative f => a -> f a
pure Cofree t a
xxs
                     | Bool
otherwise        = forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
(:<) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f a
f a
x forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Cofree t a -> f (Cofree t a)
go t (Cofree t a)
xs
{-# INLINE shoots #-}
leaves :: (Applicative f, Traversable g) => (a -> f a) -> Cofree g a -> f (Cofree g a)
leaves :: forall (f :: * -> *) (g :: * -> *) a.
(Applicative f, Traversable g) =>
(a -> f a) -> Cofree g a -> f (Cofree g a)
leaves a -> f a
f = forall {t :: * -> *}. Traversable t => Cofree t a -> f (Cofree t a)
go
  where
    go :: Cofree t a -> f (Cofree t a)
go (a
x :< t (Cofree t a)
xs) | forall (t :: * -> *) a. Foldable t => t a -> Bool
null t (Cofree t a)
xs          = (forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:< t (Cofree t a)
xs) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f a
f a
x
                 | Bool
otherwise        = (a
x forall (f :: * -> *) a. a -> f (Cofree f a) -> Cofree f a
:<) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Cofree t a -> f (Cofree t a)
go t (Cofree t a)
xs
{-# INLINE leaves #-}