category-extras-0.52.3: Various modules and constructs inspired by category theory

Portabilitynon-portable (class-associated types)
Stabilityexperimental
MaintainerEdward Kmett <ekmett@gmail.com>

Control.Functor.Composition

Description

Generalized functor composition. Since we have many reasons for which you might want to compose a functor, and many expected results. i.e. monads via adjunctions, monads via composition with a pointed endofunctor, etc. we have to make multiple composition operators.

Synopsis

Documentation

newtype CompF f g a Source

Basic functor composition

Constructors

CompF 

Fields

runCompF :: f (g a)
 

Instances

Composition CompF 
Functor f => HFunctor (CompF f) 
(Functor f, Functor g) => Functor (CompF f g) 
(Full f, Full g) => Full (CompF f g) 
(ExpFunctor f, ExpFunctor g) => ExpFunctor (CompF f g) 
(Adjunction f1 g1, Adjunction f2 g2) => Adjunction (CompF f2 f1) (CompF g1 g2) 
(Adjunction f1 g1, Adjunction f2 g2) => Representable (CompF g1 g2) (CompF f2 f1 ()) 

associateComposition :: (Functor f, Composition c) => c (c f g) h a -> c f (c g h) aSource

The only reason the compositions are all the same is for type inference. This can be liberalized.

coassociateComposition :: (Functor f, Composition c) => c f (c g h) a -> c (c f g) h aSource

type :.: = CompFSource

An infix alias for functor composition

data Comp p f g a b Source

Bifunctor composition

Instances

(Bifunctor p Hask Hask Hask, Symmetric Hask f, Symmetric Hask g) => Symmetric Hask (Comp p f g) 
(Bifunctor p Hask Hask Hask, Braided Hask f, Braided Hask g) => Braided Hask (Comp p f g) 
(Bifunctor p c d Hask, QFunctor f b c, QFunctor g b d) => QFunctor (Comp p f g) b Hask 
(Bifunctor p c d Hask, PFunctor f a c, PFunctor g a d) => PFunctor (Comp p f g) a Hask 
(Bifunctor p c d Hask, Bifunctor f a b c, Bifunctor g a b d) => Bifunctor (Comp p f g) a b Hask 
(Bifunctor p Hask Hask Hask, Bifunctor f Hask Hask Hask, Bifunctor g Hask Hask Hask) => Functor (Comp p f g a) 

type :++: = Comp EitherSource

Bifunctor coproduct

type :**: = Comp (,)Source

Bifunctor product

liftComp :: Bifunctor p r s Hask => r (f a b) (f c d) -> s (g a b) (g c d) -> Comp p f g a b -> Comp p f g c dSource