free-functors-1.0.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 # 
Instance details

Defined in Data.Functor.HHCofree

Methods

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

ProfunctorComonad (HHCofree c) Source # 
Instance details

Defined in Data.Functor.HHCofree

BifunctorComonad (HHCofree c :: (Type -> Type -> Type) -> Type -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.HHCofree

Methods

biextract :: HHCofree c p :-> p #

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

biduplicate :: HHCofree c p :-> HHCofree c (HHCofree c p) #

BifunctorFunctor (HHCofree c :: (Type -> Type -> Type) -> Type -> Type -> Type) Source # 
Instance details

Defined in Data.Functor.HHCofree

Methods

bifmap :: (p :-> q) -> HHCofree c p :-> HHCofree c q #

(forall (x :: Type -> Type -> Type). c x => Bifunctor x) => Bifunctor (HHCofree c g) Source # 
Instance details

Defined in Data.Functor.HHCofree

Methods

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

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

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

(forall (x :: Type -> Type -> Type). c x => Choice x) => Choice (HHCofree c f) Source # 
Instance details

Defined in Data.Functor.HHCofree

Methods

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

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

(forall (x :: Type -> Type -> Type). c x => Closed x) => Closed (HHCofree c f) Source # 
Instance details

Defined in Data.Functor.HHCofree

Methods

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

(forall (x :: Type -> Type -> Type). c x => Strong x) => Strong (HHCofree c f) Source # 
Instance details

Defined in Data.Functor.HHCofree

Methods

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

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

(forall (x :: Type -> Type -> Type). c x => Profunctor x) => Profunctor (HHCofree c g) Source # 
Instance details

Defined in Data.Functor.HHCofree

Methods

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

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

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

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

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

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 #