[commit: ghc] master: Add strict ver. of (<$>): (<$!>) to Control.Monad (0148a1c)
git at git.haskell.org
git at git.haskell.org
Wed May 14 07:17:07 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/0148a1c416e42a7d7c9ff3624a0640963bfe0012/ghc
>---------------------------------------------------------------
commit 0148a1c416e42a7d7c9ff3624a0640963bfe0012
Author: Alexander Berntsen <alexander at plaimi.net>
Date: Tue May 13 10:50:30 2014 +0200
Add strict ver. of (<$>): (<$!>) to Control.Monad
A strict (<$>) has been proposed numerous times. The first time
around[1] by Johan Tibell, and the last time around[2] by David
Luposchainsky. David's thread was able to avoid The Bikeshed Monster,
and his (<$!>) proposal received unanimous +1s all around.
This addresses #9099.
[1]: http://www.haskell.org/pipermail/libraries/2013-November/021728.html
[2]: http://www.haskell.org/pipermail/libraries/2014-April/022864.html
Authored-by: Alexander Berntsen <alexander at plaimi.net>
Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org>
>---------------------------------------------------------------
0148a1c416e42a7d7c9ff3624a0640963bfe0012
libraries/base/Control/Monad.hs | 15 +++++++++++++++
libraries/base/changelog.md | 2 ++
2 files changed, 17 insertions(+)
diff --git a/libraries/base/Control/Monad.hs b/libraries/base/Control/Monad.hs
index 19c9a87..00c1fdd 100644
--- a/libraries/base/Control/Monad.hs
+++ b/libraries/base/Control/Monad.hs
@@ -74,6 +74,9 @@ module Control.Monad
, ap
+ -- ** Strict monadic functions
+
+ , (<$!>)
) where
import Data.Maybe
@@ -311,6 +314,18 @@ is equivalent to
ap :: (Monad m) => m (a -> b) -> m a -> m b
ap = liftM2 id
+infixl 4 <$!>
+
+-- | Strict version of 'Data.Functor.<$>'.
+--
+-- /Since: 4.7.1.0/
+(<$!>) :: Monad m => (a -> b) -> m a -> m b
+{-# INLINE (<$!>) #-}
+f <$!> m = do
+ x <- m
+ let z = f x
+ z `seq` return z
+
-- -----------------------------------------------------------------------------
-- Other MonadPlus functions
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index c561165..4efb121 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -12,6 +12,8 @@
* Weaken RealFloat constraints on some `Data.Complex` functions
+ * Add `Control.Monad.(<$!>)` as a strict version of `(<$>)`
+
## 4.7.0.0 *Apr 2014*
* Bundled with GHC 7.8.1
More information about the ghc-commits
mailing list