| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Prolude.Monad
Synopsis
- guard :: Alternative f => Bool -> f ()
- join :: Monad m => m (m a) -> m a
- when :: Applicative f => Bool -> f () -> f ()
- void :: Functor f => f a -> f ()
- forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m ()
- forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b)
- forever :: Applicative f => f a -> f b
- unless :: Applicative f => Bool -> f () -> f ()
Documentation
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 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.
'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
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.
void :: Functor f => f a -> f () #
void valueIO action.
Using ApplicativeDo: 'void asdo expression
do as pure ()
with an inferred Functor constraint.
Examples
Replace the contents of a Maybe Int
>>>void NothingNothing>>>void (Just 3)Just ()
Replace the contents of an Either Int IntEither 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
forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) #
forever :: Applicative f => f a -> f b #
Repeat an action indefinitely.
Using ApplicativeDo: 'forever asdo expression
do as as ..
with as repeating.
Examples
A common use of forever is to process input from network sockets,
 Handles, 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
unless :: Applicative f => Bool -> f () -> f () #
The reverse of when.