Safe Haskell | None |
---|---|
Language | Haskell2010 |
Control-flow
Synopsis
- class Monad m => MonadIO (m :: Type -> Type) where
- class MonadIO m => MonadInIO (m :: Type -> Type) where
- (>.>) :: (a -> b) -> (b -> c) -> a -> c
- (<.<) :: (b -> c) -> (a -> b) -> a -> c
- (|>) :: a -> (a -> b) -> b
- (<|) :: (a -> b) -> a -> b
- (||>) :: Functor f => f a -> (a -> b) -> f b
- (<||) :: Functor f => (a -> b) -> f a -> f b
- (|||>) :: (Functor f, Functor g) => f (g a) -> (a -> b) -> f (g b)
- (<|||) :: (Functor f, Functor g) => (a -> b) -> f (g a) -> f (g b)
- when :: Applicative f => Bool -> f () -> f ()
- unless :: Applicative f => Bool -> f () -> f ()
- whenM :: Monad m => m Bool -> m () -> m ()
- unlessM :: Monad m => m Bool -> m () -> m ()
- ifM :: Monad m => m Bool -> m a -> m a -> m a
- guard :: Alternative f => Bool -> f ()
- void :: Functor f => f a -> f ()
- forever :: Applicative f => f a -> f b
- foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
- foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m ()
- forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b)
- forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m ()
- forMaybeM :: Monad m => [a] -> (a -> m (Maybe b)) -> m [b]
- mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b)
- mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
- sequence :: (Traversable t, Monad m) => t (m a) -> m (t a)
- replicateM :: Applicative m => Int -> m a -> m [a]
- replicateM_ :: Applicative m => Int -> m a -> m ()
- filterM :: Applicative m => (a -> m Bool) -> [a] -> m [a]
- join :: Monad m => m (m a) -> m a
- (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c
- (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c
- loopM :: Monad m => (a -> m (Either a b)) -> a -> m b
- whileM :: Monad m => m Bool -> m ()
- intersperseM_ :: Monad m => m () -> [a] -> (a -> m ()) -> m ()
- forLoopM_ :: Monad m => a -> (a -> Bool) -> (a -> a) -> (a -> m ()) -> m ()
- forLoop :: a -> (a -> Bool) -> (a -> a) -> acc -> (acc -> a -> acc) -> acc
- module Haskus.Utils.Variant.Excepts
- lift :: (MonadTrans t, Monad m) => m a -> t m a
Documentation
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:
Instances
MonadIO IO | Since: base-4.9.0.0 |
Defined in Control.Monad.IO.Class | |
MonadIO Q | |
Defined in Language.Haskell.TH.Syntax | |
MonadIO m => MonadIO (ListT m) | |
MonadIO m => MonadIO (IdentityT m) | |
Defined in Control.Monad.Trans.Identity | |
(Functor f, MonadIO m) => MonadIO (FreeT f m) | |
Defined in Control.Monad.Trans.Free | |
MonadIO m => MonadIO (Excepts es m) | |
Defined in Haskus.Utils.Variant.Excepts | |
MonadIO m => MonadIO (StateT s m) | |
Defined in Control.Monad.Trans.State.Lazy | |
(Error e, MonadIO m) => MonadIO (ErrorT e m) | |
Defined in Control.Monad.Trans.Error |
class MonadIO m => MonadInIO (m :: Type -> Type) where #
liftWith :: (forall c. (a -> IO c) -> IO c) -> (a -> m b) -> m b #
Lift with*-like functions into IO (alloca, etc.)
liftWith2 :: (forall c. (a -> b -> IO c) -> IO c) -> (a -> b -> m e) -> m e #
Lift with*-like functions into IO (alloca, etc.)
Basic operators
(||>) :: Functor f => f a -> (a -> b) -> f b infixl 0 Source #
Apply a function in a Functor
>>>
Just 5 ||> (*2)
Just 10
(<||) :: Functor f => (a -> b) -> f a -> f b infixr 0 Source #
Apply a function in a Functor
>>>
(*2) <|| Just 5
Just 10
(|||>) :: (Functor f, Functor g) => f (g a) -> (a -> b) -> f (g b) infixl 0 Source #
Apply a function in a Functor
>>>
Just [5] |||> (*2)
Just [10]
(<|||) :: (Functor f, Functor g) => (a -> b) -> f (g a) -> f (g b) infixr 0 Source #
Apply a function in a Functor
>>>
(*2) <||| Just [5]
Just [10]
Monadic/applicative operators
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.
unless :: Applicative f => Bool -> f () -> f () #
The reverse of when
.
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)
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
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
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.
foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m () #
Like foldM
, but discards the result.
forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) #
forMaybeM :: Monad m => [a] -> (a -> m (Maybe b)) -> m [b] Source #
Composition of catMaybes and forM
>>>
let f x = if x > 3 then putStrLn "OK" >> return (Just x) else return Nothing
>>>
forMaybeM [0..5] f
OK OK [4,5]
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_
.
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_
.
replicateM :: Applicative m => Int -> m a -> m [a] #
performs the action replicateM
n actn
times,
gathering the results.
replicateM_ :: Applicative m => Int -> m a -> m () #
Like replicateM
, but discards the result.
filterM :: Applicative m => (a -> m Bool) -> [a] -> m [a] #
This generalizes the list-based filter
function.
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.
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
(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1 #
Left-to-right composition of Kleisli arrows.
intersperseM_ :: Monad m => m () -> [a] -> (a -> m ()) -> m () Source #
forM_ with interspersed action
>>>
intersperseM_ (putStr ", ") ["1","2","3","4"] putStr
1, 2, 3, 4
forLoopM_ :: Monad m => a -> (a -> Bool) -> (a -> a) -> (a -> m ()) -> m () Source #
Fast for-loop in a Monad (more efficient than forM_ [0..n] for instance).
>>>
forLoopM_ (0::Word) (<5) (+1) print
0 1 2 3 4
forLoop :: a -> (a -> Bool) -> (a -> a) -> acc -> (acc -> a -> acc) -> acc Source #
Fast fort-loop with an accumulated result
>>>
let f acc n = acc ++ (if n == 0 then "" else ", ") ++ show n
>>>
forLoop (0::Word) (<5) (+1) "" f
"0, 1, 2, 3, 4"
Variant based operators
module Haskus.Utils.Variant.Excepts
Monad transformers
lift :: (MonadTrans t, Monad m) => m a -> t m a #
Lift a computation from the argument monad to the constructed monad.