free-functors-1.1.2: Free functors, adjoint to functors that forget class constraints.
LicenseBSD-style (see the file LICENSE)
Maintainersjoerd@w3future.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Functor.HCofree

Description

A cofree functor is right adjoint to a forgetful functor. In this package the forgetful functor forgets class constraints.

Compared to Data.Functor.Cofree we're going up a level. These free functors go between categories of functors and the natural transformations between them.

Synopsis

Documentation

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

Natural transformations.

data HCofree c g a where Source #

The higher order cofree functor for constraint c.

Constructors

HCofree :: c f => (f :~> g) -> f a -> HCofree c g a 

Instances

Instances details
c ~=> Functor => Functor (HCofree c a) Source # 
Instance details

Defined in Data.Functor.HCofree

Methods

fmap :: (a0 -> b) -> HCofree c a a0 -> HCofree c a b #

(<$) :: a0 -> HCofree c a b -> HCofree c a a0 #

c ~=> Foldable => Foldable (HCofree c a) Source # 
Instance details

Defined in Data.Functor.HCofree

Methods

fold :: Monoid m => HCofree c a m -> m #

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

foldMap' :: Monoid m => (a0 -> m) -> HCofree c a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> HCofree c a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> HCofree c a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> HCofree c a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> HCofree c a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> HCofree c a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> HCofree c a a0 -> a0 #

toList :: HCofree c a a0 -> [a0] #

null :: HCofree c a a0 -> Bool #

length :: HCofree c a a0 -> Int #

elem :: Eq a0 => a0 -> HCofree c a a0 -> Bool #

maximum :: Ord a0 => HCofree c a a0 -> a0 #

minimum :: Ord a0 => HCofree c a a0 -> a0 #

sum :: Num a0 => HCofree c a a0 -> a0 #

product :: Num a0 => HCofree c a a0 -> a0 #

c ~=> Traversable => Traversable (HCofree c a) Source # 
Instance details

Defined in Data.Functor.HCofree

Methods

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

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

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

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

c ~=> Comonad => Comonad (HCofree c g) Source #

The cofree comonad of a functor.

Instance details

Defined in Data.Functor.HCofree

Methods

extract :: HCofree c g a -> a #

duplicate :: HCofree c g a -> HCofree c g (HCofree c g a) #

extend :: (HCofree c g a -> b) -> HCofree c g a -> HCofree c g b #

deriveHCofreeInstance :: Name -> Q [Dec] Source #

Derive the instance of HCofree c a for the class c.

For example:

deriveHCofreeInstance ''Traversable

leftAdjunct :: c f => (f :~> g) -> f :~> HCofree c g Source #

unit :: c g => g :~> HCofree c g Source #

unit = leftAdjunct id

rightAdjunct :: (f :~> HCofree c g) -> f :~> g Source #

rightAdjunct f = counit . f

transform :: (forall r. c r => (r :~> f) -> r :~> g) -> HCofree c f :~> HCofree c g Source #

hfmap :: (f :~> g) -> HCofree c f :~> HCofree c g Source #

hextend :: (HCofree c f :~> g) -> HCofree c f :~> HCofree c g Source #

liftCofree :: c f => f a -> HCofree c f a Source #

lowerCofree :: HCofree c f a -> f a Source #

convert :: (c (t f), Comonad f, ComonadTrans t) => t f a -> HCofree c f a Source #

coiter :: c Identity => (forall b. b -> f b) -> a -> HCofree c f a Source #