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

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Constrained

Contents

Description

A module for constrained monads. This module is intended to be imported with the -XRebindableSyntax extension turned on: everything from the Prelude (that doesn't conflict with the new Functor, Applicative, etc) is reexported, so these type classes can be used the same way that the Prelude classes are used.

Synopsis

Basic Classes

class Functor f where Source #

This is the same class as Functor from the Prelude. Most of the functions here are simply rewritten versions of those, with one difference: types can indicate which types they can contain. This allows Set to be made into a monad, as well as some other exotic types. (but, to be fair, Set is kind of the poster child for this technique).

The way that types indicate what they can contain is with the Suitable associated type.

The default implementation is for types which conform to the Prelude's Functor. The way to make a standard Functor conform is by indicating that it has no constraints. For instance, for []:

instance Functor [] where
  fmap = map
  (<$) = (Prelude.<$)

Monomorphic types can also conform, using GADT aliases. For instance, if you create an alias for IntSet of kind * -> *:

data IntSet a where
  IntSet :: IntSet.IntSet -> IntSet Int

It can be made to conform to Functor like so:

instance Functor IntSet where
  type Suitable IntSet a = a ~ Int
  fmap f (IntSet xs) = IntSet (IntSet.map f xs)
  x <$ xs = if null xs then empty else pure x

It can also be made conform to Foldable, etc. This type is provided in Control.Monad.Constrained.IntSet.

Minimal complete definition

fmap

Associated Types

type Suitable f a :: Constraint Source #

Indicate which types can be contained by f. For instance, Set conforms like so:

instance Functor Set where
    type Suitable Set a = Ord a
    fmap = Set.map
    x <$ xs = if Set.null xs then Set.empty else Set.singleton x

Methods

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

Maps a function over a functor

(<$) :: Suitable f a => a -> f b -> f a infixl 4 Source #

Replace all values in the input with a default value.

Instances

Functor [] Source # 

Associated Types

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

Methods

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

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

Functor Maybe Source # 

Associated Types

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

Methods

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

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

Functor IO Source # 

Associated Types

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

Methods

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

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

Functor Identity Source # 

Associated Types

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

Methods

fmap :: Suitable Identity b => (a -> b) -> Identity a -> Identity b Source #

(<$) :: Suitable Identity a => a -> Identity b -> Identity a Source #

Functor ZipList Source # 

Associated Types

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

Methods

fmap :: Suitable ZipList b => (a -> b) -> ZipList a -> ZipList b Source #

(<$) :: Suitable ZipList a => a -> ZipList b -> ZipList a Source #

Functor IntMap Source # 

Associated Types

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

Methods

fmap :: Suitable IntMap b => (a -> b) -> IntMap a -> IntMap b Source #

(<$) :: Suitable IntMap a => a -> IntMap b -> IntMap a Source #

Functor Tree Source # 

Associated Types

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

Methods

fmap :: Suitable Tree b => (a -> b) -> Tree a -> Tree b Source #

(<$) :: Suitable Tree a => a -> Tree b -> Tree a Source #

Functor Seq Source # 

Associated Types

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

Methods

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

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

Functor Set Source # 

Associated Types

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

Methods

fmap :: Suitable Set b => (a -> b) -> Set a -> Set b Source #

(<$) :: Suitable Set a => a -> Set b -> Set a Source #

Functor IntSet Source # 

Associated Types

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

Methods

fmap :: Suitable IntSet b => (a -> b) -> IntSet a -> IntSet b Source #

(<$) :: Suitable IntSet a => a -> IntSet b -> IntSet a Source #

Functor ((->) a) Source # 

Associated Types

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

Methods

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

(<$) :: Suitable ((->) a) a => a -> (a -> b) -> a -> a Source #

Functor (Either e) Source # 

Associated Types

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

Methods

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

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

Functor ((,) a) Source # 

Associated Types

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

Methods

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

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

Functor (ST s) Source # 

Associated Types

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

Methods

fmap :: Suitable (ST s) b => (a -> b) -> ST s a -> ST s b Source #

(<$) :: Suitable (ST s) a => a -> ST s b -> ST s a Source #

Functor (Map a) Source # 

Associated Types

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

Methods

fmap :: Suitable (Map a) b => (a -> b) -> Map a a -> Map a b Source #

(<$) :: Suitable (Map a) a => a -> Map a b -> Map a a Source #

Functor m => Functor (MaybeT m) Source # 

Associated Types

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

Methods

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

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

Functor (Const * a) Source # 

Associated Types

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

Methods

fmap :: Suitable (Const * a) b => (a -> b) -> Const * a a -> Const * a b Source #

(<$) :: Suitable (Const * a) a => a -> Const * a b -> Const * a a Source #

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

Functor m => Functor (WriterT s m) Source # 

Associated Types

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

Methods

fmap :: Suitable (WriterT s m) b => (a -> b) -> WriterT s m a -> WriterT s m b Source #

(<$) :: Suitable (WriterT s m) a => a -> WriterT s m b -> WriterT s m a Source #

(Functor f, Functor g) => Functor (Sum * f g) Source # 

Associated Types

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

Methods

fmap :: Suitable (Sum * f g) b => (a -> b) -> Sum * f g a -> Sum * f g b Source #

(<$) :: Suitable (Sum * f g) a => a -> Sum * f g b -> Sum * f g a Source #

(Functor f, Functor g) => Functor (Product * f g) Source # 

Associated Types

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

Methods

fmap :: Suitable (Product * f g) b => (a -> b) -> Product * f g a -> Product * f g b Source #

(<$) :: Suitable (Product * f g) a => a -> Product * f g b -> Product * f g a Source #

Functor (ContT * r m) Source # 

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

fmap :: Suitable (ReaderT * r m) b => (a -> b) -> ReaderT * r m a -> ReaderT * r m b Source #

(<$) :: Suitable (ReaderT * r m) a => a -> ReaderT * r m b -> ReaderT * r m a Source #

(Functor f, Functor g) => Functor (Compose * * f g) Source # 

Associated Types

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

Methods

fmap :: Suitable (Compose * * f g) b => (a -> b) -> Compose * * f g a -> Compose * * f g b Source #

(<$) :: Suitable (Compose * * f g) a => a -> Compose * * f g b -> Compose * * f g a Source #

class (Applicative (Unconstrained f), Functor f) => Applicative f where Source #

A functor with application.

This class is slightly different (although equivalent) to the class provided in the Prelude. This is to facilitate the lifting of functions to arbitrary numbers of arguments.

A minimal complete definition must include implementations of reflect and reify which convert to and from a law-abiding applicative, such that they form an isomorphism. Alternatively, you can conform to the standard prelude classes, and satisfy the following laws:

identity
pure id <*> v = v
composition
pure (.) <*> u <*> v <*> w = u <*> (v <*> w)
homomorphism
pure f <*> pure x = pure (f x)
interchange
u <*> pure y = pure ($ y) <*> u

The other methods have the following default definitions, which may be overridden with equivalent specialized implementations:

As a consequence of these laws, the Functor instance for f will satisfy

If f is also a Monad, it should satisfy

(which implies that pure and <*> satisfy the applicative functor laws).

Minimal complete definition

reflect, reify

Associated Types

type Unconstrained f :: * -> * Source #

Methods

reflect :: f a -> Unconstrained f a Source #

reify :: Suitable f a => Unconstrained f a -> f a Source #

pure :: Suitable f a => a -> f a Source #

Lift a value.

(<*>) :: Suitable f b => f (a -> b) -> f a -> f b infixl 4 Source #

Sequential application.

(*>) :: Suitable f b => f a -> f b -> f b infixl 4 Source #

Sequence actions, discarding the value of the first argument.

(<*) :: Suitable f a => f a -> f b -> f a infixl 4 Source #

Sequence actions, discarding the value of the second argument.

liftA2 :: Suitable f c => (a -> b -> c) -> f a -> f b -> f c Source #

liftA3 :: Suitable f d => (a -> b -> c -> d) -> f a -> f b -> f c -> f d Source #

Instances

Applicative [] Source # 

Associated Types

type Unconstrained ([] :: * -> *) :: * -> * Source #

Methods

reflect :: [a] -> Unconstrained [] a Source #

reify :: Suitable [] a => Unconstrained [] a -> [a] Source #

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

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

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

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

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

liftA3 :: Suitable [] d => (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] Source #

Applicative Maybe Source # 

Associated Types

type Unconstrained (Maybe :: * -> *) :: * -> * Source #

Methods

reflect :: Maybe a -> Unconstrained Maybe a Source #

reify :: Suitable Maybe a => Unconstrained Maybe a -> Maybe a Source #

pure :: Suitable Maybe a => a -> Maybe a Source #

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

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

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

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

liftA3 :: Suitable Maybe d => (a -> b -> c -> d) -> Maybe a -> Maybe b -> Maybe c -> Maybe d Source #

Applicative IO Source # 

Associated Types

type Unconstrained (IO :: * -> *) :: * -> * Source #

Methods

reflect :: IO a -> Unconstrained IO a Source #

reify :: Suitable IO a => Unconstrained IO a -> IO a Source #

pure :: Suitable IO a => a -> IO a Source #

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

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

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

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

liftA3 :: Suitable IO d => (a -> b -> c -> d) -> IO a -> IO b -> IO c -> IO d Source #

Applicative Identity Source # 

Associated Types

type Unconstrained (Identity :: * -> *) :: * -> * Source #

Applicative ZipList Source # 

Associated Types

type Unconstrained (ZipList :: * -> *) :: * -> * Source #

Methods

reflect :: ZipList a -> Unconstrained ZipList a Source #

reify :: Suitable ZipList a => Unconstrained ZipList a -> ZipList a Source #

pure :: Suitable ZipList a => a -> ZipList a Source #

(<*>) :: Suitable ZipList b => ZipList (a -> b) -> ZipList a -> ZipList b Source #

(*>) :: Suitable ZipList b => ZipList a -> ZipList b -> ZipList b Source #

(<*) :: Suitable ZipList a => ZipList a -> ZipList b -> ZipList a Source #

liftA2 :: Suitable ZipList c => (a -> b -> c) -> ZipList a -> ZipList b -> ZipList c Source #

liftA3 :: Suitable ZipList d => (a -> b -> c -> d) -> ZipList a -> ZipList b -> ZipList c -> ZipList d Source #

Applicative Tree Source # 

Associated Types

type Unconstrained (Tree :: * -> *) :: * -> * Source #

Methods

reflect :: Tree a -> Unconstrained Tree a Source #

reify :: Suitable Tree a => Unconstrained Tree a -> Tree a Source #

pure :: Suitable Tree a => a -> Tree a Source #

(<*>) :: Suitable Tree b => Tree (a -> b) -> Tree a -> Tree b Source #

(*>) :: Suitable Tree b => Tree a -> Tree b -> Tree b Source #

(<*) :: Suitable Tree a => Tree a -> Tree b -> Tree a Source #

liftA2 :: Suitable Tree c => (a -> b -> c) -> Tree a -> Tree b -> Tree c Source #

liftA3 :: Suitable Tree d => (a -> b -> c -> d) -> Tree a -> Tree b -> Tree c -> Tree d Source #

Applicative Seq Source # 

Associated Types

type Unconstrained (Seq :: * -> *) :: * -> * Source #

Methods

reflect :: Seq a -> Unconstrained Seq a Source #

reify :: Suitable Seq a => Unconstrained Seq a -> Seq a Source #

pure :: Suitable Seq a => a -> Seq a Source #

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

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

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

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

liftA3 :: Suitable Seq d => (a -> b -> c -> d) -> Seq a -> Seq b -> Seq c -> Seq d Source #

Applicative Set Source # 

Associated Types

type Unconstrained (Set :: * -> *) :: * -> * Source #

Methods

reflect :: Set a -> Unconstrained Set a Source #

reify :: Suitable Set a => Unconstrained Set a -> Set a Source #

pure :: Suitable Set a => a -> Set a Source #

(<*>) :: Suitable Set b => Set (a -> b) -> Set a -> Set b Source #

(*>) :: Suitable Set b => Set a -> Set b -> Set b Source #

(<*) :: Suitable Set a => Set a -> Set b -> Set a Source #

liftA2 :: Suitable Set c => (a -> b -> c) -> Set a -> Set b -> Set c Source #

liftA3 :: Suitable Set d => (a -> b -> c -> d) -> Set a -> Set b -> Set c -> Set d Source #

Applicative IntSet Source # 

Associated Types

type Unconstrained (IntSet :: * -> *) :: * -> * Source #

Methods

reflect :: IntSet a -> Unconstrained IntSet a Source #

reify :: Suitable IntSet a => Unconstrained IntSet a -> IntSet a Source #

pure :: Suitable IntSet a => a -> IntSet a Source #

(<*>) :: Suitable IntSet b => IntSet (a -> b) -> IntSet a -> IntSet b Source #

(*>) :: Suitable IntSet b => IntSet a -> IntSet b -> IntSet b Source #

(<*) :: Suitable IntSet a => IntSet a -> IntSet b -> IntSet a Source #

liftA2 :: Suitable IntSet c => (a -> b -> c) -> IntSet a -> IntSet b -> IntSet c Source #

liftA3 :: Suitable IntSet d => (a -> b -> c -> d) -> IntSet a -> IntSet b -> IntSet c -> IntSet d Source #

Applicative ((->) a) Source # 

Associated Types

type Unconstrained ((->) a :: * -> *) :: * -> * Source #

Methods

reflect :: (a -> a) -> Unconstrained ((->) a) a Source #

reify :: Suitable ((->) a) a => Unconstrained ((->) a) a -> a -> a Source #

pure :: Suitable ((->) a) a => a -> a -> a Source #

(<*>) :: Suitable ((->) a) b => (a -> a -> b) -> (a -> a) -> a -> b Source #

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

(<*) :: Suitable ((->) a) a => (a -> a) -> (a -> b) -> a -> a Source #

liftA2 :: Suitable ((->) a) c => (a -> b -> c) -> (a -> a) -> (a -> b) -> a -> c Source #

liftA3 :: Suitable ((->) a) d => (a -> b -> c -> d) -> (a -> a) -> (a -> b) -> (a -> c) -> a -> d Source #

Applicative (Either a) Source # 

Associated Types

type Unconstrained (Either a :: * -> *) :: * -> * Source #

Methods

reflect :: Either a a -> Unconstrained (Either a) a Source #

reify :: Suitable (Either a) a => Unconstrained (Either a) a -> Either a a Source #

pure :: Suitable (Either a) a => a -> Either a a Source #

(<*>) :: Suitable (Either a) b => Either a (a -> b) -> Either a a -> Either a b Source #

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

(<*) :: Suitable (Either a) a => Either a a -> Either a b -> Either a a Source #

liftA2 :: Suitable (Either a) c => (a -> b -> c) -> Either a a -> Either a b -> Either a c Source #

liftA3 :: Suitable (Either a) d => (a -> b -> c -> d) -> Either a a -> Either a b -> Either a c -> Either a d Source #

Monoid a => Applicative ((,) a) Source # 

Associated Types

type Unconstrained ((,) a :: * -> *) :: * -> * Source #

Methods

reflect :: (a, a) -> Unconstrained ((,) a) a Source #

reify :: Suitable ((,) a) a => Unconstrained ((,) a) a -> (a, a) Source #

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

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

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

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

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

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

Applicative (ST s) Source # 

Associated Types

type Unconstrained (ST s :: * -> *) :: * -> * Source #

Methods

reflect :: ST s a -> Unconstrained (ST s) a Source #

reify :: Suitable (ST s) a => Unconstrained (ST s) a -> ST s a Source #

pure :: Suitable (ST s) a => a -> ST s a Source #

(<*>) :: Suitable (ST s) b => ST s (a -> b) -> ST s a -> ST s b Source #

(*>) :: Suitable (ST s) b => ST s a -> ST s b -> ST s b Source #

(<*) :: Suitable (ST s) a => ST s a -> ST s b -> ST s a Source #

liftA2 :: Suitable (ST s) c => (a -> b -> c) -> ST s a -> ST s b -> ST s c Source #

liftA3 :: Suitable (ST s) d => (a -> b -> c -> d) -> ST s a -> ST s b -> ST s c -> ST s d Source #

(Monad (Unconstrained m), Monad m) => Applicative (MaybeT m) Source # 

Associated Types

type Unconstrained (MaybeT m :: * -> *) :: * -> * Source #

Methods

reflect :: MaybeT m a -> Unconstrained (MaybeT m) a Source #

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

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

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

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

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

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

liftA3 :: Suitable (MaybeT m) d => (a -> b -> c -> d) -> MaybeT m a -> MaybeT m b -> MaybeT m c -> MaybeT m d Source #

Monoid a => Applicative (Const * a) Source # 

Associated Types

type Unconstrained (Const * a :: * -> *) :: * -> * Source #

Methods

reflect :: Const * a a -> Unconstrained (Const * a) a Source #

reify :: Suitable (Const * a) a => Unconstrained (Const * a) a -> Const * a a Source #

pure :: Suitable (Const * a) a => a -> Const * a a Source #

(<*>) :: Suitable (Const * a) b => Const * a (a -> b) -> Const * a a -> Const * a b Source #

(*>) :: Suitable (Const * a) b => Const * a a -> Const * a b -> Const * a b Source #

(<*) :: Suitable (Const * a) a => Const * a a -> Const * a b -> Const * a a Source #

liftA2 :: Suitable (Const * a) c => (a -> b -> c) -> Const * a a -> Const * a b -> Const * a c Source #

liftA3 :: Suitable (Const * a) d => (a -> b -> c -> d) -> Const * a a -> Const * a b -> Const * a c -> Const * a d Source #

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

Associated Types

type Unconstrained (IdentityT * m :: * -> *) :: * -> * Source #

Methods

reflect :: IdentityT * m a -> Unconstrained (IdentityT * m) a Source #

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

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

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

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

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

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

liftA3 :: Suitable (IdentityT * m) d => (a -> b -> c -> d) -> IdentityT * m a -> IdentityT * m b -> IdentityT * m c -> IdentityT * m d Source #

(Monad m, Monad (Unconstrained m)) => Applicative (ExceptT e m) Source # 

Associated Types

type Unconstrained (ExceptT e m :: * -> *) :: * -> * Source #

Methods

reflect :: ExceptT e m a -> Unconstrained (ExceptT e m) a Source #

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

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

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

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

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

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

liftA3 :: Suitable (ExceptT e m) d => (a -> b -> c -> d) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c -> ExceptT e m d Source #

(Monad m, Monad (Unconstrained m)) => Applicative (StateT s m) Source # 

Associated Types

type Unconstrained (StateT s m :: * -> *) :: * -> * Source #

Methods

reflect :: StateT s m a -> Unconstrained (StateT s m) a Source #

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

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

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

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

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

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

liftA3 :: Suitable (StateT s m) d => (a -> b -> c -> d) -> StateT s m a -> StateT s m b -> StateT s m c -> StateT s m d Source #

(Monad m, Monad (Unconstrained m)) => Applicative (StateT s m) Source # 

Associated Types

type Unconstrained (StateT s m :: * -> *) :: * -> * Source #

Methods

reflect :: StateT s m a -> Unconstrained (StateT s m) a Source #

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

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

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

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

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

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

liftA3 :: Suitable (StateT s m) d => (a -> b -> c -> d) -> StateT s m a -> StateT s m b -> StateT s m c -> StateT s m d Source #

(Monad m, Monad (Unconstrained m)) => Applicative (WriterT s m) Source # 

Associated Types

type Unconstrained (WriterT s m :: * -> *) :: * -> * Source #

Methods

reflect :: WriterT s m a -> Unconstrained (WriterT s m) a Source #

reify :: Suitable (WriterT s m) a => Unconstrained (WriterT s m) a -> WriterT s m a Source #

pure :: Suitable (WriterT s m) a => a -> WriterT s m a Source #

(<*>) :: Suitable (WriterT s m) b => WriterT s m (a -> b) -> WriterT s m a -> WriterT s m b Source #

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

(<*) :: Suitable (WriterT s m) a => WriterT s m a -> WriterT s m b -> WriterT s m a Source #

liftA2 :: Suitable (WriterT s m) c => (a -> b -> c) -> WriterT s m a -> WriterT s m b -> WriterT s m c Source #

liftA3 :: Suitable (WriterT s m) d => (a -> b -> c -> d) -> WriterT s m a -> WriterT s m b -> WriterT s m c -> WriterT s m d Source #

(Applicative f, Applicative g) => Applicative (Product * f g) Source # 

Associated Types

type Unconstrained (Product * f g :: * -> *) :: * -> * Source #

Methods

reflect :: Product * f g a -> Unconstrained (Product * f g) a Source #

reify :: Suitable (Product * f g) a => Unconstrained (Product * f g) a -> Product * f g a Source #

pure :: Suitable (Product * f g) a => a -> Product * f g a Source #

(<*>) :: Suitable (Product * f g) b => Product * f g (a -> b) -> Product * f g a -> Product * f g b Source #

(*>) :: Suitable (Product * f g) b => Product * f g a -> Product * f g b -> Product * f g b Source #

(<*) :: Suitable (Product * f g) a => Product * f g a -> Product * f g b -> Product * f g a Source #

liftA2 :: Suitable (Product * f g) c => (a -> b -> c) -> Product * f g a -> Product * f g b -> Product * f g c Source #

liftA3 :: Suitable (Product * f g) d => (a -> b -> c -> d) -> Product * f g a -> Product * f g b -> Product * f g c -> Product * f g d Source #

Applicative (ContT * r m) Source # 

Associated Types

type Unconstrained (ContT * r m :: * -> *) :: * -> * Source #

Methods

reflect :: ContT * r m a -> Unconstrained (ContT * r m) a Source #

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

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

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

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

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

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

liftA3 :: Suitable (ContT * r m) d => (a -> b -> c -> d) -> ContT * r m a -> ContT * r m b -> ContT * r m c -> ContT * r m d Source #

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

Associated Types

type Unconstrained (ReaderT * r m :: * -> *) :: * -> * Source #

Methods

reflect :: ReaderT * r m a -> Unconstrained (ReaderT * r m) a Source #

reify :: Suitable (ReaderT * r m) a => Unconstrained (ReaderT * r m) a -> ReaderT * r m a Source #

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

(<*>) :: Suitable (ReaderT * r m) b => ReaderT * r m (a -> b) -> ReaderT * r m a -> ReaderT * r m b Source #

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

(<*) :: Suitable (ReaderT * r m) a => ReaderT * r m a -> ReaderT * r m b -> ReaderT * r m a Source #

liftA2 :: Suitable (ReaderT * r m) c => (a -> b -> c) -> ReaderT * r m a -> ReaderT * r m b -> ReaderT * r m c Source #

liftA3 :: Suitable (ReaderT * r m) d => (a -> b -> c -> d) -> ReaderT * r m a -> ReaderT * r m b -> ReaderT * r m c -> ReaderT * r m d Source #

(Applicative f, Applicative g) => Applicative (Compose * * f g) Source # 

Associated Types

type Unconstrained (Compose * * f g :: * -> *) :: * -> * Source #

Methods

reflect :: Compose * * f g a -> Unconstrained (Compose * * f g) a Source #

reify :: Suitable (Compose * * f g) a => Unconstrained (Compose * * f g) a -> Compose * * f g a Source #

pure :: Suitable (Compose * * f g) a => a -> Compose * * f g a Source #

(<*>) :: Suitable (Compose * * f g) b => Compose * * f g (a -> b) -> Compose * * f g a -> Compose * * f g b Source #

(*>) :: Suitable (Compose * * f g) b => Compose * * f g a -> Compose * * f g b -> Compose * * f g b Source #

(<*) :: Suitable (Compose * * f g) a => Compose * * f g a -> Compose * * f g b -> Compose * * f g a Source #

liftA2 :: Suitable (Compose * * f g) c => (a -> b -> c) -> Compose * * f g a -> Compose * * f g b -> Compose * * f g c Source #

liftA3 :: Suitable (Compose * * f g) d => (a -> b -> c -> d) -> Compose * * f g a -> Compose * * f g b -> Compose * * f g c -> Compose * * f g d Source #

class Applicative f => Monad f where Source #

The Monad class defines the basic operations over a monad, a concept from a branch of mathematics known as category theory. From the perspective of a Haskell programmer, however, it is best to think of a monad as an abstract datatype of actions. Haskell's do expressions provide a convenient syntax for writing monadic expressions.

Instances of Monad should satisfy the following laws:

Furthermore, the Monad and Applicative operations should relate as follows:

The above laws imply:

and that pure and (<*>) satisfy the applicative functor laws.

The instances of Monad for lists, Maybe and IO defined in the "Prelude" satisfy these laws.

Minimal complete definition

(>>=)

Methods

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

Sequentially compose two actions, passing any value produced by the first as an argument to the second.

Instances

Monad [] Source # 

Methods

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

Monad Maybe Source # 

Methods

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

Monad IO Source # 

Methods

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

Monad Identity Source # 

Methods

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

Monad Tree Source # 

Methods

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

Monad Seq Source # 

Methods

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

Monad Set Source # 

Methods

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

Monad IntSet Source # 

Methods

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

Monad ((->) a) Source # 

Methods

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

Monad (Either a) Source # 

Methods

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

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

Methods

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

Monad (ST s) Source # 

Methods

(>>=) :: Suitable (ST s) b => ST s a -> (a -> ST s b) -> ST s b Source #

(Monad m, Monad (Unconstrained m)) => Monad (MaybeT m) Source # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

(Monad m, Monad (Unconstrained m)) => Monad (WriterT s m) Source # 

Methods

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

(Monad f, Monad g) => Monad (Product * f g) Source # 

Methods

(>>=) :: Suitable (Product * f g) b => Product * f g a -> (a -> Product * f g b) -> Product * f g b Source #

Monad (ContT * r m) Source # 

Methods

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

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

Methods

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

class Applicative f => Alternative f where Source #

A monoid on applicative functors.

If defined, some and many should be the least solutions of the equations:

Minimal complete definition

empty, (<|>)

Methods

empty :: Suitable f a => f a Source #

The identity of <|>

(<|>) :: Suitable f a => f a -> f a -> f a infixl 3 Source #

An associative binary operation

some :: Suitable f [a] => f a -> f [a] Source #

One or more.

many :: Suitable f [a] => f a -> f [a] Source #

Zero or more.

Instances

Alternative [] Source # 

Methods

empty :: Suitable [] a => [a] Source #

(<|>) :: Suitable [] a => [a] -> [a] -> [a] Source #

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

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

Alternative Maybe Source # 

Methods

empty :: Suitable Maybe a => Maybe a Source #

(<|>) :: Suitable Maybe a => Maybe a -> Maybe a -> Maybe a Source #

some :: Suitable Maybe [a] => Maybe a -> Maybe [a] Source #

many :: Suitable Maybe [a] => Maybe a -> Maybe [a] Source #

Alternative IO Source # 

Methods

empty :: Suitable IO a => IO a Source #

(<|>) :: Suitable IO a => IO a -> IO a -> IO a Source #

some :: Suitable IO [a] => IO a -> IO [a] Source #

many :: Suitable IO [a] => IO a -> IO [a] Source #

Alternative Seq Source # 

Methods

empty :: Suitable Seq a => Seq a Source #

(<|>) :: Suitable Seq a => Seq a -> Seq a -> Seq a Source #

some :: Suitable Seq [a] => Seq a -> Seq [a] Source #

many :: Suitable Seq [a] => Seq a -> Seq [a] Source #

Alternative Set Source # 

Methods

empty :: Suitable Set a => Set a Source #

(<|>) :: Suitable Set a => Set a -> Set a -> Set a Source #

some :: Suitable Set [a] => Set a -> Set [a] Source #

many :: Suitable Set [a] => Set a -> Set [a] Source #

Alternative IntSet Source # 
(Monad m, Monad (Unconstrained m)) => Alternative (MaybeT m) Source # 

Methods

empty :: Suitable (MaybeT m) a => MaybeT m a Source #

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

some :: Suitable (MaybeT m) [a] => MaybeT m a -> MaybeT m [a] Source #

many :: Suitable (MaybeT m) [a] => MaybeT m a -> MaybeT m [a] Source #

(Monad m, Monoid e, Monad (Unconstrained m)) => Alternative (ExceptT e m) Source # 

Methods

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

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

some :: Suitable (ExceptT e m) [a] => ExceptT e m a -> ExceptT e m [a] Source #

many :: Suitable (ExceptT e m) [a] => ExceptT e m a -> ExceptT e m [a] Source #

(Monad m, Alternative m, Monad (Unconstrained m)) => Alternative (StateT s m) Source # 

Methods

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

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

some :: Suitable (StateT s m) [a] => StateT s m a -> StateT s m [a] Source #

many :: Suitable (StateT s m) [a] => StateT s m a -> StateT s m [a] Source #

(Monad m, Alternative m, Monad (Unconstrained m)) => Alternative (StateT s m) Source # 

Methods

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

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

some :: Suitable (StateT s m) [a] => StateT s m a -> StateT s m [a] Source #

many :: Suitable (StateT s m) [a] => StateT s m a -> StateT s m [a] Source #

(Alternative f, Alternative g) => Alternative (Product * f g) Source # 

Methods

empty :: Suitable (Product * f g) a => Product * f g a Source #

(<|>) :: Suitable (Product * f g) a => Product * f g a -> Product * f g a -> Product * f g a Source #

some :: Suitable (Product * f g) [a] => Product * f g a -> Product * f g [a] Source #

many :: Suitable (Product * f g) [a] => Product * f g a -> Product * f g [a] Source #

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

Methods

empty :: Suitable (ReaderT * r m) a => ReaderT * r m a Source #

(<|>) :: Suitable (ReaderT * r m) a => ReaderT * r m a -> ReaderT * r m a -> ReaderT * r m a Source #

some :: Suitable (ReaderT * r m) [a] => ReaderT * r m a -> ReaderT * r m [a] Source #

many :: Suitable (ReaderT * r m) [a] => ReaderT * r m a -> ReaderT * r m [a] Source #

(Alternative f, Applicative g) => Alternative (Compose * * f g) Source # 

Methods

empty :: Suitable (Compose * * f g) a => Compose * * f g a Source #

(<|>) :: Suitable (Compose * * f g) a => Compose * * f g a -> Compose * * f g a -> Compose * * f g a Source #

some :: Suitable (Compose * * f g) [a] => Compose * * f g a -> Compose * * f g [a] Source #

many :: Suitable (Compose * * f g) [a] => Compose * * f g a -> Compose * * f g [a] Source #

class (Foldable t, Functor t) => Traversable t where Source #

Functors representing data structures that can be traversed from left to right.

A definition of traverse must satisfy the following laws:

naturality
t . traverse f = traverse (t . f) for every applicative transformation t
identity
traverse Identity = Identity
composition
traverse (Compose . fmap g . f) = Compose . fmap (traverse g) . traverse f

A definition of sequenceA must satisfy the following laws:

naturality
t . sequenceA = sequenceA . fmap t for every applicative transformation t
identity
sequenceA . fmap Identity = Identity
composition
sequenceA . fmap Compose = Compose . fmap sequenceA . sequenceA

where an applicative transformation is a function

t :: (Applicative f, Applicative g) => f a -> g a

preserving the Applicative operations, i.e.

and the identity functor Identity and composition of functors Compose are defined as

  newtype Identity a = Identity a

  instance Functor Identity where
    fmap f (Identity x) = Identity (f x)

  instance Applicative Identity where
    pure x = Identity x
    Identity f <*> Identity x = Identity (f x)

  newtype Compose f g a = Compose (f (g a))

  instance (Functor f, Functor g) => Functor (Compose f g) where
    fmap f (Compose x) = Compose (fmap (fmap f) x)

  instance (Applicative f, Applicative g) => Applicative (Compose f g) where
    pure x = Compose (pure (pure x))
    Compose f <*> Compose x = Compose ((<*>) <$> f <*> x)

(The naturality law is implied by parametricity.)

Instances are similar to Functor, e.g. given a data type

data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)

a suitable instance would be

instance Traversable Tree where
   traverse f Empty = pure Empty
   traverse f (Leaf x) = Leaf <$> f x
   traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r

This is suitable even for abstract types, as the laws for <*> imply a form of associativity.

The superclass instances should satisfy the following:

  • In the Functor instance, fmap should be equivalent to traversal with the identity applicative functor (fmapDefault).
  • In the Foldable instance, foldMap should be equivalent to traversal with a constant applicative functor (foldMapDefault).

Minimal complete definition

traverse

Methods

traverse :: (Suitable t b, Applicative f, Suitable f (t b), Suitable f b) => (a -> f b) -> t a -> f (t b) Source #

Map each element of a structure to an action, evaluate these actions from left to right, and collect the results. For a version that ignores the results see traverse_.

Instances

Traversable [] Source # 

Methods

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

Traversable Maybe Source # 

Methods

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

Traversable Identity Source # 

Methods

traverse :: (Suitable Identity b, Applicative f, Suitable f (Identity b), Suitable f b) => (a -> f b) -> Identity a -> f (Identity b) Source #

Traversable Tree Source # 

Methods

traverse :: (Suitable Tree b, Applicative f, Suitable f (Tree b), Suitable f b) => (a -> f b) -> Tree a -> f (Tree b) Source #

Traversable (Either a) Source # 

Methods

traverse :: (Suitable (Either a) b, Applicative f, Suitable f (Either a b), Suitable f b) => (a -> f b) -> Either a a -> f (Either a b) Source #

Traversable ((,) a) Source # 

Methods

traverse :: (Suitable ((,) a) b, Applicative f, Suitable f (a, b), Suitable f b) => (a -> f b) -> (a, a) -> f (a, b) 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 #

MonadFail Set Source # 

Methods

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

IsString a => MonadFail (Either a) Source # 

Methods

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

(Monad m, Monad (Unconstrained 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, Monad (Unconstrained m)) => 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 #

Unconstrained applicative stuff

ap :: (Monad f, Suitable f a) => (a -> f a) -> Ap f a -> f a Source #

A definition of reify that uses monadic operations. This is actually the instance of applicative for codensity in disguise.

Useful functions

guard :: (Alternative f, Suitable f ()) => Bool -> f () Source #

guard b is pure () if b is True, and empty if b is False.

ensure :: (Alternative f, Suitable f a) => Bool -> f a -> f a Source #

ensure b x is x if b is True, and empty if b is False.

(<**>) :: (Applicative f, Suitable f b) => f a -> f (a -> b) -> f b infixl 4 Source #

A variant of <*> with the arguments reversed.

(<$>) :: (Functor f, Suitable f b) => (a -> b) -> f a -> f b infixl 4 Source #

An infix synonym for fmap.

The name of this operator is an allusion to $. Note the similarities between their types:

 ($)  ::              (a -> b) ->   a ->   b
(<$>) :: Functor f => (a -> b) -> f a -> f b

Whereas $ is function application, <$> is function application lifted over a Functor.

Examples

Convert from a Maybe Int to a Maybe String using show:

>>> show <$> Nothing
Nothing
>>> show <$> Just 3
Just "3"

Convert from an Either Int Int to an Either Int String using show:

>>> show <$> Left 17
Left 17
>>> show <$> Right 17
Right "17"

Double each element of a list:

>>> (*2) <$> [1,2,3]
[2,4,6]

Apply even to the second element of a pair:

>>> even <$> (2,2)
(2,True)

(=<<) :: (Monad f, Suitable f b) => (a -> f b) -> f a -> f b infixr 1 Source #

A flipped version of >>=

(<=<) :: (Monad f, Suitable f c) => (b -> f c) -> (a -> f b) -> a -> f c infixr 1 Source #

Right-to-left Kleisli composition of monads. (>=>), with the arguments flipped.

Note how this operator resembles function composition (.):

(.)   ::            (b ->   c) -> (a ->   b) -> a ->   c
(<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c

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

Left-to-right Kleisli composition of monads.

foldM :: (Foldable t, Monad m, Suitable m b) => (b -> a -> m b) -> b -> t a -> m b Source #

Monadic fold over the elements of a structure, associating to the left, i.e. from left to right.

traverse_ :: (Applicative f, Foldable t, Suitable f ()) => (a -> f b) -> t a -> f () Source #

Map each element of a structure to an action, evaluate these actions from left to right, and ignore the results. For a version that doesn't ignore the results see traverse.

sequenceA :: (Applicative f, Suitable t a, Suitable f (t a), Traversable t, Suitable f a) => t (f a) -> f (t a) Source #

Evaluate each action in the structure from left to right, and and collect the results. For a version that ignores the results see sequenceA_.

sequenceA_ :: (Foldable t, Applicative f, Suitable f ()) => t (f a) -> f () Source #

Evaluate each action in the structure from left to right, and ignore the results. For a version that doesn't ignore the results see sequenceA.

mapAccumL :: (Traversable t, Suitable t c) => (a -> b -> (a, c)) -> a -> t b -> (a, t c) Source #

The mapAccumL function behaves like a combination of fmap and foldl; it applies a function to each element of a structure, passing an accumulating parameter from left to right, and returning a final value of this accumulator together with the new structure.

replicateM :: (Applicative m, Suitable m [a]) => Int -> m a -> m [a] Source #

replicateM n act performs the action n times, gathering the results.

void :: (Functor f, Suitable f ()) => f a -> f () Source #

void value discards or ignores the result of evaluation, such as the return value of an IO action.

Examples

Replace the contents of a Maybe Int with unit:

>>> void Nothing
Nothing
>>> void (Just 3)
Just ()

Replace the contents of an Either Int Int with unit, resulting in an Either Int '()':

>>> void (Left 8675309)
Left 8675309
>>> void (Right 8675309)
Right ()

Replace every element of a list with unit:

>>> void [1,2,3]
[(),(),()]

Replace the second element of a pair with unit:

>>> void (1,2)
(1,())

Discard the result of an IO action:

>>> traverse print [1,2]
1
2
[(),()]
>>> void $ traverse print [1,2]
1
2

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

forever act repeats the action infinitely.

for_ :: (Foldable t, Applicative f, Suitable f ()) => t a -> (a -> f b) -> f () Source #

for_ is traverse_ with its arguments flipped. For a version that doesn't ignore the results see for.

>>> for_ [1..4] print
1
2
3
4

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

Collapse one monadic layer.

Syntax

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

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

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

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

return :: (Applicative f, Suitable f a) => a -> f a Source #

Alias for pure.