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.HHCofree

Description

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

Compared to Data.Functor.HCofree we have 2 two parameters.

Synopsis

Documentation

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

Natural transformations.

data HHCofree c g a b where Source #

The higher order cofree functor for constraint c.

Constructors

HHCofree :: c f => (f :~~> g) -> f a b -> HHCofree c g a b 

Instances

ProfunctorFunctor (HHCofree c) Source # 

Methods

promap :: Profunctor p => (p :-> q) -> HHCofree c p :-> HHCofree c q #

ProfunctorComonad (HHCofree c) Source # 
BifunctorComonad * * (HHCofree c) Source # 

Methods

biextract :: t p a b -> p a b #

biextend :: (HHCofree c :-> k1) (t p) q -> (HHCofree c :-> k1) (t p) (t q) #

biduplicate :: t p a b -> t (t p) a b #

BifunctorFunctor * * * * (HHCofree c) Source # 

Methods

bifmap :: (k2 :-> k3) p q -> (HHCofree c :-> k1) (t p) (t q) #

SuperClass1 (* -> * -> *) Bifunctor c => Bifunctor (HHCofree c g) Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> HHCofree c g a c -> HHCofree c g b d #

first :: (a -> b) -> HHCofree c g a c -> HHCofree c g b c #

second :: (b -> c) -> HHCofree c g a b -> HHCofree c g a c #

SuperClass1 (* -> * -> *) Closed c => Closed (HHCofree c f) Source # 

Methods

closed :: HHCofree c f a b -> HHCofree c f (x -> a) (x -> b) #

SuperClass1 (* -> * -> *) Choice c => Choice (HHCofree c f) Source # 

Methods

left' :: HHCofree c f a b -> HHCofree c f (Either a c) (Either b c) #

right' :: HHCofree c f a b -> HHCofree c f (Either c a) (Either c b) #

SuperClass1 (* -> * -> *) Strong c => Strong (HHCofree c f) Source # 

Methods

first' :: HHCofree c f a b -> HHCofree c f (a, c) (b, c) #

second' :: HHCofree c f a b -> HHCofree c f (c, a) (c, b) #

SuperClass1 (* -> * -> *) Profunctor c => Profunctor (HHCofree c g) Source # 

Methods

dimap :: (a -> b) -> (c -> d) -> HHCofree c g b c -> HHCofree c g a d #

lmap :: (a -> b) -> HHCofree c g b c -> HHCofree c g a c #

rmap :: (b -> c) -> HHCofree c g a b -> HHCofree c g a c #

(#.) :: Coercible * c b => (b -> c) -> HHCofree c g a b -> HHCofree c g a c #

(.#) :: Coercible * b a => HHCofree c g b c -> (a -> b) -> HHCofree c g a c #

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

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

unit = leftAdjunct id

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

rightAdjunct f = counit . f

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

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