free-functors-0.8.1: Free functors, adjoint to functors that forget class constraints.

LicenseBSD-style (see the file LICENSE)
Maintainersjoerd@w3future.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe
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

SuperClass1 (* -> *) Functor c => Functor (HCofree c g) Source # 

Methods

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

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

SuperClass1 (* -> *) Foldable c => Foldable (HCofree c g) Source # 

Methods

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

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

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

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

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

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

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

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

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

null :: HCofree c g a -> Bool #

length :: HCofree c g a -> Int #

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

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

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

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

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

SuperClass1 (* -> *) Traversable c => Traversable (HCofree c g) Source # 

Methods

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

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

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

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

SuperClass1 (* -> *) Comonad c => Comonad (HCofree c g) Source #

The cofree comonad of a functor.

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 #

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 #