Stability | experimental |
---|---|
Safe Haskell | Safe |
Language | Haskell2010 |
This module defines a class Has
intended to be used with the MonadReader
class
or Reader
/ ReaderT
types.
The problem
Assume there are two types representing the MonadReader
environments
for different parts of an application:
data DbConfig = DbConfig { .. } data WebConfig = WebConfig { .. }
as well as a single type containing both of those:
data AppEnv = AppEnv { dbConfig :: DbConfig , webConfig :: WebConfig }
What should be the MonadReader
constraint of the DB module and web module respectively?
- It could be
MonadReader AppEnv m
for both, introducing unnecessary coupling. - Or it could be
MonadReader DbConfig m
for the DB module andMonadReader WebConfig m
for the web module respectively, but combining them becomes a pain.
Or, it could be MonadReader r m, Has DbConfig r
for the DB module (and similarly for the web module),
where some appropriately defined Has part record
class allows projecting part
out of some record
.
This approach keeps both modules decoupled, while allowing using them in the same monad stack.
The only downside is that now one has to define the Has
class and write tediuos instances for the AppEnv
type
(and potentially other types in case of, for example, tests).
But why bother doing the work that the machine will happily do for you?
The solution
This module defines the generic Has
class as well as hides all the boilerplate behind GHC.Generics,
so all you have to do is to add the corresponding deriving
-clause:
data AppEnv = AppEnv { dbConfig :: DbConfig , webConfig :: WebConfig } deriving (Generic, Has DbConfig, Has WebConfig)
and use ask extract
instead of ask
(but this is something you'd have to do anyway).
Type safety
What should happen if record
does not have any field of type part
at all?
Of course, this means that we cannot project part
out of record
, and no Has
instance can be derived at all.
Indeed, this library will refuse to generate an instance in this case.
On the other hand, what should happen if record
contains multiple values of type part
,
perhaps on different levels of nesting? While technically we could make an arbitrary choice, like taking
the first one in breadth-first or depth-first order, we instead decide that such a choice is inherently ambiguous,
so this library will refuse to generate an instance in this case as well.
Updating the records, or poor man's lenses, and State
One we know that a value of type part
is contained in record
,
we might easily update a record
having a function that updates the part
.
This is done in the obvious way: we just locate the part
in the record
and update
it!
Has
has a method for this, called (unsurprisingly) update
.
Note that this might be used for more composable functions living in State
:
now instead of MonadState StateType m
we write (MonadState s m, Has StateType s)
and use update
and extract
where necessary
(likely in combination with modify
and gets
).
Exports
This module also reexports Reader
along with some functions like ask
or reader
with types adjusted for the intended usage of the Has
class.
Synopsis
- class Has part record where
- type SuccessfulSearch part record path = (Search part (Rep record) ~ 'Found path, GHas path part (Rep record))
- guard :: Alternative f => Bool -> f ()
- join :: Monad m => m (m a) -> m a
- class Applicative m => Monad (m :: Type -> Type) where
- class Functor (f :: Type -> Type) where
- class Monad m => MonadFix (m :: Type -> Type) where
- mfix :: (a -> m a) -> m a
- class Monad m => MonadFail (m :: Type -> Type) where
- mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b)
- sequence :: (Traversable t, Monad m) => t (m a) -> m (t a)
- class Monad m => MonadIO (m :: Type -> Type) where
- zipWithM_ :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m ()
- zipWithM :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m [c]
- unless :: Applicative f => Bool -> f () -> f ()
- replicateM_ :: Applicative m => Int -> m a -> m ()
- replicateM :: Applicative m => Int -> m a -> m [a]
- mfilter :: MonadPlus m => (a -> Bool) -> m a -> m a
- mapAndUnzipM :: Applicative m => (a -> m (b, c)) -> [a] -> m ([b], [c])
- forever :: Applicative f => f a -> f b
- foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m ()
- foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
- filterM :: Applicative m => (a -> m Bool) -> [a] -> m [a]
- (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c
- (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c
- (<$!>) :: Monad m => (a -> b) -> m a -> m b
- forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b)
- sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
- msum :: (Foldable t, MonadPlus m) => t (m a) -> m a
- mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
- forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m ()
- fix :: (a -> a) -> a
- void :: Functor f => f a -> f ()
- class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where
- when :: Applicative f => Bool -> f () -> f ()
- liftM5 :: Monad m => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r
- liftM4 :: Monad m => (a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r
- liftM3 :: Monad m => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r
- liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
- liftM :: Monad m => (a1 -> r) -> m a1 -> m r
- ap :: Monad m => m (a -> b) -> m a -> m b
- (=<<) :: Monad m => (a -> m b) -> m a -> m b
- class MonadTrans (t :: (Type -> Type) -> Type -> Type) where
- class Monad m => MonadReader r (m :: Type -> Type) | m -> r where
- local :: (r -> r) -> m a -> m a
- mapReader :: (a -> b) -> Reader r a -> Reader r b
- mapReaderT :: (m a -> n b) -> ReaderT r m a -> ReaderT r n b
- runReader :: Reader r a -> r -> a
- withReader :: (r' -> r) -> Reader r a -> Reader r' a
- withReaderT :: forall r' r (m :: Type -> Type) a. (r' -> r) -> ReaderT r m a -> ReaderT r' m a
- type Reader r = ReaderT r Identity
- newtype ReaderT r (m :: Type -> Type) a = ReaderT {
- runReaderT :: r -> m a
- ask :: (MonadReader record m, Has part record) => m part
- asks :: (MonadReader record m, Has part record) => (part -> a) -> m a
- reader :: (MonadReader record m, Has part record) => (part -> a) -> m a
Documentation
class Has part record where Source #
The Has part record
class is used for records of type record
supporting
projecting out a value of type part
.
Nothing
extract :: record -> part Source #
Extract a subvalue of type part
from the record
.
The default implementation searches for some value of the type part
in record
and returns that value.
The default implementation typechecks iff there is a single subvalue of type part
in record
.
default extract :: forall path. (Generic record, SuccessfulSearch part record path) => record -> part Source #
update :: (part -> part) -> record -> record Source #
Update the record
given an update function for the part
.
The default implementation searches for some value of the type part
in record
and updates that value using the supplied function.
The default implementation typechecks iff there is a single subvalue of type part
in record
.
default update :: forall path. (Generic record, SuccessfulSearch part record path) => (part -> part) -> record -> record Source #
Instances
Has record record Source # | Each type allows projecting itself (and that is an |
SuccessfulSearch a (a0, a1) path => Has a (a0, a1) Source # | |
SuccessfulSearch a (a0, a1, a2) path => Has a (a0, a1, a2) Source # | |
SuccessfulSearch a (a0, a1, a2, a3) path => Has a (a0, a1, a2, a3) Source # | |
SuccessfulSearch a (a0, a1, a2, a3, a4) path => Has a (a0, a1, a2, a3, a4) Source # | |
SuccessfulSearch a (a0, a1, a2, a3, a4, a5) path => Has a (a0, a1, a2, a3, a4, a5) Source # | |
type SuccessfulSearch part record path = (Search part (Rep record) ~ 'Found path, GHas path part (Rep record)) Source #
Type alias representing that the search of part
in record
has been successful.
The path
is used to guide the default generic implementation of Has
.
guard :: Alternative f => Bool -> f () #
Conditional failure of Alternative
computations. Defined by
guard True =pure
() guard False =empty
Examples
Common uses of guard
include conditionally signaling an error in
an error monad and conditionally rejecting the current choice in an
Alternative
-based parser.
As an example of signaling an error in the error monad Maybe
,
consider a safe division function safeDiv x y
that returns
Nothing
when the denominator y
is zero and
otherwise. For example:Just
(x `div`
y)
>>>
safeDiv 4 0
Nothing
>>>
safeDiv 4 2
Just 2
A definition of safeDiv
using guards, but not guard
:
safeDiv :: Int -> Int -> Maybe Int safeDiv x y | y /= 0 = Just (x `div` y) | otherwise = Nothing
A definition of safeDiv
using guard
and Monad
do
-notation:
safeDiv :: Int -> Int -> Maybe Int safeDiv x y = do guard (y /= 0) return (x `div` y)
join :: Monad m => m (m a) -> m a #
The join
function is the conventional monad join operator. It
is used to remove one level of monadic structure, projecting its
bound argument into the outer level.
'
' can be understood as the join
bssdo
expression
do bs <- bss bs
Examples
A common use of join
is to run an IO
computation returned from
an STM
transaction, since STM
transactions
can't perform IO
directly. Recall that
atomically
:: STM a -> IO a
is used to run STM
transactions atomically. So, by
specializing the types of atomically
and join
to
atomically
:: STM (IO b) -> IO (IO b)join
:: IO (IO b) -> IO b
we can compose them as
join
.atomically
:: STM (IO b) -> IO b
class Applicative m => Monad (m :: Type -> Type) where #
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:
- Left identity
return
a>>=
k = k a- Right identity
m
>>=
return
= m- Associativity
m
>>=
(\x -> k x>>=
h) = (m>>=
k)>>=
h
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.
(>>=) :: m a -> (a -> m b) -> m b infixl 1 #
Sequentially compose two actions, passing any value produced by the first as an argument to the second.
'as
' can be understood as the >>=
bsdo
expression
do a <- as bs a
(>>) :: m a -> m b -> m b infixl 1 #
Sequentially compose two actions, discarding any value produced by the first, like sequencing operators (such as the semicolon) in imperative languages.
'as
' can be understood as the >>
bsdo
expression
do as bs
Inject a value into the monadic type.
Instances
Monad Down | Since: base-4.11.0.0 |
Monad Par1 | Since: base-4.9.0.0 |
Monad P | Since: base-2.1 |
Monad ReadP | Since: base-2.1 |
Monad IO | Since: base-2.1 |
Monad NonEmpty | Since: base-4.9.0.0 |
Monad Maybe | Since: base-2.1 |
Monad Solo | Since: base-4.15 |
Monad [] | Since: base-2.1 |
Monad (Either e) | Since: base-4.4.0.0 |
Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Monad (U1 :: Type -> Type) | Since: base-4.9.0.0 |
Monad m => Monad (ListT m) | |
Monad m => Monad (MaybeT m) | |
Monoid a => Monad ((,) a) | Since: base-4.9.0.0 |
Monad f => Monad (Rec1 f) | Since: base-4.9.0.0 |
(Monad m, Error e) => Monad (ErrorT e m) | |
Monad m => Monad (ExceptT e m) | |
Monad m => Monad (IdentityT m) | |
Monad m => Monad (ReaderT r m) | |
Monad m => Monad (StateT s m) | |
Monad m => Monad (StateT s m) | |
(Monoid w, Monad m) => Monad (WriterT w m) | |
(Monoid w, Monad m) => Monad (WriterT w m) | |
(Monoid a, Monoid b) => Monad ((,,) a b) | Since: base-4.14.0.0 |
(Monad f, Monad g) => Monad (f :*: g) | Since: base-4.9.0.0 |
Monad (ContT r m) | |
(Monoid a, Monoid b, Monoid c) => Monad ((,,,) a b c) | Since: base-4.14.0.0 |
Monad ((->) r) | Since: base-2.1 |
Monad f => Monad (M1 i c f) | Since: base-4.9.0.0 |
(Monoid w, Monad m) => Monad (RWST r w s m) | |
(Monoid w, Monad m) => Monad (RWST r w s m) | |
class Functor (f :: Type -> Type) where #
A type f
is a Functor if it provides a function fmap
which, given any types a
and b
lets you apply any function from (a -> b)
to turn an f a
into an f b
, preserving the
structure of f
. Furthermore f
needs to adhere to the following:
Note, that the second law follows from the free theorem of the type fmap
and
the first law, so you need only check that the former condition holds.
fmap :: (a -> b) -> f a -> f b #
fmap
is used to apply a function of type (a -> b)
to a value of type f a
,
where f is a functor, to produce a value of type f b
.
Note that for any type constructor with more than one parameter (e.g., Either
),
only the last type parameter can be modified with fmap
(e.g., b
in `Either a b`).
Some type constructors with two parameters or more have a
instance that allows
both the last and the penultimate parameters to be mapped over.Bifunctor
Examples
Convert from a
to a Maybe
IntMaybe String
using show
:
>>>
fmap show Nothing
Nothing>>>
fmap show (Just 3)
Just "3"
Convert from an
to an
Either
Int IntEither Int String
using show
:
>>>
fmap show (Left 17)
Left 17>>>
fmap show (Right 17)
Right "17"
Double each element of a list:
>>>
fmap (*2) [1,2,3]
[2,4,6]
Apply even
to the second element of a pair:
>>>
fmap even (2,2)
(2,True)
It may seem surprising that the function is only applied to the last element of the tuple
compared to the list example above which applies it to every element in the list.
To understand, remember that tuples are type constructors with multiple type parameters:
a tuple of 3 elements (a,b,c)
can also be written (,,) a b c
and its Functor
instance
is defined for Functor ((,,) a b)
(i.e., only the third parameter is free to be mapped over
with fmap
).
It explains why fmap
can be used with tuples containing values of different types as in the
following example:
>>>
fmap even ("hello", 1.0, 4)
("hello",1.0,True)
Instances
Functor Handler | Since: base-4.6.0.0 |
Functor Down | Since: base-4.11.0.0 |
Functor Par1 | Since: base-4.9.0.0 |
Functor P | Since: base-4.8.0.0 |
Defined in Text.ParserCombinators.ReadP | |
Functor ReadP | Since: base-2.1 |
Functor IO | Since: base-2.1 |
Functor NonEmpty | Since: base-4.9.0.0 |
Functor Maybe | Since: base-2.1 |
Functor Solo | Since: base-4.15 |
Functor [] | Since: base-2.1 |
Functor (Either a) | Since: base-3.0 |
Functor (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Functor (U1 :: Type -> Type) | Since: base-4.9.0.0 |
Functor (V1 :: TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
Functor m => Functor (ListT m) | |
Functor m => Functor (MaybeT m) | |
Functor ((,) a) | Since: base-2.1 |
Functor f => Functor (Rec1 f) | Since: base-4.9.0.0 |
Functor (URec (Ptr ()) :: TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
Functor (URec Char :: TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
Functor (URec Double :: TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
Functor (URec Float :: TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
Functor (URec Int :: TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
Functor (URec Word :: TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
Functor m => Functor (ErrorT e m) | |
Functor m => Functor (ExceptT e m) | |
Functor m => Functor (IdentityT m) | |
Functor m => Functor (ReaderT r m) | |
Functor m => Functor (StateT s m) | |
Functor m => Functor (StateT s m) | |
Functor m => Functor (WriterT w m) | |
Functor m => Functor (WriterT w m) | |
Functor ((,,) a b) | Since: base-4.14.0.0 |
(Functor f, Functor g) => Functor (f :*: g) | Since: base-4.9.0.0 |
(Functor f, Functor g) => Functor (f :+: g) | Since: base-4.9.0.0 |
Functor (K1 i c :: TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
Functor (ContT r m) | |
Functor ((,,,) a b c) | Since: base-4.14.0.0 |
Functor ((->) r) | Since: base-2.1 |
(Functor f, Functor g) => Functor (f :.: g) | Since: base-4.9.0.0 |
Functor f => Functor (M1 i c f) | Since: base-4.9.0.0 |
Functor m => Functor (RWST r w s m) | |
Functor m => Functor (RWST r w s m) | |
class Monad m => MonadFix (m :: Type -> Type) where #
Monads having fixed points with a 'knot-tying' semantics.
Instances of MonadFix
should satisfy the following laws:
- Purity
mfix
(return
. h) =return
(fix
h)- Left shrinking (or Tightening)
mfix
(\x -> a >>= \y -> f x y) = a >>= \y ->mfix
(\x -> f x y)- Sliding
, for strictmfix
(liftM
h . f) =liftM
h (mfix
(f . h))h
.- Nesting
mfix
(\x ->mfix
(\y -> f x y)) =mfix
(\x -> f x x)
This class is used in the translation of the recursive do
notation
supported by GHC and Hugs.
Instances
class Monad m => MonadFail (m :: Type -> Type) where #
When a value is bound in do
-notation, the pattern on the left
hand side of <-
might not match. In this case, this class
provides a function to recover.
A Monad
without a MonadFail
instance may only be used in conjunction
with pattern that always match, such as newtypes, tuples, data types with
only a single data constructor, and irrefutable patterns (~pat
).
Instances of MonadFail
should satisfy the following law: fail s
should
be a left zero for >>=
,
fail s >>= f = fail s
If your Monad
is also MonadPlus
, a popular definition is
fail _ = mzero
Since: base-4.9.0.0
Instances
mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) #
Map each element of a structure to a monadic action, evaluate
these actions from left to right, and collect the results. For
a version that ignores the results see mapM_
.
Examples
sequence :: (Traversable t, Monad m) => t (m a) -> m (t a) #
Evaluate each monadic action in the structure from left to
right, and collect the results. For a version that ignores the
results see sequence_
.
Examples
Basic usage:
The first two examples are instances where the input and
and output of sequence
are isomorphic.
>>>
sequence $ Right [1,2,3,4]
[Right 1,Right 2,Right 3,Right 4]
>>>
sequence $ [Right 1,Right 2,Right 3,Right 4]
Right [1,2,3,4]
The following examples demonstrate short circuit behavior
for sequence
.
>>>
sequence $ Left [1,2,3,4]
Left [1,2,3,4]
>>>
sequence $ [Left 0, Right 1,Right 2,Right 3,Right 4]
Left 0
class Monad m => MonadIO (m :: Type -> Type) where #
Monads in which IO
computations may be embedded.
Any monad built by applying a sequence of monad transformers to the
IO
monad will be an instance of this class.
Instances should satisfy the following laws, which state that liftIO
is a transformer of monads:
Lift a computation from the IO
monad.
This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations
(i.e. IO
is the base monad for the stack).
Example
import Control.Monad.Trans.State -- from the "transformers" library printState :: Show s => StateT s IO () printState = do state <- get liftIO $ print state
Had we omitted
, we would have ended up with this error:liftIO
• Couldn't match type ‘IO’ with ‘StateT s IO’ Expected type: StateT s IO () Actual type: IO ()
The important part here is the mismatch between StateT s IO ()
and
.IO
()
Luckily, we know of a function that takes an
and returns an IO
a(m a)
:
,
enabling us to run the program and see the expected results:liftIO
> evalStateT printState "hello" "hello" > evalStateT printState 3 3
Instances
zipWithM_ :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m () #
zipWithM :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m [c] #
unless :: Applicative f => Bool -> f () -> f () #
The reverse of when
.
replicateM_ :: Applicative m => Int -> m a -> m () #
replicateM :: Applicative m => Int -> m a -> m [a] #
performs the action replicateM
n actact
n
times,
and then returns the list of results:
Examples
>>>
import Control.Monad.State
>>>
runState (replicateM 3 $ state $ \s -> (s, s + 1)) 1
([1,2,3],4)
mapAndUnzipM :: Applicative m => (a -> m (b, c)) -> [a] -> m ([b], [c]) #
The mapAndUnzipM
function maps its first argument over a list, returning
the result as a pair of lists. This function is mainly used with complicated
data structures or a state monad.
forever :: Applicative f => f a -> f b #
Repeat an action indefinitely.
Examples
A common use of forever
is to process input from network sockets,
Handle
s, and channels
(e.g. MVar
and
Chan
).
For example, here is how we might implement an echo
server, using
forever
both to listen for client connections on a network socket
and to echo client input on client connection handles:
echoServer :: Socket -> IO () echoServer socket =forever
$ do client <- accept socketforkFinally
(echo client) (\_ -> hClose client) where echo :: Handle -> IO () echo client =forever
$ hGetLine client >>= hPutStrLn client
Note that "forever" isn't necessarily non-terminating.
If the action is in a
and short-circuits after some number of iterations.
then MonadPlus
actually returns forever
mzero
, effectively short-circuiting its caller.
foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m () #
Like foldM
, but discards the result.
foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b #
The foldM
function is analogous to foldl
, except that its result is
encapsulated in a monad. Note that foldM
works from left-to-right over
the list arguments. This could be an issue where (
and the `folded
function' are not commutative.>>
)
foldM f a1 [x1, x2, ..., xm] == do a2 <- f a1 x1 a3 <- f a2 x2 ... f am xm
If right-to-left evaluation is required, the input list should be reversed.
filterM :: Applicative m => (a -> m Bool) -> [a] -> m [a] #
This generalizes the list-based filter
function.
(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1 #
Left-to-right composition of Kleisli arrows.
'(bs
' can be understood as the >=>
cs) ado
expression
do b <- bs a cs b
forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) #
sequence_ :: (Foldable t, Monad m) => t (m a) -> m () #
Evaluate each monadic action in the structure from left to right,
and ignore the results. For a version that doesn't ignore the
results see sequence
.
sequence_
is just like sequenceA_
, but specialised to monadic
actions.
is the least fixed point of the function fix
ff
,
i.e. the least defined x
such that f x = x
.
For example, we can write the factorial function using direct recursion as
>>>
let fac n = if n <= 1 then 1 else n * fac (n-1) in fac 5
120
This uses the fact that Haskell’s let
introduces recursive bindings. We can
rewrite this definition using fix
,
>>>
fix (\rec n -> if n <= 1 then 1 else n * rec (n-1)) 5
120
Instead of making a recursive call, we introduce a dummy parameter rec
;
when used within fix
, this parameter then refers to fix
’s argument, hence
the recursion is reintroduced.
void :: Functor f => f a -> f () #
discards or ignores the result of evaluation, such
as the return value of an void
valueIO
action.
Examples
Replace the contents of a
with unit:Maybe
Int
>>>
void Nothing
Nothing>>>
void (Just 3)
Just ()
Replace the contents of an
with unit, resulting in an Either
Int
Int
: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:
>>>
mapM print [1,2]
1 2 [(),()]>>>
void $ mapM print [1,2]
1 2
class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where #
Monads that also support choice and failure.
Nothing
The identity of mplus
. It should also satisfy the equations
mzero >>= f = mzero v >> mzero = mzero
The default definition is
mzero = empty
An associative operation. The default definition is
mplus = (<|>
)
Instances
MonadPlus P | Since: base-2.1 |
Defined in Text.ParserCombinators.ReadP | |
MonadPlus ReadP | Since: base-2.1 |
MonadPlus IO | Since: base-4.9.0.0 |
MonadPlus Maybe | Since: base-2.1 |
MonadPlus [] | Since: base-2.1 |
MonadPlus (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
MonadPlus (U1 :: Type -> Type) | Since: base-4.9.0.0 |
Monad m => MonadPlus (ListT m) | |
Monad m => MonadPlus (MaybeT m) | |
MonadPlus f => MonadPlus (Rec1 f) | Since: base-4.9.0.0 |
(Monad m, Error e) => MonadPlus (ErrorT e m) | |
(Monad m, Monoid e) => MonadPlus (ExceptT e m) | |
MonadPlus m => MonadPlus (IdentityT m) | |
MonadPlus m => MonadPlus (ReaderT r m) | |
MonadPlus m => MonadPlus (StateT s m) | |
MonadPlus m => MonadPlus (StateT s m) | |
(Monoid w, MonadPlus m) => MonadPlus (WriterT w m) | |
(Monoid w, MonadPlus m) => MonadPlus (WriterT w m) | |
(MonadPlus f, MonadPlus g) => MonadPlus (f :*: g) | Since: base-4.9.0.0 |
MonadPlus f => MonadPlus (M1 i c f) | Since: base-4.9.0.0 |
(Monoid w, MonadPlus m) => MonadPlus (RWST r w s m) | |
(Monoid w, MonadPlus m) => MonadPlus (RWST r w s m) | |
when :: Applicative f => Bool -> f () -> f () #
Conditional execution of Applicative
expressions. For example,
when debug (putStrLn "Debugging")
will output the string Debugging
if the Boolean value debug
is True
, and otherwise do nothing.
liftM5 :: Monad m => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r #
Promote a function to a monad, scanning the monadic arguments from
left to right (cf. liftM2
).
liftM4 :: Monad m => (a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r #
Promote a function to a monad, scanning the monadic arguments from
left to right (cf. liftM2
).
liftM3 :: Monad m => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r #
Promote a function to a monad, scanning the monadic arguments from
left to right (cf. liftM2
).
liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r #
Promote a function to a monad, scanning the monadic arguments from left to right. For example,
liftM2 (+) [0,1] [0,2] = [0,2,1,3] liftM2 (+) (Just 1) Nothing = Nothing
(=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 #
Same as >>=
, but with the arguments interchanged.
class MonadTrans (t :: (Type -> Type) -> Type -> Type) where #
The class of monad transformers. Instances should satisfy the
following laws, which state that lift
is a monad transformation:
lift :: Monad m => m a -> t m a #
Lift a computation from the argument monad to the constructed monad.
Instances
MonadTrans ListT | |
Defined in Control.Monad.Trans.List | |
MonadTrans MaybeT | |
Defined in Control.Monad.Trans.Maybe | |
MonadTrans (ErrorT e) | |
Defined in Control.Monad.Trans.Error | |
MonadTrans (ExceptT e) | |
Defined in Control.Monad.Trans.Except | |
MonadTrans (IdentityT :: (Type -> Type) -> Type -> Type) | |
Defined in Control.Monad.Trans.Identity | |
MonadTrans (ReaderT r) | |
Defined in Control.Monad.Trans.Reader | |
MonadTrans (StateT s) | |
Defined in Control.Monad.Trans.State.Lazy | |
MonadTrans (StateT s) | |
Defined in Control.Monad.Trans.State.Strict | |
Monoid w => MonadTrans (WriterT w) | |
Defined in Control.Monad.Trans.Writer.Lazy | |
Monoid w => MonadTrans (WriterT w) | |
Defined in Control.Monad.Trans.Writer.Strict | |
MonadTrans (ContT r) | |
Defined in Control.Monad.Trans.Cont | |
Monoid w => MonadTrans (RWST r w s) | |
Defined in Control.Monad.Trans.RWS.Lazy | |
Monoid w => MonadTrans (RWST r w s) | |
Defined in Control.Monad.Trans.RWS.Strict |
class Monad m => MonadReader r (m :: Type -> Type) | m -> r where #
See examples in Control.Monad.Reader.
Note, the partially applied function type (->) r
is a simple reader monad.
See the instance
declaration below.
:: (r -> r) | The function to modify the environment. |
-> m a |
|
-> m a |
Executes a computation in a modified environment.
Instances
MonadReader r m => MonadReader r (ListT m) | |
MonadReader r m => MonadReader r (MaybeT m) | |
(Error e, MonadReader r m) => MonadReader r (ErrorT e m) | |
MonadReader r m => MonadReader r (ExceptT e m) | Since: mtl-2.2 |
MonadReader r m => MonadReader r (IdentityT m) | |
Monad m => MonadReader r (ReaderT r m) | |
MonadReader r m => MonadReader r (StateT s m) | |
MonadReader r m => MonadReader r (StateT s m) | |
(Monoid w, MonadReader r m) => MonadReader r (WriterT w m) | |
(Monoid w, MonadReader r m) => MonadReader r (WriterT w m) | |
MonadReader r ((->) r) | |
MonadReader r' m => MonadReader r' (ContT r m) | |
(Monad m, Monoid w) => MonadReader r (RWST r w s m) | |
(Monad m, Monoid w) => MonadReader r (RWST r w s m) | |
mapReaderT :: (m a -> n b) -> ReaderT r m a -> ReaderT r n b #
Transform the computation inside a ReaderT
.
runReaderT
(mapReaderT
f m) = f .runReaderT
m
:: Reader r a | A |
-> r | An initial environment. |
-> a |
Runs a Reader
and extracts the final value from it.
(The inverse of reader
.)
:: (r' -> r) | The function to modify the environment. |
-> Reader r a | Computation to run in the modified environment. |
-> Reader r' a |
Execute a computation in a modified environment
(a specialization of withReaderT
).
runReader
(withReader
f m) =runReader
m . f
:: forall r' r (m :: Type -> Type) a. (r' -> r) | The function to modify the environment. |
-> ReaderT r m a | Computation to run in the modified environment. |
-> ReaderT r' m a |
Execute a computation in a modified environment
(a more general version of local
).
runReaderT
(withReaderT
f m) =runReaderT
m . f
type Reader r = ReaderT r Identity #
The parameterizable reader monad.
Computations are functions of a shared environment.
The return
function ignores the environment, while >>=
passes
the inherited environment to both subcomputations.
newtype ReaderT r (m :: Type -> Type) a #
The reader monad transformer, which adds a read-only environment to the given monad.
The return
function ignores the environment, while >>=
passes
the inherited environment to both subcomputations.
ReaderT | |
|
Instances
MonadError e m => MonadError e (ReaderT r m) | |
Defined in Control.Monad.Error.Class throwError :: e -> ReaderT r m a # catchError :: ReaderT r m a -> (e -> ReaderT r m a) -> ReaderT r m a # | |
Monad m => MonadReader r (ReaderT r m) | |
MonadTrans (ReaderT r) | |
Defined in Control.Monad.Trans.Reader | |
MonadFail m => MonadFail (ReaderT r m) | |
Defined in Control.Monad.Trans.Reader | |
MonadFix m => MonadFix (ReaderT r m) | |
Defined in Control.Monad.Trans.Reader | |
MonadIO m => MonadIO (ReaderT r m) | |
Defined in Control.Monad.Trans.Reader | |
MonadZip m => MonadZip (ReaderT r m) | |
Contravariant m => Contravariant (ReaderT r m) | |
Alternative m => Alternative (ReaderT r m) | |
Applicative m => Applicative (ReaderT r m) | |
Defined in Control.Monad.Trans.Reader | |
Functor m => Functor (ReaderT r m) | |
Monad m => Monad (ReaderT r m) | |
MonadPlus m => MonadPlus (ReaderT r m) | |
ask :: (MonadReader record m, Has part record) => m part Source #
Retrieves the part
of the monad environment.
This is Control.Monad.Reader's ask
with the type adjusted for better compatibility with Has
.
asks :: (MonadReader record m, Has part record) => (part -> a) -> m a Source #
Retrieves a function of the part
of the current environment.
This is Control.Monad.Reader's asks
with the type adjusted for better compatibility with Has
.
reader :: (MonadReader record m, Has part record) => (part -> a) -> m a Source #
Retrieves a function of the part
of the current environment.
This is Control.Monad.Reader's reader
with the type adjusted for better compatibility with Has
.