-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Profunctors -- -- Profunctors @package profunctors @version 5.2 -- | For a good explanation of profunctors in Haskell see Dan Piponi's -- article: -- -- http://blog.sigfpe.com/2011/07/profunctors-in-haskell.html -- -- This module includes unsafe composition operators that are -- useful in practice when it comes to generating optimal core in GHC. -- -- If you import this module you are taking upon yourself the obligation -- that you will only call the operators with # in their names -- with functions that are operationally identity such as -- newtype constructors or the field accessor of a -- newtype. -- -- If you are ever in doubt, use rmap or lmap. module Data.Profunctor.Unsafe -- | Formally, the class Profunctor represents a profunctor from -- Hask -> Hask. -- -- Intuitively it is a bifunctor where the first argument is -- contravariant and the second argument is covariant. -- -- You can define a Profunctor by either defining dimap or -- by defining both lmap and rmap. -- -- If you supply dimap, you should ensure that: -- --
--   dimap id idid
--   
-- -- If you supply lmap and rmap, ensure: -- --
--   lmap idid
--   rmap idid
--   
-- -- If you supply both, you should also ensure: -- --
--   dimap f g ≡ lmap f . rmap g
--   
-- -- These ensure by parametricity: -- --
--   dimap (f . g) (h . i) ≡ dimap g h . dimap f i
--   lmap (f . g) ≡ lmap g . lmap f
--   rmap (f . g) ≡ rmap f . rmap g
--   
class Profunctor p where dimap f g = lmap f . rmap g lmap f = dimap f id rmap = dimap id (#.) = \ f -> \ p -> p `seq` rmap f p (.#) = \ p -> p `seq` \ f -> lmap f p -- | Map over both arguments at the same time. -- --
--   dimap f g ≡ lmap f . rmap g
--   
dimap :: Profunctor p => (a -> b) -> (c -> d) -> p b c -> p a d -- | Map the first argument contravariantly. -- --
--   lmap f ≡ dimap f id
--   
lmap :: Profunctor p => (a -> b) -> p b c -> p a c -- | Map the second argument covariantly. -- --
--   rmapdimap id
--   
rmap :: Profunctor p => (b -> c) -> p a b -> p a c -- | Strictly map the second argument argument covariantly with a function -- that is assumed operationally to be a cast, such as a newtype -- constructor. -- -- Note: This operation is explicitly unsafe since an -- implementation may choose to use unsafeCoerce to implement -- this combinator and it has no way to validate that your function meets -- the requirements. -- -- If you implement this combinator with unsafeCoerce, then you -- are taking upon yourself the obligation that you don't use GADT-like -- tricks to distinguish values. -- -- If you import Data.Profunctor.Unsafe you are taking upon -- yourself the obligation that you will only call this with a first -- argument that is operationally identity. -- -- The semantics of this function with respect to bottoms should match -- the default definition: -- --
--   (#.) ≡ \f -> \p -> p `seq` rmap f p
--   
(#.) :: (Profunctor p, Coercible c b) => (b -> c) -> p a b -> p a c -- | Strictly map the first argument argument contravariantly with a -- function that is assumed operationally to be a cast, such as a newtype -- constructor. -- -- Note: This operation is explicitly unsafe since an -- implementation may choose to use unsafeCoerce to implement -- this combinator and it has no way to validate that your function meets -- the requirements. -- -- If you implement this combinator with unsafeCoerce, then you -- are taking upon yourself the obligation that you don't use GADT-like -- tricks to distinguish values. -- -- If you import Data.Profunctor.Unsafe you are taking upon -- yourself the obligation that you will only call this with a second -- argument that is operationally identity. -- --
--   (.#) ≡ \p -> p `seq` \f -> lmap f p
--   
(.#) :: (Profunctor p, Coercible b a) => p b c -> (a -> b) -> p a c instance Data.Profunctor.Unsafe.Profunctor (->) instance Data.Profunctor.Unsafe.Profunctor Data.Tagged.Tagged instance GHC.Base.Monad m => Data.Profunctor.Unsafe.Profunctor (Control.Arrow.Kleisli m) instance GHC.Base.Functor w => Data.Profunctor.Unsafe.Profunctor (Control.Comonad.Cokleisli w) instance Data.Functor.Contravariant.Contravariant f => Data.Profunctor.Unsafe.Profunctor (Data.Bifunctor.Clown.Clown f) instance GHC.Base.Functor f => Data.Profunctor.Unsafe.Profunctor (Data.Bifunctor.Joker.Joker f) instance (Data.Profunctor.Unsafe.Profunctor p, GHC.Base.Functor f, GHC.Base.Functor g) => Data.Profunctor.Unsafe.Profunctor (Data.Bifunctor.Biff.Biff p f g) instance (Data.Profunctor.Unsafe.Profunctor p, Data.Profunctor.Unsafe.Profunctor q) => Data.Profunctor.Unsafe.Profunctor (Data.Bifunctor.Product.Product p q) instance (GHC.Base.Functor f, Data.Profunctor.Unsafe.Profunctor p) => Data.Profunctor.Unsafe.Profunctor (Data.Bifunctor.Tannen.Tannen f p) -- | For a good explanation of profunctors in Haskell see Dan Piponi's -- article: -- -- http://blog.sigfpe.com/2011/07/profunctors-in-haskell.html -- -- For more information on strength and costrength, see: -- -- http://comonad.com/reader/2008/deriving-strength-from-laziness/ module Data.Profunctor.Types -- | Formally, the class Profunctor represents a profunctor from -- Hask -> Hask. -- -- Intuitively it is a bifunctor where the first argument is -- contravariant and the second argument is covariant. -- -- You can define a Profunctor by either defining dimap or -- by defining both lmap and rmap. -- -- If you supply dimap, you should ensure that: -- --
--   dimap id idid
--   
-- -- If you supply lmap and rmap, ensure: -- --
--   lmap idid
--   rmap idid
--   
-- -- If you supply both, you should also ensure: -- --
--   dimap f g ≡ lmap f . rmap g
--   
-- -- These ensure by parametricity: -- --
--   dimap (f . g) (h . i) ≡ dimap g h . dimap f i
--   lmap (f . g) ≡ lmap g . lmap f
--   rmap (f . g) ≡ rmap f . rmap g
--   
class Profunctor p where dimap f g = lmap f . rmap g lmap f = dimap f id rmap = dimap id (#.) = \ f -> \ p -> p `seq` rmap f p (.#) = \ p -> p `seq` \ f -> lmap f p -- | Map over both arguments at the same time. -- --
--   dimap f g ≡ lmap f . rmap g
--   
dimap :: Profunctor p => (a -> b) -> (c -> d) -> p b c -> p a d -- | Map the first argument contravariantly. -- --
--   lmap f ≡ dimap f id
--   
lmap :: Profunctor p => (a -> b) -> p b c -> p a c -- | Map the second argument covariantly. -- --
--   rmapdimap id
--   
rmap :: Profunctor p => (b -> c) -> p a b -> p a c -- | Lift a Functor into a Profunctor (forwards). newtype Star f d c Star :: (d -> f c) -> Star f d c [runStar] :: Star f d c -> d -> f c -- | Lift a Functor into a Profunctor (backwards). newtype Costar f d c Costar :: (f d -> c) -> Costar f d c [runCostar] :: Costar f d c -> f d -> c -- | Wrap an arrow for use as a Profunctor. newtype WrappedArrow p a b WrapArrow :: p a b -> WrappedArrow p a b [unwrapArrow] :: WrappedArrow p a b -> p a b newtype Forget r a b Forget :: (a -> r) -> Forget r a b [runForget] :: Forget r a b -> a -> r type (:->) p q = forall a b. p a b -> q a b instance GHC.Base.Functor f => Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Types.Star f) instance GHC.Base.Functor f => GHC.Base.Functor (Data.Profunctor.Types.Star f a) instance GHC.Base.Applicative f => GHC.Base.Applicative (Data.Profunctor.Types.Star f a) instance GHC.Base.Alternative f => GHC.Base.Alternative (Data.Profunctor.Types.Star f a) instance GHC.Base.Monad f => GHC.Base.Monad (Data.Profunctor.Types.Star f a) instance GHC.Base.MonadPlus f => GHC.Base.MonadPlus (Data.Profunctor.Types.Star f a) instance Data.Distributive.Distributive f => Data.Distributive.Distributive (Data.Profunctor.Types.Star f a) instance GHC.Base.Functor f => Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Types.Costar f) instance Data.Distributive.Distributive (Data.Profunctor.Types.Costar f d) instance GHC.Base.Functor (Data.Profunctor.Types.Costar f a) instance GHC.Base.Applicative (Data.Profunctor.Types.Costar f a) instance GHC.Base.Monad (Data.Profunctor.Types.Costar f a) instance Control.Category.Category p => Control.Category.Category (Data.Profunctor.Types.WrappedArrow p) instance Control.Arrow.Arrow p => Control.Arrow.Arrow (Data.Profunctor.Types.WrappedArrow p) instance Control.Arrow.ArrowZero p => Control.Arrow.ArrowZero (Data.Profunctor.Types.WrappedArrow p) instance Control.Arrow.ArrowChoice p => Control.Arrow.ArrowChoice (Data.Profunctor.Types.WrappedArrow p) instance Control.Arrow.ArrowApply p => Control.Arrow.ArrowApply (Data.Profunctor.Types.WrappedArrow p) instance Control.Arrow.ArrowLoop p => Control.Arrow.ArrowLoop (Data.Profunctor.Types.WrappedArrow p) instance Control.Arrow.Arrow p => Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Types.WrappedArrow p) instance Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Types.Forget r) instance GHC.Base.Functor (Data.Profunctor.Types.Forget r a) instance Data.Foldable.Foldable (Data.Profunctor.Types.Forget r a) instance Data.Traversable.Traversable (Data.Profunctor.Types.Forget r a) module Data.Profunctor.Monad class ProfunctorFunctor t promap :: (ProfunctorFunctor t, Profunctor p) => (p :-> q) -> t p :-> t q class ProfunctorFunctor t => ProfunctorMonad t proreturn :: (ProfunctorMonad t, Profunctor p) => p :-> t p projoin :: (ProfunctorMonad t, Profunctor p) => t (t p) :-> t p class ProfunctorFunctor t => ProfunctorComonad t proextract :: (ProfunctorComonad t, Profunctor p) => t p :-> p produplicate :: (ProfunctorComonad t, Profunctor p) => t p :-> t (t p) instance GHC.Base.Functor f => Data.Profunctor.Monad.ProfunctorFunctor (Data.Bifunctor.Tannen.Tannen f) instance Data.Profunctor.Monad.ProfunctorFunctor (Data.Bifunctor.Product.Product p) instance Data.Profunctor.Monad.ProfunctorFunctor (Data.Bifunctor.Sum.Sum p) instance GHC.Base.Monad f => Data.Profunctor.Monad.ProfunctorMonad (Data.Bifunctor.Tannen.Tannen f) instance Data.Profunctor.Monad.ProfunctorMonad (Data.Bifunctor.Sum.Sum p) instance Control.Comonad.Comonad f => Data.Profunctor.Monad.ProfunctorComonad (Data.Bifunctor.Tannen.Tannen f) instance Data.Profunctor.Monad.ProfunctorComonad (Data.Bifunctor.Product.Product p) module Data.Profunctor.Adjunction class (ProfunctorFunctor f, ProfunctorFunctor u) => ProfunctorAdjunction f u | f -> u, u -> f unit :: (ProfunctorAdjunction f u, Profunctor p) => p :-> u (f p) counit :: (ProfunctorAdjunction f u, Profunctor p) => f (u p) :-> p module Data.Profunctor.Strong -- | Generalizing Star of a strong Functor -- -- Note: Every Functor in Haskell is strong with respect to -- (,). -- -- This describes profunctor strength with respect to the product -- structure of Hask. -- -- http://www-kb.is.s.u-tokyo.ac.jp/~asada/papers/arrStrMnd.pdf class Profunctor p => Strong p where first' = dimap swap swap . second' second' = dimap swap swap . first' first' :: Strong p => p a b -> p (a, c) (b, c) second' :: Strong p => p a b -> p (c, a) (c, b) uncurry' :: Strong p => p a (b -> c) -> p (a, b) c -- | Tambara cofreely makes any Profunctor Strong. newtype Tambara p a b Tambara :: (forall c. p (a, c) (b, c)) -> Tambara p a b [runTambara] :: Tambara p a b -> forall c. p (a, c) (b, c) -- |
--   tambara . untambaraid
--   untambara . tambaraid
--   
tambara :: Strong p => (p :-> q) -> p :-> Tambara q -- |
--   tambara . untambaraid
--   untambara . tambaraid
--   
untambara :: Profunctor q => (p :-> Tambara q) -> p :-> q -- | Pastro -| Tambara -- --
--   Pastro p ~ exists z. Costar ((,)z) Procompose p Procompose Star ((,)z)
--   
-- -- Pastro freely makes any Profunctor Strong. data Pastro p a b [Pastro] :: ((y, z) -> b) -> p x y -> (a -> (x, z)) -> Pastro p a b -- | Analogous to ArrowLoop, loop = unfirst class Profunctor p => Costrong p where unfirst = unsecond . dimap swap swap unsecond = unfirst . dimap swap swap unfirst :: Costrong p => p (a, d) (b, d) -> p a b unsecond :: Costrong p => p (d, a) (d, b) -> p a b -- | Cotambara cofreely constructs costrength data Cotambara q a b [Cotambara] :: Costrong r => (r :-> q) -> r a b -> Cotambara q a b -- |
--   cotambara . uncotambaraid
--   uncotambara . cotambaraid
--   
cotambara :: Costrong p => (p :-> q) -> p :-> Cotambara q -- |
--   cotambara . uncotambaraid
--   uncotambara . cotambaraid
--   
uncotambara :: Profunctor q => (p :-> Cotambara q) -> p :-> q -- | Copastro -| Cotambara -- -- Copastro freely constructs costrength newtype Copastro p a b Copastro :: (forall r. Costrong r => (forall x y. p x y -> r x y) -> r a b) -> Copastro p a b [runCopastro] :: Copastro p a b -> forall r. Costrong r => (forall x y. p x y -> r x y) -> r a b instance Data.Profunctor.Strong.Strong (->) instance GHC.Base.Monad m => Data.Profunctor.Strong.Strong (Control.Arrow.Kleisli m) instance GHC.Base.Functor m => Data.Profunctor.Strong.Strong (Data.Profunctor.Types.Star m) instance Control.Arrow.Arrow p => Data.Profunctor.Strong.Strong (Data.Profunctor.Types.WrappedArrow p) instance Data.Profunctor.Strong.Strong (Data.Profunctor.Types.Forget r) instance Data.Functor.Contravariant.Contravariant f => Data.Profunctor.Strong.Strong (Data.Bifunctor.Clown.Clown f) instance (Data.Profunctor.Strong.Strong p, Data.Profunctor.Strong.Strong q) => Data.Profunctor.Strong.Strong (Data.Bifunctor.Product.Product p q) instance (GHC.Base.Functor f, Data.Profunctor.Strong.Strong p) => Data.Profunctor.Strong.Strong (Data.Bifunctor.Tannen.Tannen f p) instance Data.Profunctor.Unsafe.Profunctor p => Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Strong.Tambara p) instance Data.Profunctor.Monad.ProfunctorFunctor Data.Profunctor.Strong.Tambara instance Data.Profunctor.Monad.ProfunctorComonad Data.Profunctor.Strong.Tambara instance Data.Profunctor.Unsafe.Profunctor p => Data.Profunctor.Strong.Strong (Data.Profunctor.Strong.Tambara p) instance Control.Category.Category p => Control.Category.Category (Data.Profunctor.Strong.Tambara p) instance Control.Arrow.Arrow p => Control.Arrow.Arrow (Data.Profunctor.Strong.Tambara p) instance Control.Arrow.ArrowChoice p => Control.Arrow.ArrowChoice (Data.Profunctor.Strong.Tambara p) instance Control.Arrow.ArrowApply p => Control.Arrow.ArrowApply (Data.Profunctor.Strong.Tambara p) instance Control.Arrow.ArrowLoop p => Control.Arrow.ArrowLoop (Data.Profunctor.Strong.Tambara p) instance Control.Arrow.ArrowZero p => Control.Arrow.ArrowZero (Data.Profunctor.Strong.Tambara p) instance Control.Arrow.ArrowPlus p => Control.Arrow.ArrowPlus (Data.Profunctor.Strong.Tambara p) instance Data.Profunctor.Unsafe.Profunctor p => GHC.Base.Functor (Data.Profunctor.Strong.Tambara p a) instance (Data.Profunctor.Unsafe.Profunctor p, Control.Arrow.Arrow p) => GHC.Base.Applicative (Data.Profunctor.Strong.Tambara p a) instance (Data.Profunctor.Unsafe.Profunctor p, Control.Arrow.ArrowPlus p) => GHC.Base.Alternative (Data.Profunctor.Strong.Tambara p a) instance Control.Arrow.ArrowPlus p => GHC.Base.Monoid (Data.Profunctor.Strong.Tambara p a b) instance Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Strong.Pastro p) instance Data.Profunctor.Monad.ProfunctorFunctor Data.Profunctor.Strong.Pastro instance Data.Profunctor.Monad.ProfunctorMonad Data.Profunctor.Strong.Pastro instance Data.Profunctor.Adjunction.ProfunctorAdjunction Data.Profunctor.Strong.Pastro Data.Profunctor.Strong.Tambara instance Data.Profunctor.Strong.Strong (Data.Profunctor.Strong.Pastro p) instance Data.Profunctor.Strong.Costrong (->) instance GHC.Base.Functor f => Data.Profunctor.Strong.Costrong (Data.Profunctor.Types.Costar f) instance Data.Profunctor.Strong.Costrong Data.Tagged.Tagged instance Control.Arrow.ArrowLoop p => Data.Profunctor.Strong.Costrong (Data.Profunctor.Types.WrappedArrow p) instance Control.Monad.Fix.MonadFix m => Data.Profunctor.Strong.Costrong (Control.Arrow.Kleisli m) instance GHC.Base.Functor f => Data.Profunctor.Strong.Costrong (Control.Comonad.Cokleisli f) instance (GHC.Base.Functor f, Data.Profunctor.Strong.Costrong p) => Data.Profunctor.Strong.Costrong (Data.Bifunctor.Tannen.Tannen f p) instance (Data.Profunctor.Strong.Costrong p, Data.Profunctor.Strong.Costrong q) => Data.Profunctor.Strong.Costrong (Data.Bifunctor.Product.Product p q) instance Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Strong.Cotambara p) instance Data.Profunctor.Monad.ProfunctorFunctor Data.Profunctor.Strong.Cotambara instance Data.Profunctor.Monad.ProfunctorComonad Data.Profunctor.Strong.Cotambara instance Data.Profunctor.Strong.Costrong (Data.Profunctor.Strong.Cotambara p) instance GHC.Base.Functor (Data.Profunctor.Strong.Cotambara p a) instance Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Strong.Copastro p) instance Data.Profunctor.Adjunction.ProfunctorAdjunction Data.Profunctor.Strong.Copastro Data.Profunctor.Strong.Cotambara instance Data.Profunctor.Monad.ProfunctorFunctor Data.Profunctor.Strong.Copastro instance Data.Profunctor.Monad.ProfunctorMonad Data.Profunctor.Strong.Copastro instance Data.Profunctor.Strong.Costrong (Data.Profunctor.Strong.Copastro p) module Data.Profunctor.Choice -- | The generalization of Costar of Functor that is strong -- with respect to Either. -- -- Note: This is also a notion of strength, except with regards to -- another monoidal structure that we can choose to equip Hask with: the -- cocartesian coproduct. class Profunctor p => Choice p where left' = dimap (either Right Left) (either Right Left) . right' right' = dimap (either Right Left) (either Right Left) . left' left' :: Choice p => p a b -> p (Either a c) (Either b c) right' :: Choice p => p a b -> p (Either c a) (Either c b) -- | TambaraSum is cofreely adjoins strength with respect to Either. -- -- Note: this is not dual to Tambara. It is Tambara with -- respect to a different tensor. newtype TambaraSum p a b TambaraSum :: (forall c. p (Either a c) (Either b c)) -> TambaraSum p a b [runTambaraSum] :: TambaraSum p a b -> forall c. p (Either a c) (Either b c) -- |
--   tambaraSum . untambaraSumid
--   untambaraSum . tambaraSumid
--   
tambaraSum :: Choice p => (p :-> q) -> p :-> TambaraSum q -- |
--   tambaraSum . untambaraSumid
--   untambaraSum . tambaraSumid
--   
untambaraSum :: Profunctor q => (p :-> TambaraSum q) -> p :-> q -- | PastroSum -| TambaraSum -- -- PastroSum freely constructs strength with respect to Either. data PastroSum p a b [PastroSum] :: (Either y z -> b) -> p x y -> (a -> Either x z) -> PastroSum p a b class Profunctor p => Cochoice p where unleft = unright . dimap (either Right Left) (either Right Left) unright = unleft . dimap (either Right Left) (either Right Left) unleft :: Cochoice p => p (Either a d) (Either b d) -> p a b unright :: Cochoice p => p (Either d a) (Either d b) -> p a b -- | CotambaraSum cofreely constructs costrength with respect to -- Either (aka Choice) data CotambaraSum q a b [CotambaraSum] :: Cochoice r => (r :-> q) -> r a b -> CotambaraSum q a b -- |
--   cotambaraSum . uncotambaraSumid
--   uncotambaraSum . cotambaraSumid
--   
cotambaraSum :: Cochoice p => (p :-> q) -> p :-> CotambaraSum q -- |
--   cotambaraSum . uncotambaraSumid
--   uncotambaraSum . cotambaraSumid
--   
uncotambaraSum :: Profunctor q => (p :-> CotambaraSum q) -> p :-> q -- | CopastroSum -| CotambaraSum -- -- CopastroSum freely constructs costrength with respect to -- Either (aka Choice) newtype CopastroSum p a b CopastroSum :: (forall r. Cochoice r => (forall x y. p x y -> r x y) -> r a b) -> CopastroSum p a b [runCopastroSum] :: CopastroSum p a b -> forall r. Cochoice r => (forall x y. p x y -> r x y) -> r a b instance Data.Profunctor.Choice.Choice (->) instance GHC.Base.Monad m => Data.Profunctor.Choice.Choice (Control.Arrow.Kleisli m) instance GHC.Base.Applicative f => Data.Profunctor.Choice.Choice (Data.Profunctor.Types.Star f) instance Control.Comonad.Comonad w => Data.Profunctor.Choice.Choice (Control.Comonad.Cokleisli w) instance Data.Traversable.Traversable w => Data.Profunctor.Choice.Choice (Data.Profunctor.Types.Costar w) instance Data.Profunctor.Choice.Choice Data.Tagged.Tagged instance Control.Arrow.ArrowChoice p => Data.Profunctor.Choice.Choice (Data.Profunctor.Types.WrappedArrow p) instance GHC.Base.Monoid r => Data.Profunctor.Choice.Choice (Data.Profunctor.Types.Forget r) instance GHC.Base.Functor f => Data.Profunctor.Choice.Choice (Data.Bifunctor.Joker.Joker f) instance (Data.Profunctor.Choice.Choice p, Data.Profunctor.Choice.Choice q) => Data.Profunctor.Choice.Choice (Data.Bifunctor.Product.Product p q) instance (GHC.Base.Functor f, Data.Profunctor.Choice.Choice p) => Data.Profunctor.Choice.Choice (Data.Bifunctor.Tannen.Tannen f p) instance Data.Profunctor.Choice.Choice p => Data.Profunctor.Choice.Choice (Data.Profunctor.Strong.Tambara p) instance Data.Profunctor.Monad.ProfunctorFunctor Data.Profunctor.Choice.TambaraSum instance Data.Profunctor.Monad.ProfunctorComonad Data.Profunctor.Choice.TambaraSum instance Data.Profunctor.Unsafe.Profunctor p => Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Choice.TambaraSum p) instance Data.Profunctor.Unsafe.Profunctor p => Data.Profunctor.Choice.Choice (Data.Profunctor.Choice.TambaraSum p) instance Control.Category.Category p => Control.Category.Category (Data.Profunctor.Choice.TambaraSum p) instance Data.Profunctor.Unsafe.Profunctor p => GHC.Base.Functor (Data.Profunctor.Choice.TambaraSum p a) instance Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Choice.PastroSum p) instance Data.Profunctor.Adjunction.ProfunctorAdjunction Data.Profunctor.Choice.PastroSum Data.Profunctor.Choice.TambaraSum instance Data.Profunctor.Monad.ProfunctorFunctor Data.Profunctor.Choice.PastroSum instance Data.Profunctor.Monad.ProfunctorMonad Data.Profunctor.Choice.PastroSum instance Data.Profunctor.Choice.Choice (Data.Profunctor.Choice.PastroSum p) instance Data.Profunctor.Choice.Cochoice (->) instance GHC.Base.Applicative f => Data.Profunctor.Choice.Cochoice (Data.Profunctor.Types.Costar f) instance Data.Traversable.Traversable f => Data.Profunctor.Choice.Cochoice (Data.Profunctor.Types.Star f) instance (GHC.Base.Functor f, Data.Profunctor.Choice.Cochoice p) => Data.Profunctor.Choice.Cochoice (Data.Bifunctor.Tannen.Tannen f p) instance (Data.Profunctor.Choice.Cochoice p, Data.Profunctor.Choice.Cochoice q) => Data.Profunctor.Choice.Cochoice (Data.Bifunctor.Product.Product p q) instance Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Choice.CotambaraSum p) instance Data.Profunctor.Monad.ProfunctorFunctor Data.Profunctor.Choice.CotambaraSum instance Data.Profunctor.Monad.ProfunctorComonad Data.Profunctor.Choice.CotambaraSum instance Data.Profunctor.Choice.Cochoice (Data.Profunctor.Choice.CotambaraSum p) instance GHC.Base.Functor (Data.Profunctor.Choice.CotambaraSum p a) instance Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Choice.CopastroSum p) instance Data.Profunctor.Adjunction.ProfunctorAdjunction Data.Profunctor.Choice.CopastroSum Data.Profunctor.Choice.CotambaraSum instance Data.Profunctor.Monad.ProfunctorFunctor Data.Profunctor.Choice.CopastroSum instance Data.Profunctor.Monad.ProfunctorMonad Data.Profunctor.Choice.CopastroSum instance Data.Profunctor.Choice.Cochoice (Data.Profunctor.Choice.CopastroSum p) module Data.Profunctor.Closed -- | A strong profunctor allows the monoidal structure to pass through. -- -- A closed profunctor allows the closed structure to pass through. class Profunctor p => Closed p closed :: Closed p => p a b -> p (x -> a) (x -> b) -- | Closure adjoins a Closed structure to any -- Profunctor. -- -- Analogous to Tambara for Strong. newtype Closure p a b Closure :: (forall x. p (x -> a) (x -> b)) -> Closure p a b [runClosure] :: Closure p a b -> forall x. p (x -> a) (x -> b) -- |
--   close . uncloseid
--   unclose . closeid
--   
close :: Closed p => (p :-> q) -> p :-> Closure q -- |
--   close . uncloseid
--   unclose . closeid
--   
unclose :: Profunctor q => (p :-> Closure q) -> p :-> q data Environment p a b [Environment] :: ((z -> y) -> b) -> p x y -> (a -> z -> x) -> Environment p a b curry' :: Closed p => p (a, b) c -> p a (b -> c) instance Data.Profunctor.Closed.Closed Data.Tagged.Tagged instance Data.Profunctor.Closed.Closed (->) instance GHC.Base.Functor f => Data.Profunctor.Closed.Closed (Data.Profunctor.Types.Costar f) instance GHC.Base.Functor f => Data.Profunctor.Closed.Closed (Control.Comonad.Cokleisli f) instance Data.Distributive.Distributive f => Data.Profunctor.Closed.Closed (Data.Profunctor.Types.Star f) instance (Data.Distributive.Distributive f, GHC.Base.Monad f) => Data.Profunctor.Closed.Closed (Control.Arrow.Kleisli f) instance (Data.Profunctor.Closed.Closed p, Data.Profunctor.Closed.Closed q) => Data.Profunctor.Closed.Closed (Data.Bifunctor.Product.Product p q) instance (GHC.Base.Functor f, Data.Profunctor.Closed.Closed p) => Data.Profunctor.Closed.Closed (Data.Bifunctor.Tannen.Tannen f p) instance Data.Profunctor.Unsafe.Profunctor p => Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Closed.Closure p) instance Data.Profunctor.Monad.ProfunctorFunctor Data.Profunctor.Closed.Closure instance Data.Profunctor.Monad.ProfunctorComonad Data.Profunctor.Closed.Closure instance Data.Profunctor.Unsafe.Profunctor p => Data.Profunctor.Closed.Closed (Data.Profunctor.Closed.Closure p) instance Data.Profunctor.Strong.Strong p => Data.Profunctor.Strong.Strong (Data.Profunctor.Closed.Closure p) instance Control.Category.Category p => Control.Category.Category (Data.Profunctor.Closed.Closure p) instance Control.Arrow.Arrow p => Control.Arrow.Arrow (Data.Profunctor.Closed.Closure p) instance Control.Arrow.ArrowLoop p => Control.Arrow.ArrowLoop (Data.Profunctor.Closed.Closure p) instance Control.Arrow.ArrowZero p => Control.Arrow.ArrowZero (Data.Profunctor.Closed.Closure p) instance Control.Arrow.ArrowPlus p => Control.Arrow.ArrowPlus (Data.Profunctor.Closed.Closure p) instance Data.Profunctor.Unsafe.Profunctor p => GHC.Base.Functor (Data.Profunctor.Closed.Closure p a) instance (Data.Profunctor.Unsafe.Profunctor p, Control.Arrow.Arrow p) => GHC.Base.Applicative (Data.Profunctor.Closed.Closure p a) instance (Data.Profunctor.Unsafe.Profunctor p, Control.Arrow.ArrowPlus p) => GHC.Base.Alternative (Data.Profunctor.Closed.Closure p a) instance (Data.Profunctor.Unsafe.Profunctor p, Control.Arrow.Arrow p, GHC.Base.Monoid b) => GHC.Base.Monoid (Data.Profunctor.Closed.Closure p a b) instance Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Closed.Environment p) instance Data.Profunctor.Monad.ProfunctorFunctor Data.Profunctor.Closed.Environment instance Data.Profunctor.Monad.ProfunctorMonad Data.Profunctor.Closed.Environment instance Data.Profunctor.Adjunction.ProfunctorAdjunction Data.Profunctor.Closed.Environment Data.Profunctor.Closed.Closure instance Data.Profunctor.Closed.Closed (Data.Profunctor.Closed.Environment p) module Data.Profunctor.Traversing -- | Note: Definitions in terms of wander are much more efficient! class (Choice p, Strong p) => Traversing p where traverse' = wander traverse wander f pab = dimap (\ s -> Baz $ \ afb -> f afb s) sold (traverse' pab) traverse' :: (Traversing p, Traversable f) => p a b -> p (f a) (f b) wander :: Traversing p => (forall f. Applicative f => (a -> f b) -> s -> f t) -> p a b -> p s t newtype CofreeTraversing p a b CofreeTraversing :: (forall f. Traversable f => p (f a) (f b)) -> CofreeTraversing p a b [runCofreeTraversing] :: CofreeTraversing p a b -> forall f. Traversable f => p (f a) (f b) -- |
--   FreeTraversing -| CofreeTraversing
--   
data FreeTraversing p a b [FreeTraversing] :: Traversable f => (f y -> b) -> p x y -> (a -> f x) -> FreeTraversing p a b firstTraversing :: Traversing p => p a b -> p (a, c) (b, c) secondTraversing :: Traversing p => p a b -> p (c, a) (c, b) leftTraversing :: Traversing p => p a b -> p (Either a c) (Either b c) rightTraversing :: Traversing p => p a b -> p (Either c a) (Either c b) instance GHC.Base.Functor (Data.Profunctor.Traversing.Baz t b) instance GHC.Base.Functor (Data.Profunctor.Traversing.Bazaar a b) instance GHC.Base.Applicative (Data.Profunctor.Traversing.Bazaar a b) instance Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Traversing.Bazaar a) instance Data.Foldable.Foldable (Data.Profunctor.Traversing.Baz t b) instance Data.Traversable.Traversable (Data.Profunctor.Traversing.Baz t b) instance Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Traversing.Baz t) instance Data.Profunctor.Traversing.Traversing (->) instance GHC.Base.Monad m => Data.Profunctor.Traversing.Traversing (Control.Arrow.Kleisli m) instance GHC.Base.Applicative m => Data.Profunctor.Traversing.Traversing (Data.Profunctor.Types.Star m) instance Data.Profunctor.Unsafe.Profunctor p => Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Traversing.CofreeTraversing p) instance Data.Profunctor.Unsafe.Profunctor p => Data.Profunctor.Strong.Strong (Data.Profunctor.Traversing.CofreeTraversing p) instance Data.Profunctor.Unsafe.Profunctor p => Data.Profunctor.Choice.Choice (Data.Profunctor.Traversing.CofreeTraversing p) instance Data.Profunctor.Unsafe.Profunctor p => Data.Profunctor.Traversing.Traversing (Data.Profunctor.Traversing.CofreeTraversing p) instance Data.Profunctor.Monad.ProfunctorFunctor Data.Profunctor.Traversing.CofreeTraversing instance Data.Profunctor.Monad.ProfunctorComonad Data.Profunctor.Traversing.CofreeTraversing instance Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Traversing.FreeTraversing p) instance Data.Profunctor.Strong.Strong (Data.Profunctor.Traversing.FreeTraversing p) instance Data.Profunctor.Choice.Choice (Data.Profunctor.Traversing.FreeTraversing p) instance Data.Profunctor.Traversing.Traversing (Data.Profunctor.Traversing.FreeTraversing p) instance Data.Profunctor.Monad.ProfunctorFunctor Data.Profunctor.Traversing.FreeTraversing instance Data.Profunctor.Monad.ProfunctorMonad Data.Profunctor.Traversing.FreeTraversing module Data.Profunctor.Mapping class (Traversing p, Closed p) => Mapping p map' :: (Mapping p, Functor f) => p a b -> p (f a) (f b) newtype CofreeMapping p a b CofreeMapping :: (forall f. Functor f => p (f a) (f b)) -> CofreeMapping p a b [runCofreeMapping] :: CofreeMapping p a b -> forall f. Functor f => p (f a) (f b) -- |
--   FreeMapping -| CofreeMapping
--   
data FreeMapping p a b [FreeMapping] :: Functor f => (f y -> b) -> p x y -> (a -> f x) -> FreeMapping p a b traverseMapping :: (Mapping p, Functor f) => p a b -> p (f a) (f b) closedMapping :: Mapping p => p a b -> p (x -> a) (x -> b) instance Data.Profunctor.Mapping.Mapping (->) instance (GHC.Base.Monad m, Data.Distributive.Distributive m) => Data.Profunctor.Mapping.Mapping (Control.Arrow.Kleisli m) instance (GHC.Base.Applicative m, Data.Distributive.Distributive m) => Data.Profunctor.Mapping.Mapping (Data.Profunctor.Types.Star m) instance Data.Profunctor.Unsafe.Profunctor p => Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Mapping.CofreeMapping p) instance Data.Profunctor.Unsafe.Profunctor p => Data.Profunctor.Strong.Strong (Data.Profunctor.Mapping.CofreeMapping p) instance Data.Profunctor.Unsafe.Profunctor p => Data.Profunctor.Choice.Choice (Data.Profunctor.Mapping.CofreeMapping p) instance Data.Profunctor.Unsafe.Profunctor p => Data.Profunctor.Closed.Closed (Data.Profunctor.Mapping.CofreeMapping p) instance Data.Profunctor.Unsafe.Profunctor p => Data.Profunctor.Traversing.Traversing (Data.Profunctor.Mapping.CofreeMapping p) instance Data.Profunctor.Unsafe.Profunctor p => Data.Profunctor.Mapping.Mapping (Data.Profunctor.Mapping.CofreeMapping p) instance Data.Profunctor.Monad.ProfunctorFunctor Data.Profunctor.Mapping.CofreeMapping instance Data.Profunctor.Monad.ProfunctorComonad Data.Profunctor.Mapping.CofreeMapping instance Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Mapping.FreeMapping p) instance Data.Profunctor.Strong.Strong (Data.Profunctor.Mapping.FreeMapping p) instance Data.Profunctor.Choice.Choice (Data.Profunctor.Mapping.FreeMapping p) instance Data.Profunctor.Closed.Closed (Data.Profunctor.Mapping.FreeMapping p) instance Data.Profunctor.Traversing.Traversing (Data.Profunctor.Mapping.FreeMapping p) instance Data.Profunctor.Mapping.Mapping (Data.Profunctor.Mapping.FreeMapping p) instance Data.Profunctor.Monad.ProfunctorFunctor Data.Profunctor.Mapping.FreeMapping instance Data.Profunctor.Monad.ProfunctorMonad Data.Profunctor.Mapping.FreeMapping -- | For a good explanation of profunctors in Haskell see Dan Piponi's -- article: -- -- http://blog.sigfpe.com/2011/07/profunctors-in-haskell.html -- -- For more information on strength and costrength, see: -- -- http://comonad.com/reader/2008/deriving-strength-from-laziness/ module Data.Profunctor -- | Formally, the class Profunctor represents a profunctor from -- Hask -> Hask. -- -- Intuitively it is a bifunctor where the first argument is -- contravariant and the second argument is covariant. -- -- You can define a Profunctor by either defining dimap or -- by defining both lmap and rmap. -- -- If you supply dimap, you should ensure that: -- --
--   dimap id idid
--   
-- -- If you supply lmap and rmap, ensure: -- --
--   lmap idid
--   rmap idid
--   
-- -- If you supply both, you should also ensure: -- --
--   dimap f g ≡ lmap f . rmap g
--   
-- -- These ensure by parametricity: -- --
--   dimap (f . g) (h . i) ≡ dimap g h . dimap f i
--   lmap (f . g) ≡ lmap g . lmap f
--   rmap (f . g) ≡ rmap f . rmap g
--   
class Profunctor p where dimap f g = lmap f . rmap g lmap f = dimap f id rmap = dimap id (#.) = \ f -> \ p -> p `seq` rmap f p (.#) = \ p -> p `seq` \ f -> lmap f p -- | Map over both arguments at the same time. -- --
--   dimap f g ≡ lmap f . rmap g
--   
dimap :: Profunctor p => (a -> b) -> (c -> d) -> p b c -> p a d -- | Map the first argument contravariantly. -- --
--   lmap f ≡ dimap f id
--   
lmap :: Profunctor p => (a -> b) -> p b c -> p a c -- | Map the second argument covariantly. -- --
--   rmapdimap id
--   
rmap :: Profunctor p => (b -> c) -> p a b -> p a c -- | Generalizing Star of a strong Functor -- -- Note: Every Functor in Haskell is strong with respect to -- (,). -- -- This describes profunctor strength with respect to the product -- structure of Hask. -- -- http://www-kb.is.s.u-tokyo.ac.jp/~asada/papers/arrStrMnd.pdf class Profunctor p => Strong p where first' = dimap swap swap . second' second' = dimap swap swap . first' first' :: Strong p => p a b -> p (a, c) (b, c) second' :: Strong p => p a b -> p (c, a) (c, b) uncurry' :: Strong p => p a (b -> c) -> p (a, b) c -- | The generalization of Costar of Functor that is strong -- with respect to Either. -- -- Note: This is also a notion of strength, except with regards to -- another monoidal structure that we can choose to equip Hask with: the -- cocartesian coproduct. class Profunctor p => Choice p where left' = dimap (either Right Left) (either Right Left) . right' right' = dimap (either Right Left) (either Right Left) . left' left' :: Choice p => p a b -> p (Either a c) (Either b c) right' :: Choice p => p a b -> p (Either c a) (Either c b) -- | A strong profunctor allows the monoidal structure to pass through. -- -- A closed profunctor allows the closed structure to pass through. class Profunctor p => Closed p closed :: Closed p => p a b -> p (x -> a) (x -> b) curry' :: Closed p => p (a, b) c -> p a (b -> c) class (Traversing p, Closed p) => Mapping p map' :: (Mapping p, Functor f) => p a b -> p (f a) (f b) -- | Analogous to ArrowLoop, loop = unfirst class Profunctor p => Costrong p where unfirst = unsecond . dimap swap swap unsecond = unfirst . dimap swap swap unfirst :: Costrong p => p (a, d) (b, d) -> p a b unsecond :: Costrong p => p (d, a) (d, b) -> p a b class Profunctor p => Cochoice p where unleft = unright . dimap (either Right Left) (either Right Left) unright = unleft . dimap (either Right Left) (either Right Left) unleft :: Cochoice p => p (Either a d) (Either b d) -> p a b unright :: Cochoice p => p (Either d a) (Either d b) -> p a b -- | Lift a Functor into a Profunctor (forwards). newtype Star f d c Star :: (d -> f c) -> Star f d c [runStar] :: Star f d c -> d -> f c -- | Lift a Functor into a Profunctor (backwards). newtype Costar f d c Costar :: (f d -> c) -> Costar f d c [runCostar] :: Costar f d c -> f d -> c -- | Wrap an arrow for use as a Profunctor. newtype WrappedArrow p a b WrapArrow :: p a b -> WrappedArrow p a b [unwrapArrow] :: WrappedArrow p a b -> p a b newtype Forget r a b Forget :: (a -> r) -> Forget r a b [runForget] :: Forget r a b -> a -> r type (:->) p q = forall a b. p a b -> q a b module Data.Profunctor.Cayley newtype Cayley f p a b Cayley :: f (p a b) -> Cayley f p a b [runCayley] :: Cayley f p a b -> f (p a b) -- | Cayley transforms Monads in Hask into monads on Prof -- | Cayley transforms Comonads in Hask into comonads on -- Prof instance GHC.Base.Functor f => Data.Profunctor.Monad.ProfunctorFunctor (Data.Profunctor.Cayley.Cayley f) instance (GHC.Base.Functor f, GHC.Base.Monad f) => Data.Profunctor.Monad.ProfunctorMonad (Data.Profunctor.Cayley.Cayley f) instance Control.Comonad.Comonad f => Data.Profunctor.Monad.ProfunctorComonad (Data.Profunctor.Cayley.Cayley f) instance (GHC.Base.Functor f, Data.Profunctor.Unsafe.Profunctor p) => Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Cayley.Cayley f p) instance (GHC.Base.Functor f, Data.Profunctor.Strong.Strong p) => Data.Profunctor.Strong.Strong (Data.Profunctor.Cayley.Cayley f p) instance (GHC.Base.Functor f, Data.Profunctor.Choice.Choice p) => Data.Profunctor.Choice.Choice (Data.Profunctor.Cayley.Cayley f p) instance (GHC.Base.Applicative f, Control.Category.Category p) => Control.Category.Category (Data.Profunctor.Cayley.Cayley f p) instance (GHC.Base.Applicative f, Control.Arrow.Arrow p) => Control.Arrow.Arrow (Data.Profunctor.Cayley.Cayley f p) instance (GHC.Base.Applicative f, Control.Arrow.ArrowChoice p) => Control.Arrow.ArrowChoice (Data.Profunctor.Cayley.Cayley f p) instance (GHC.Base.Applicative f, Control.Arrow.ArrowLoop p) => Control.Arrow.ArrowLoop (Data.Profunctor.Cayley.Cayley f p) instance (GHC.Base.Applicative f, Control.Arrow.ArrowZero p) => Control.Arrow.ArrowZero (Data.Profunctor.Cayley.Cayley f p) instance (GHC.Base.Applicative f, Control.Arrow.ArrowPlus p) => Control.Arrow.ArrowPlus (Data.Profunctor.Cayley.Cayley f p) module Data.Profunctor.Sieve -- | A Profunctor p is a Sieve on f -- if it is a subprofunctor of Star f. -- -- That is to say it is a subset of Hom(-,f=) closed under -- lmap and rmap. -- -- Alternately, you can view it as a sieve in the comma category -- Hask/f. class (Profunctor p, Functor f) => Sieve p f | p -> f sieve :: Sieve p f => p a b -> a -> f b -- | A Profunctor p is a Cosieve on -- f if it is a subprofunctor of Costar f. -- -- That is to say it is a subset of Hom(f-,=) closed under -- lmap and rmap. -- -- Alternately, you can view it as a cosieve in the comma category -- f/Hask. class (Profunctor p, Functor f) => Cosieve p f | p -> f cosieve :: Cosieve p f => p a b -> f a -> b instance Data.Profunctor.Sieve.Sieve (->) Data.Functor.Identity.Identity instance (GHC.Base.Monad m, GHC.Base.Functor m) => Data.Profunctor.Sieve.Sieve (Control.Arrow.Kleisli m) m instance GHC.Base.Functor f => Data.Profunctor.Sieve.Sieve (Data.Profunctor.Types.Star f) f instance Data.Profunctor.Sieve.Sieve (Data.Profunctor.Types.Forget r) (Data.Functor.Const.Const r) instance Data.Profunctor.Sieve.Cosieve (->) Data.Functor.Identity.Identity instance GHC.Base.Functor w => Data.Profunctor.Sieve.Cosieve (Control.Comonad.Cokleisli w) w instance Data.Profunctor.Sieve.Cosieve Data.Tagged.Tagged Data.Proxy.Proxy instance GHC.Base.Functor f => Data.Profunctor.Sieve.Cosieve (Data.Profunctor.Types.Costar f) f module Data.Profunctor.Rep -- | A Profunctor p is Representable if there exists -- a Functor f such that p d c is isomorphic to -- d -> f c. class (Sieve p (Rep p), Strong p) => Representable p where type Rep p :: * -> * where { type family Rep p :: * -> *; } tabulate :: Representable p => (d -> Rep p c) -> p d c -- | tabulate and sieve form two halves of an isomorphism. -- -- This can be used with the combinators from the lens package. -- --
--   tabulated :: Representable p => Iso' (d -> Rep p c) (p d c)
--   
tabulated :: (Representable p, Representable q) => Iso (d -> Rep p c) (d' -> Rep q c') (p d c) (q d' c') -- | Default definition for first' given that p is -- Representable. firstRep :: Representable p => p a b -> p (a, c) (b, c) -- | Default definition for second' given that p is -- Representable. secondRep :: Representable p => p a b -> p (c, a) (c, b) -- | A Profunctor p is Corepresentable if there -- exists a Functor f such that p d c is -- isomorphic to f d -> c. class (Cosieve p (Corep p), Costrong p) => Corepresentable p where type Corep p :: * -> * where { type family Corep p :: * -> *; } cotabulate :: Corepresentable p => (Corep p d -> c) -> p d c -- | cotabulate and cosieve form two halves of an -- isomorphism. -- -- This can be used with the combinators from the lens package. -- --
--   cotabulated :: Corep f p => Iso' (f d -> c) (p d c)
--   
cotabulated :: (Corepresentable p, Corepresentable q) => Iso (Corep p d -> c) (Corep q d' -> c') (p d c) (q d' c') -- | Default definition for unfirst given that p is -- Corepresentable. unfirstCorep :: Corepresentable p => p (a, d) (b, d) -> p a b -- | Default definition for unsecond given that p is -- Corepresentable. unsecondCorep :: Corepresentable p => p (d, a) (d, b) -> p a b -- | Default definition for closed given that p is -- Corepresentable closedCorep :: Corepresentable p => p a b -> p (x -> a) (x -> b) -- |
--   Prep -| Star :: [Hask, Hask] -> Prof
--   
-- -- This gives rise to a monad in Prof, ('Star'.'Prep'), -- and a comonad in [Hask,Hask] ('Prep'.'Star') data Prep p a [Prep] :: x -> p x a -> Prep p a prepAdj :: (forall a. Prep p a -> g a) -> p :-> Star g unprepAdj :: (p :-> Star g) -> Prep p a -> g a prepUnit :: p :-> Star (Prep p) prepCounit :: Prep (Star f) a -> f a newtype Coprep p a Coprep :: (forall r. p a r -> r) -> Coprep p a [runCoprep] :: Coprep p a -> forall r. p a r -> r -- |
--   Coprep -| Costar :: [Hask, Hask]^op -> Prof
--   
-- -- Like all adjunctions this gives rise to a monad and a comonad. -- -- This gives rise to a monad on Prof ('Costar'.'Coprep') and a -- comonad on [Hask, Hask]^op given by -- ('Coprep'.'Costar') which is a monad in [Hask,Hask] coprepAdj :: (forall a. f a -> Coprep p a) -> p :-> Costar f uncoprepAdj :: (p :-> Costar f) -> f a -> Coprep p a coprepUnit :: p :-> Costar (Coprep p) coprepCounit :: f a -> Coprep (Costar f) a instance Data.Profunctor.Rep.Representable (->) instance (GHC.Base.Monad m, GHC.Base.Functor m) => Data.Profunctor.Rep.Representable (Control.Arrow.Kleisli m) instance GHC.Base.Functor f => Data.Profunctor.Rep.Representable (Data.Profunctor.Types.Star f) instance Data.Profunctor.Rep.Representable (Data.Profunctor.Types.Forget r) instance Data.Profunctor.Rep.Corepresentable (->) instance GHC.Base.Functor w => Data.Profunctor.Rep.Corepresentable (Control.Comonad.Cokleisli w) instance Data.Profunctor.Rep.Corepresentable Data.Tagged.Tagged instance GHC.Base.Functor f => Data.Profunctor.Rep.Corepresentable (Data.Profunctor.Types.Costar f) instance Data.Profunctor.Unsafe.Profunctor p => GHC.Base.Functor (Data.Profunctor.Rep.Prep p) instance (GHC.Base.Applicative (Data.Profunctor.Rep.Rep p), Data.Profunctor.Rep.Representable p) => GHC.Base.Applicative (Data.Profunctor.Rep.Prep p) instance (GHC.Base.Monad (Data.Profunctor.Rep.Rep p), Data.Profunctor.Rep.Representable p) => GHC.Base.Monad (Data.Profunctor.Rep.Prep p) instance Data.Profunctor.Unsafe.Profunctor p => GHC.Base.Functor (Data.Profunctor.Rep.Coprep p) module Data.Profunctor.Composition -- | Procompose p q is the Profunctor composition of -- the Profunctors p and q. -- -- For a good explanation of Profunctor composition in Haskell see -- Dan Piponi's article: -- -- http://blog.sigfpe.com/2011/07/profunctors-in-haskell.html data Procompose p q d c [Procompose] :: p x c -> q d x -> Procompose p q d c procomposed :: Category p => Procompose p p a b -> p a b -- | (->) functions as a lax identity for Profunctor -- composition. -- -- This provides an Iso for the lens package that -- witnesses the isomorphism between Procompose (->) q d -- c and q d c, which is the left identity law. -- --
--   idl :: Profunctor q => Iso' (Procompose (->) q d c) (q d c)
--   
idl :: Profunctor q => Iso (Procompose (->) q d c) (Procompose (->) r d' c') (q d c) (r d' c') -- | (->) functions as a lax identity for Profunctor -- composition. -- -- This provides an Iso for the lens package that -- witnesses the isomorphism between Procompose q (->) d -- c and q d c, which is the right identity law. -- --
--   idr :: Profunctor q => Iso' (Procompose q (->) d c) (q d c)
--   
idr :: Profunctor q => Iso (Procompose q (->) d c) (Procompose r (->) d' c') (q d c) (r d' c') -- | The associator for Profunctor composition. -- -- This provides an Iso for the lens package that -- witnesses the isomorphism between Procompose p -- (Procompose q r) a b and Procompose -- (Procompose p q) r a b, which arises because Prof -- is only a bicategory, rather than a strict 2-category. assoc :: Iso (Procompose p (Procompose q r) a b) (Procompose x (Procompose y z) a b) (Procompose (Procompose p q) r a b) (Procompose (Procompose x y) z a b) -- | a Category that is also a Profunctor is a Monoid -- in Prof eta :: (Profunctor p, Category p) => (->) :-> p mu :: Category p => Procompose p p :-> p -- | Profunctor composition generalizes Functor composition -- in two ways. -- -- This is the first, which shows that exists b. (a -> f b, b -- -> g c) is isomorphic to a -> f (g c). -- --
--   stars :: Functor f => Iso' (Procompose (Star f) (Star g) d c) (Star (Compose f g) d c)
--   
stars :: Functor g => Iso (Procompose (Star f) (Star g) d c) (Procompose (Star f') (Star g') d' c') (Star (Compose g f) d c) (Star (Compose g' f') d' c') -- | This is a variant on stars that uses Kleisli instead of -- Star. -- --
--   kleislis :: Monad f => Iso' (Procompose (Kleisli f) (Kleisli g) d c) (Kleisli (Compose f g) d c)
--   
kleislis :: Monad g => Iso (Procompose (Kleisli f) (Kleisli g) d c) (Procompose (Kleisli f') (Kleisli g') d' c') (Kleisli (Compose g f) d c) (Kleisli (Compose g' f') d' c') -- | Profunctor composition generalizes Functor composition -- in two ways. -- -- This is the second, which shows that exists b. (f a -> b, g b -- -> c) is isomorphic to g (f a) -> c. -- --
--   costars :: Functor f => Iso' (Procompose (Costar f) (Costar g) d c) (Costar (Compose g f) d c)
--   
costars :: Functor f => Iso (Procompose (Costar f) (Costar g) d c) (Procompose (Costar f') (Costar g') d' c') (Costar (Compose f g) d c) (Costar (Compose f' g') d' c') -- | This is a variant on costars that uses Cokleisli instead -- of Costar. -- --
--   cokleislis :: Functor f => Iso' (Procompose (Cokleisli f) (Cokleisli g) d c) (Cokleisli (Compose g f) d c)
--   
cokleislis :: Functor f => Iso (Procompose (Cokleisli f) (Cokleisli g) d c) (Procompose (Cokleisli f') (Cokleisli g') d' c') (Cokleisli (Compose f g) d c) (Cokleisli (Compose f' g') d' c') -- | This represents the right Kan lift of a Profunctor q -- along a Profunctor p in a limited version of the -- 2-category of Profunctors where the only object is the category Hask, -- 1-morphisms are profunctors composed and compose with Profunctor -- composition, and 2-morphisms are just natural transformations. newtype Rift p q a b Rift :: (forall x. p b x -> q a x) -> Rift p q a b [runRift] :: Rift p q a b -> forall x. p b x -> q a x -- | The 2-morphism that defines a left Kan lift. -- -- Note: When p is right adjoint to Rift p -- (->) then decomposeRift is the counit of the -- adjunction. decomposeRift :: Procompose p (Rift p q) :-> q instance Data.Profunctor.Monad.ProfunctorFunctor (Data.Profunctor.Composition.Procompose p) instance Control.Category.Category p => Data.Profunctor.Monad.ProfunctorMonad (Data.Profunctor.Composition.Procompose p) instance (Data.Profunctor.Unsafe.Profunctor p, Data.Profunctor.Unsafe.Profunctor q) => Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Composition.Procompose p q) instance Data.Profunctor.Unsafe.Profunctor p => GHC.Base.Functor (Data.Profunctor.Composition.Procompose p q a) instance (Data.Profunctor.Sieve.Sieve p f, Data.Profunctor.Sieve.Sieve q g) => Data.Profunctor.Sieve.Sieve (Data.Profunctor.Composition.Procompose p q) (Data.Functor.Compose.Compose g f) instance (Data.Profunctor.Rep.Representable p, Data.Profunctor.Rep.Representable q) => Data.Profunctor.Rep.Representable (Data.Profunctor.Composition.Procompose p q) instance (Data.Profunctor.Sieve.Cosieve p f, Data.Profunctor.Sieve.Cosieve q g) => Data.Profunctor.Sieve.Cosieve (Data.Profunctor.Composition.Procompose p q) (Data.Functor.Compose.Compose f g) instance (Data.Profunctor.Rep.Corepresentable p, Data.Profunctor.Rep.Corepresentable q) => Data.Profunctor.Rep.Corepresentable (Data.Profunctor.Composition.Procompose p q) instance (Data.Profunctor.Strong.Strong p, Data.Profunctor.Strong.Strong q) => Data.Profunctor.Strong.Strong (Data.Profunctor.Composition.Procompose p q) instance (Data.Profunctor.Choice.Choice p, Data.Profunctor.Choice.Choice q) => Data.Profunctor.Choice.Choice (Data.Profunctor.Composition.Procompose p q) instance (Data.Profunctor.Closed.Closed p, Data.Profunctor.Closed.Closed q) => Data.Profunctor.Closed.Closed (Data.Profunctor.Composition.Procompose p q) instance (Data.Profunctor.Rep.Corepresentable p, Data.Profunctor.Rep.Corepresentable q) => Data.Profunctor.Strong.Costrong (Data.Profunctor.Composition.Procompose p q) instance Data.Profunctor.Monad.ProfunctorFunctor (Data.Profunctor.Composition.Rift p) instance Control.Category.Category p => Data.Profunctor.Monad.ProfunctorComonad (Data.Profunctor.Composition.Rift p) instance (Data.Profunctor.Unsafe.Profunctor p, Data.Profunctor.Unsafe.Profunctor q) => Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Composition.Rift p q) instance Data.Profunctor.Unsafe.Profunctor p => GHC.Base.Functor (Data.Profunctor.Composition.Rift p q a) instance p ~ q => Control.Category.Category (Data.Profunctor.Composition.Rift p q) instance Data.Profunctor.Adjunction.ProfunctorAdjunction (Data.Profunctor.Composition.Procompose p) (Data.Profunctor.Composition.Rift p) module Data.Profunctor.Ran -- | This represents the right Kan extension of a Profunctor -- q along a Profunctor p in a limited version -- of the 2-category of Profunctors where the only object is the category -- Hask, 1-morphisms are profunctors composed and compose with Profunctor -- composition, and 2-morphisms are just natural transformations. newtype Ran p q a b Ran :: (forall x. p x a -> q x b) -> Ran p q a b [runRan] :: Ran p q a b -> forall x. p x a -> q x b -- | The 2-morphism that defines a right Kan extension. -- -- Note: When q is left adjoint to Ran q (->) -- then decomposeRan is the counit of the adjunction. decomposeRan :: Procompose (Ran q p) q :-> p precomposeRan :: Profunctor q => Procompose q (Ran p (->)) :-> Ran p q curryRan :: (Procompose p q :-> r) -> p :-> Ran q r uncurryRan :: (p :-> Ran q r) -> Procompose p q :-> r -- | This represents the right Kan extension of a Profunctor -- p along itself. This provides a generalization of the -- "difference list" trick to profunctors. newtype Codensity p a b Codensity :: (forall x. p x a -> p x b) -> Codensity p a b [runCodensity] :: Codensity p a b -> forall x. p x a -> p x b decomposeCodensity :: Procompose (Codensity p) p a b -> p a b instance Data.Profunctor.Monad.ProfunctorFunctor (Data.Profunctor.Ran.Ran p) instance Control.Category.Category p => Data.Profunctor.Monad.ProfunctorComonad (Data.Profunctor.Ran.Ran p) instance (Data.Profunctor.Unsafe.Profunctor p, Data.Profunctor.Unsafe.Profunctor q) => Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Ran.Ran p q) instance Data.Profunctor.Unsafe.Profunctor q => GHC.Base.Functor (Data.Profunctor.Ran.Ran p q a) instance p ~ q => Control.Category.Category (Data.Profunctor.Ran.Ran p q) instance Data.Profunctor.Unsafe.Profunctor p => Data.Profunctor.Unsafe.Profunctor (Data.Profunctor.Ran.Codensity p) instance Data.Profunctor.Unsafe.Profunctor p => GHC.Base.Functor (Data.Profunctor.Ran.Codensity p a) instance Control.Category.Category (Data.Profunctor.Ran.Codensity p)