constrained-monads-0.5.0.0: Typeclasses and instances for monads with constraints.

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Constrained.Ap

Description

This module allows the use of the Applicative Do extension with constrained monads.

Synopsis

Documentation

class Applicative f => Monad f where Source #

This class is for types which have no constraints on their applicative operations, but do have constraints on the monadic operations.

Most types which can conform are just standard unconstrained monads, with the exception of the free applicative. The type Ap f a is an applicative for any f. However, it can only be made a monad by interpreting the underlying type (which may be constrained), running the monadic operation, and then lifting the result. In practice, this allows you to write code on on the Ap type, using applicative do notation, and have it be interpreted correctly.

For instance, take the following expression:

example = do
   x <- pure 1
   y <- pure 2
   pure (x + y)

With the standard constrained monad module, you can instantiate that at any type which is a constrained monad. Set, for instance. However, if -XApplicativeDo is turned on, you will get the error:

No instance for (Ord (Integer -> Set Integer))

The solution is to use Ap Set instead, which has the same constraints on expressions built with <*> as those built with >>=.

Minimal complete definition

(>>=), join

Associated Types

type Suitable f a :: Constraint Source #

Methods

(>>=) :: (Suitable f a, Suitable f b) => f a -> (a -> f b) -> f b infixl 1 Source #

join :: Suitable f a => f (f a) -> f a Source #

Instances

Monad [] Source # 

Associated Types

type Suitable ([] :: * -> *) a :: Constraint Source #

Methods

(>>=) :: (Suitable [] a, Suitable [] b) => [a] -> (a -> [b]) -> [b] Source #

join :: Suitable [] a => [[a]] -> [a] Source #

Monad Maybe Source # 

Associated Types

type Suitable (Maybe :: * -> *) a :: Constraint Source #

Methods

(>>=) :: (Suitable Maybe a, Suitable Maybe b) => Maybe a -> (a -> Maybe b) -> Maybe b Source #

join :: Suitable Maybe a => Maybe (Maybe a) -> Maybe a Source #

Monad IO Source # 

Associated Types

type Suitable (IO :: * -> *) a :: Constraint Source #

Methods

(>>=) :: (Suitable IO a, Suitable IO b) => IO a -> (a -> IO b) -> IO b Source #

join :: Suitable IO a => IO (IO a) -> IO a Source #

Monad Identity Source # 

Associated Types

type Suitable (Identity :: * -> *) a :: Constraint Source #

Monad Seq Source # 

Associated Types

type Suitable (Seq :: * -> *) a :: Constraint Source #

Methods

(>>=) :: (Suitable Seq a, Suitable Seq b) => Seq a -> (a -> Seq b) -> Seq b Source #

join :: Suitable Seq a => Seq (Seq a) -> Seq a Source #

Monad ((->) b) Source # 

Associated Types

type Suitable ((->) b :: * -> *) a :: Constraint Source #

Methods

(>>=) :: (Suitable ((->) b) a, Suitable ((->) b) b) => (b -> a) -> (a -> b -> b) -> b -> b Source #

join :: Suitable ((->) b) a => (b -> b -> a) -> b -> a Source #

Monad (Either e) Source # 

Associated Types

type Suitable (Either e :: * -> *) a :: Constraint Source #

Methods

(>>=) :: (Suitable (Either e) a, Suitable (Either e) b) => Either e a -> (a -> Either e b) -> Either e b Source #

join :: Suitable (Either e) a => Either e (Either e a) -> Either e a Source #

Monoid m => Monad ((,) m) Source # 

Associated Types

type Suitable ((,) m :: * -> *) a :: Constraint Source #

Methods

(>>=) :: (Suitable ((,) m) a, Suitable ((,) m) b) => (m, a) -> (a -> (m, b)) -> (m, b) Source #

join :: Suitable ((,) m) a => (m, (m, a)) -> (m, a) Source #

Monad m => Monad (MaybeT m) Source # 

Associated Types

type Suitable (MaybeT m :: * -> *) a :: Constraint Source #

Methods

(>>=) :: (Suitable (MaybeT m) a, Suitable (MaybeT m) b) => MaybeT m a -> (a -> MaybeT m b) -> MaybeT m b Source #

join :: Suitable (MaybeT m) a => MaybeT m (MaybeT m a) -> MaybeT m a Source #

Monad f => Monad (ConstrainedWrapper f) Source # 
Monad f => Monad (Codensity f) Source # 

Associated Types

type Suitable (Codensity f :: * -> *) a :: Constraint Source #

Methods

(>>=) :: (Suitable (Codensity f) a, Suitable (Codensity f) b) => Codensity f a -> (a -> Codensity f b) -> Codensity f b Source #

join :: Suitable (Codensity f) a => Codensity f (Codensity f a) -> Codensity f a Source #

Monad f => Monad (Final f) Source # 

Associated Types

type Suitable (Final f :: * -> *) a :: Constraint Source #

Methods

(>>=) :: (Suitable (Final f) a, Suitable (Final f) b) => Final f a -> (a -> Final f b) -> Final f b Source #

join :: Suitable (Final f) a => Final f (Final f a) -> Final f a Source #

Monad f => Monad (Initial f) Source # 

Associated Types

type Suitable (Initial f :: * -> *) a :: Constraint Source #

Methods

(>>=) :: (Suitable (Initial f) a, Suitable (Initial f) b) => Initial f a -> (a -> Initial f b) -> Initial f b Source #

join :: Suitable (Initial f) a => Initial f (Initial f a) -> Initial f a Source #

Monad m => Monad (IdentityT * m) Source # 

Associated Types

type Suitable (IdentityT * m :: * -> *) a :: Constraint Source #

Methods

(>>=) :: (Suitable (IdentityT * m) a, Suitable (IdentityT * m) b) => IdentityT * m a -> (a -> IdentityT * m b) -> IdentityT * m b Source #

join :: Suitable (IdentityT * m) a => IdentityT * m (IdentityT * m a) -> IdentityT * m a Source #

Monad m => Monad (ExceptT e m) Source # 

Associated Types

type Suitable (ExceptT e m :: * -> *) a :: Constraint Source #

Methods

(>>=) :: (Suitable (ExceptT e m) a, Suitable (ExceptT e m) b) => ExceptT e m a -> (a -> ExceptT e m b) -> ExceptT e m b Source #

join :: Suitable (ExceptT e m) a => ExceptT e m (ExceptT e m a) -> ExceptT e m a Source #

Monad m => Monad (StateT s m) Source # 

Associated Types

type Suitable (StateT s m :: * -> *) a :: Constraint Source #

Methods

(>>=) :: (Suitable (StateT s m) a, Suitable (StateT s m) b) => StateT s m a -> (a -> StateT s m b) -> StateT s m b Source #

join :: Suitable (StateT s m) a => StateT s m (StateT s m a) -> StateT s m a Source #

Monad m => Monad (StateT s m) Source # 

Associated Types

type Suitable (StateT s m :: * -> *) a :: Constraint Source #

Methods

(>>=) :: (Suitable (StateT s m) a, Suitable (StateT s m) b) => StateT s m a -> (a -> StateT s m b) -> StateT s m b Source #

join :: Suitable (StateT s m) a => StateT s m (StateT s m a) -> StateT s m a Source #

Monad (ContT * r m) Source # 

Associated Types

type Suitable (ContT * r m :: * -> *) a :: Constraint Source #

Methods

(>>=) :: (Suitable (ContT * r m) a, Suitable (ContT * r m) b) => ContT * r m a -> (a -> ContT * r m b) -> ContT * r m b Source #

join :: Suitable (ContT * r m) a => ContT * r m (ContT * r m a) -> ContT * r m a Source #

Monad m => Monad (ReaderT * s m) Source # 

Associated Types

type Suitable (ReaderT * s m :: * -> *) a :: Constraint Source #

Methods

(>>=) :: (Suitable (ReaderT * s m) a, Suitable (ReaderT * s m) b) => ReaderT * s m a -> (a -> ReaderT * s m b) -> ReaderT * s m b Source #

join :: Suitable (ReaderT * s m) a => ReaderT * s m (ReaderT * s m a) -> ReaderT * s m a Source #

class Monad f => MonadFail f where Source #

See here for more details.

Minimal complete definition

fail

Methods

fail :: Suitable f a => String -> f a Source #

Called when a pattern match fails in do-notation.

Instances

MonadFail [] Source # 

Methods

fail :: Suitable [] a => String -> [a] Source #

MonadFail Maybe Source # 

Methods

fail :: Suitable Maybe a => String -> Maybe a Source #

MonadFail IO Source # 

Methods

fail :: Suitable IO a => String -> IO a Source #

MonadFail Seq Source # 

Methods

fail :: Suitable Seq a => String -> Seq a Source #

IsString a => MonadFail (Either a) Source # 

Methods

fail :: Suitable (Either a) a => String -> Either a a Source #

Monad m => MonadFail (MaybeT m) Source # 

Methods

fail :: Suitable (MaybeT m) a => String -> MaybeT m a Source #

MonadFail m => MonadFail (IdentityT * m) Source # 

Methods

fail :: Suitable (IdentityT * m) a => String -> IdentityT * m a Source #

(Monad m, IsString e) => MonadFail (ExceptT e m) Source # 

Methods

fail :: Suitable (ExceptT e m) a => String -> ExceptT e m a Source #

MonadFail m => MonadFail (ReaderT * r m) Source # 

Methods

fail :: Suitable (ReaderT * r m) a => String -> ReaderT * r m a Source #

newtype Codensity f a Source #

Constructors

Codensity 

Fields

Instances

Monad f => FreeApplicative Codensity f Source # 

Methods

liftAp :: f a -> Codensity f a Source #

retractAp :: Suitable f a => Codensity f a -> f a Source #

Functor (Codensity f) Source # 

Methods

fmap :: (a -> b) -> Codensity f a -> Codensity f b #

(<$) :: a -> Codensity f b -> Codensity f a #

Applicative (Codensity f) Source # 

Methods

pure :: a -> Codensity f a #

(<*>) :: Codensity f (a -> b) -> Codensity f a -> Codensity f b #

(*>) :: Codensity f a -> Codensity f b -> Codensity f b #

(<*) :: Codensity f a -> Codensity f b -> Codensity f a #

Monad f => Monad (Codensity f) Source # 

Associated Types

type Suitable (Codensity f :: * -> *) a :: Constraint Source #

Methods

(>>=) :: (Suitable (Codensity f) a, Suitable (Codensity f) b) => Codensity f a -> (a -> Codensity f b) -> Codensity f b Source #

join :: Suitable (Codensity f) a => Codensity f (Codensity f a) -> Codensity f a Source #

type Suitable (Codensity f) a Source # 
type Suitable (Codensity f) a = Suitable f a

return :: Applicative f => a -> f a Source #

An alias for pure

ifThenElse :: Bool -> a -> a -> a Source #

Function to which the if ... then ... else syntax desugars to

(>>) :: Applicative f => f a -> f b -> f b infixl 1 Source #

Sequence two actions, discarding the result of the first. Alias for (*>).

type Final = Ap Source #

class FreeApplicative ap f where Source #

Minimal complete definition

liftAp, retractAp

Methods

liftAp :: f a -> ap f a Source #

retractAp :: Suitable f a => ap f a -> f a Source #

Instances