Portability | non-portable (class-associated types) |
---|---|
Stability | experimental |
Maintainer | Edward Kmett <ekmett@gmail.com> |
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.
- newtype CompF f g a = CompF {
- runCompF :: f (g a)
- class Composition o where
- associateComposition :: (Functor f, Composition o) => ((f `o` g) `o` h) :~> (f `o` (g `o` h))
- coassociateComposition :: (Functor f, Composition o) => (f `o` (g `o` h)) :~> ((f `o` g) `o` h)
- type :.: = CompF
- preTransform :: Composition o => (f :~> g) -> (f `o` k) :~> (g `o` k)
- postTransform :: (Functor k, Composition o) => (f :~> g) -> (k `o` f) :~> (k `o` g)
- data Comp p f g a b
- type :++: = Comp Either
- type :**: = Comp (,)
- 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 d
Documentation
Basic functor composition
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 ()) |
class Composition o whereSource
associateComposition :: (Functor f, Composition o) => ((f `o` g) `o` h) :~> (f `o` (g `o` h))Source
The only reason the compositions are all the same is for type inference. This can be liberalized.
coassociateComposition :: (Functor f, Composition o) => (f `o` (g `o` h)) :~> ((f `o` g) `o` h)Source
preTransform :: Composition o => (f :~> g) -> (f `o` k) :~> (g `o` k)Source
postTransform :: (Functor k, Composition o) => (f :~> g) -> (k `o` f) :~> (k `o` g)Source
Bifunctor composition
(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) |