[commit: ghc] master: base: Add some notes about the default impl of '(>>)' (65f887e)
git at git.haskell.org
git at git.haskell.org
Mon Sep 15 10:04:49 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/65f887e1a0d864526f6a2609a3afc2c151c25e38/ghc
>---------------------------------------------------------------
commit 65f887e1a0d864526f6a2609a3afc2c151c25e38
Author: Austin Seipp <austin at well-typed.com>
Date: Mon Sep 15 05:02:21 2014 -0500
base: Add some notes about the default impl of '(>>)'
See Note [Recursive bindings for Applicative/Monad]. This documents the
tricky little details that kept me occupied for so long with this patch,
and why exactly we deviate from the original proposal.
Signed-off-by: Austin Seipp <austin at well-typed.com>
>---------------------------------------------------------------
65f887e1a0d864526f6a2609a3afc2c151c25e38
libraries/base/GHC/Base.lhs | 24 +++++++++++++++++++++++-
1 file changed, 23 insertions(+), 1 deletion(-)
diff --git a/libraries/base/GHC/Base.lhs b/libraries/base/GHC/Base.lhs
index 94c9404..3267bbf 100644
--- a/libraries/base/GHC/Base.lhs
+++ b/libraries/base/GHC/Base.lhs
@@ -418,7 +418,7 @@ class Applicative m => Monad m where
-- by the first, like sequencing operators (such as the semicolon)
-- in imperative languages.
(>>) :: forall a b. m a -> m b -> m b
- m >> k = m >>= \_ -> k
+ m >> k = m >>= \_ -> k -- See Note [Recursive bindings for Applicative/Monad]
{-# INLINE (>>) #-}
-- | Inject a value into the monadic type.
@@ -430,6 +430,28 @@ class Applicative m => Monad m where
fail :: String -> m a
fail s = error s
+{- Note [Recursive bindings for Applicative/Monad]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+The original Applicative/Monad proposal stated that after
+implementation, the designated implementation of (>>) would become
+
+ (>>) :: forall a b. m a -> m b -> m b
+ (>>) = (*>)
+
+by default. You might be inclined to change this to reflect the stated
+proposal, but you really shouldn't! Why? Because people tend to define
+such instances the /other/ way around: in particular, it is perfectly
+legitimate to define an instance of Applicative (*>) in terms of (>>),
+which would lead to an infinite loop for the default implementation of
+Monad! And people do this in the wild.
+
+This turned into a nasty bug that was tricky to track down, and rather
+than eliminate it everywhere upstream, it's easier to just retain the
+original default.
+
+-}
+
-- | Promote a function to a monad.
liftM :: (Monad m) => (a1 -> r) -> m a1 -> m r
liftM f m1 = do { x1 <- m1; return (f x1) }
More information about the ghc-commits
mailing list