[commit: ghc] master: Generalize `Control.Monad.forever` (6d69c3a)

git at git.haskell.org git at git.haskell.org
Tue Jul 7 17:17:43 UTC 2015


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/6d69c3a264a1cfbbc7ecda0e704598afa45848c2/ghc

>---------------------------------------------------------------

commit 6d69c3a264a1cfbbc7ecda0e704598afa45848c2
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Tue Jul 7 17:07:06 2015 +0200

    Generalize `Control.Monad.forever`
    
    This generalizes forever to depend on Applicative, rather than Monad.
    
    This was proposed a month ago
    (https://mail.haskell.org/pipermail/libraries/2015-May/025711.html).
    
    Differential Revision: https://phabricator.haskell.org/D1045


>---------------------------------------------------------------

6d69c3a264a1cfbbc7ecda0e704598afa45848c2
 libraries/base/Control/Monad.hs | 4 ++--
 libraries/base/changelog.md     | 2 ++
 2 files changed, 4 insertions(+), 2 deletions(-)

diff --git a/libraries/base/Control/Monad.hs b/libraries/base/Control/Monad.hs
index 6fa4a07..be3765d 100644
--- a/libraries/base/Control/Monad.hs
+++ b/libraries/base/Control/Monad.hs
@@ -113,9 +113,9 @@ f >=> g     = \x -> f x >>= g
 (<=<)       = flip (>=>)
 
 -- | @'forever' act@ repeats the action infinitely.
-forever     :: (Monad m) => m a -> m b
+forever     :: (Applicative f) => f a -> f b
 {-# INLINE forever #-}
-forever a   = let a' = a >> a' in a'
+forever a   = let a' = a *> a' in a'
 -- Use explicit sharing here, as it is prevents a space leak regardless of
 -- optimizations.
 
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index 363210d..bb09199 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -40,6 +40,8 @@
   * Generalize `Debug.Trace.{traceM, traceShowM}` from `Monad` to `Applicative`
     (#10023)
 
+  * Generalise `forever` from `Monad` to `Applicative`
+
 ## 4.8.1.0  *TBA*
 
   * Bundled with GHC 7.10.2



More information about the ghc-commits mailing list