Copyright | (C) 2008-2013 Edward Kmett |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | provisional |
Portability | MPTCs, fundeps |
Safe Haskell | Safe |
Language | Haskell2010 |
The cofree comonad transformer
- newtype CofreeT f w a = CofreeT {
- runCofreeT :: w (CofreeF f a (CofreeT f w a))
- type Cofree f = CofreeT f Identity
- cofree :: CofreeF f a (Cofree f a) -> Cofree f a
- runCofree :: Cofree f a -> CofreeF f a (Cofree f a)
- data CofreeF f a b = a :< (f b)
- class (Functor f, Comonad w) => ComonadCofree f w | w -> f where
- headF :: CofreeF f a b -> a
- tailF :: CofreeF f a b -> f b
- transCofreeT :: (Functor g, Comonad w) => (forall x. f x -> g x) -> CofreeT f w a -> CofreeT g w a
- coiterT :: (Functor f, Comonad w) => (w a -> f (w a)) -> w a -> CofreeT f w a
Documentation
newtype CofreeT f w a Source #
This is a cofree comonad of some functor f
, with a comonad w
threaded through it at each level.
CofreeT | |
|
cofree :: CofreeF f a (Cofree f a) -> Cofree f a Source #
Wrap another layer around a cofree comonad value.
cofree
is a right inverse of runCofree
.
runCofree . cofree == id
runCofree :: Cofree f a -> CofreeF f a (Cofree f a) Source #
Unpeel the first layer off a cofree comonad value.
runCofree
is a right inverse of cofree
.
cofree . runCofree == id
This is the base functor of the cofree comonad transformer.
a :< (f b) infixr 5 |
Traversable f => Bitraversable (CofreeF f) Source # | |
Foldable f => Bifoldable (CofreeF f) Source # | |
Functor f => Bifunctor (CofreeF f) Source # | |
Functor f => Functor (CofreeF f a) Source # | |
Foldable f => Foldable (CofreeF f a) Source # | |
Traversable f => Traversable (CofreeF f a) Source # | |
(Eq (f b), Eq a) => Eq (CofreeF f a b) Source # | |
(Typeable (* -> *) f, Typeable * a, Typeable * b, Data a, Data (f b), Data b) => Data (CofreeF f a b) Source # | |
(Ord (f b), Ord a) => Ord (CofreeF f a b) Source # | |
(Read (f b), Read a) => Read (CofreeF f a b) Source # | |
(Show (f b), Show a) => Show (CofreeF f a b) Source # | |
class (Functor f, Comonad w) => ComonadCofree f w | w -> f where Source #
Allows you to peel a layer off a cofree comonad.
ComonadCofree [] Tree Source # | |
ComonadCofree Maybe NonEmpty Source # | |
Functor f => ComonadCofree f (Cofree f) Source # | |
Comonad w => ComonadCofree Identity (CoiterT w) Source # | |
(ComonadCofree f w, Monoid m) => ComonadCofree f (TracedT m w) Source # | |
ComonadCofree f w => ComonadCofree f (StoreT s w) Source # | |
ComonadCofree f w => ComonadCofree f (EnvT e w) Source # | |
ComonadCofree f w => ComonadCofree f (IdentityT * w) Source # | |
(Functor f, Comonad w) => ComonadCofree f (CofreeT f w) Source # | |
ComonadCofree (Const * b) ((,) b) Source # | |