summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorHerbert Valerio Riedel <hvr@gnu.org>2014-09-28 08:46:07 +0200
committerHerbert Valerio Riedel <hvr@gnu.org>2014-09-28 08:47:50 +0200
commita07ce1654ac5b8033f2daf9270c6e182415b69ca (patch)
treec195b72f1df0c5acf11b0d8f70ca3625f76a4ada
parent071167c793489f4071c348223f9591d20dbe11a3 (diff)
downloadhaskell-a07ce1654ac5b8033f2daf9270c6e182415b69ca.tar.gz
Generalise `Control.Monad.{when,unless,guard}`
Generalise `when`/`unless`from `Monad` to `Applicative` and `guard` from `MonadPlus` to `Alternative` respectively. This was made possible by the AMP and is somewhat related to #9586 (but generalising in the context of the AMP instead of the FTP) Reviewed By: ekmett, austin Differential Revision: https://phabricator.haskell.org/D253
-rw-r--r--libraries/base/Control/Monad.hs12
-rw-r--r--libraries/base/GHC/Base.lhs6
-rw-r--r--libraries/base/changelog.md3
3 files changed, 12 insertions, 9 deletions
diff --git a/libraries/base/Control/Monad.hs b/libraries/base/Control/Monad.hs
index 3fe4450ba0..94318be738 100644
--- a/libraries/base/Control/Monad.hs
+++ b/libraries/base/Control/Monad.hs
@@ -85,11 +85,11 @@ import GHC.List ( zipWith, unzip, replicate )
-- -----------------------------------------------------------------------------
-- Functions mandated by the Prelude
--- | @'guard' b@ is @'return' ()@ if @b@ is 'True',
--- and 'mzero' if @b@ is 'False'.
+-- | @'guard' b@ is @'pure' ()@ if @b@ is 'True',
+-- and 'empty' if @b@ is 'False'.
guard :: (MonadPlus m) => Bool -> m ()
-guard True = return ()
-guard False = mzero
+guard True = pure ()
+guard False = empty
-- | This generalizes the list-based 'filter' function.
@@ -186,11 +186,11 @@ replicateM_ :: (Monad m) => Int -> m a -> m ()
replicateM_ n x = sequence_ (replicate n x)
-- | The reverse of 'when'.
-unless :: (Monad m) => Bool -> m () -> m ()
+unless :: (Applicative f) => Bool -> f () -> f ()
{-# INLINEABLE unless #-}
{-# SPECIALISE unless :: Bool -> IO () -> IO () #-}
{-# SPECIALISE unless :: Bool -> Maybe () -> Maybe () #-}
-unless p s = if p then return () else s
+unless p s = if p then pure () else s
infixl 4 <$!>
diff --git a/libraries/base/GHC/Base.lhs b/libraries/base/GHC/Base.lhs
index e6e35f3b92..8b51c07645 100644
--- a/libraries/base/GHC/Base.lhs
+++ b/libraries/base/GHC/Base.lhs
@@ -493,17 +493,17 @@ original default.
(=<<) :: Monad m => (a -> m b) -> m a -> m b
f =<< x = x >>= f
--- | Conditional execution of monadic expressions. For example,
+-- | 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.
-when :: (Monad m) => Bool -> m () -> m ()
+when :: (Applicative f) => Bool -> f () -> f ()
{-# INLINEABLE when #-}
{-# SPECIALISE when :: Bool -> IO () -> IO () #-}
{-# SPECIALISE when :: Bool -> Maybe () -> Maybe () #-}
-when p s = if p then s else return ()
+when p s = if p then s else pure ()
-- | Evaluate each action in the sequence from left to right,
-- and collect the results.
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index 1afcb0edc5..7b168fec5c 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -66,6 +66,9 @@
and `Data.Foldable`/`Data.Traversable` no longer lead to conflicting
definitions. (#9586)
+ * Generalise `Control.Monad.{when,unless,guard}` from `Monad` to
+ `Applicative` and from `MonadPlus` to `Alternative` respectively.
+
* New module `Data.OldList` containing only list-specialised versions of
the functions from `Data.List` (in other words, `Data.OldList` corresponds
to `base-4.7.0.1`'s `Data.List`)