profunctor-monad-0.2.0.0: Monadic bidirectional programming
Safe HaskellSafe-Inferred
LanguageHaskell2010

Profunctor.Monad.Combinators

Description

Combinators for monadic profunctors.

Synopsis

Basic combinators

with :: forall cc p x a. ForallF cc p => (cc (p x) => a) -> a Source #

Instantiate a constraint ForallF cc p at type x, yielding cc (p x).

Usage

In some context with a constraint ForallF Monad p available:

with @Monad @p @x $ do
  (...) :: p x a

with' :: forall cc p x a. ForallF cc p => (cc (p x) => p x a) -> p x a Source #

A specialization of with which deduces p and x from its argument.

Usage

In some context with a constraint ForallF Monad p available:

with' @Monad $ do
  (...) :: p x a

withFunctor :: ForallF Functor p => (Functor (p x) => p x a) -> p x a Source #

A specialization of with' for Functor, to avoid TypeApplications where this is possible.

Usage

In some context with a constraint ForallF Functor p available:

withFunctor $
  (...) <$> (...)

withApplicative :: ForallF Applicative p => (Applicative (p x) => p x a) -> p x a Source #

A specialization of with' for Applicative, to avoid TypeApplications where this is possible.

Usage

In some context with a constraint ForallF Applicative p available:

withApplicative $
  (...) <$> (...) <*> (...)

withAlternative :: ForallF Alternative p => (Alternative (p x) => p x a) -> p x a Source #

A specialization of with' for Alternative, to avoid TypeApplications where this is possible.

Usage

In some context with a constraint ForallF Alternative p available:

withAlternative $
  (...) <|> (...)

withMonad :: ForallF Monad p => (Monad (p x) => p x a) -> p x a Source #

A specialization of with' for Monad, to avoid TypeApplications where this is possible.

Usage

In some context with a constraint ForallF Alternative p available:

withMonad $ do
  (...)

replicateP :: forall p x a. (Profunctor p, ForallF Applicative p) => Int -> p x a -> p [x] [a] Source #

Bidirectional generalization of replicateM.

replicateP_ :: (Profunctor p, Applicative (p [x])) => Int -> p x a -> p [x] [a] Source #

manyP :: forall p x a. (Profunctor p, ForallF Alternative p) => (([x] -> Bool) -> p [x] ()) -> p x a -> p [x] [a] Source #

manyP_ :: (Profunctor p, Alternative (p [x])) => (([x] -> Bool) -> p [x] ()) -> p x a -> p [x] [a] Source #

someP :: forall p x a. (Profunctor p, ForallF Alternative p) => (([x] -> Bool) -> p [x] ()) -> p x a -> p [x] [a] Source #

someP_ :: (Profunctor p, Alternative (p [x])) => (([x] -> Bool) -> p [x] ()) -> p x a -> p [x] [a] Source #

sepByP :: forall p x a b. (Profunctor p, ForallF Alternative p) => (([x] -> Bool) -> p [x] ()) -> p x a -> p () b -> p [x] [a] Source #

sepByP_ :: (Profunctor p, Alternative (p [x])) => (([x] -> Bool) -> p [x] ()) -> p x a -> p () b -> p [x] [a] Source #

sepBy1P :: forall p x a b. (Profunctor p, ForallF Alternative p) => (([x] -> Bool) -> p [x] ()) -> p x a -> p () b -> p [x] [a] Source #

sepBy1P_ :: (Profunctor p, Alternative (p [x])) => (([x] -> Bool) -> p [x] ()) -> p x a -> p () b -> p [x] [a] Source #

preByP :: forall p x a b. (Profunctor p, ForallF Alternative p) => (([x] -> Bool) -> p [x] ()) -> p x a -> p () b -> p [x] [a] Source #

preByP_ :: (Profunctor p, Alternative (p [x])) => (([x] -> Bool) -> p [x] ()) -> p x a -> p () b -> p [x] [a] Source #