[commit: ghc] master: Move (=<<) to GHC.Base (8b90836)

git at git.haskell.org git at git.haskell.org
Thu Sep 18 21:13:15 UTC 2014


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/8b9083655f34120b47fe407123272e0687e0bd60/ghc

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

commit 8b9083655f34120b47fe407123272e0687e0bd60
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Thu Sep 18 23:05:31 2014 +0200

    Move (=<<) to GHC.Base
    
    This allows GHC.Stack to avoid importing Control.Monad, and
    is preparatory work for implementing #9586
    
    Reviewed By: austin
    
    Differential Revision: https://phabricator.haskell.org/D221


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

8b9083655f34120b47fe407123272e0687e0bd60
 libraries/base/Control/Monad.hs          | 6 ------
 libraries/base/GHC/Base.lhs              | 6 ++++++
 libraries/base/GHC/Event/Manager.hs      | 2 +-
 libraries/base/GHC/Event/Poll.hsc        | 2 +-
 libraries/base/GHC/Event/TimerManager.hs | 2 +-
 libraries/base/GHC/Stack.hsc             | 2 --
 6 files changed, 9 insertions(+), 11 deletions(-)

diff --git a/libraries/base/Control/Monad.hs b/libraries/base/Control/Monad.hs
index 532c42c..089e996 100644
--- a/libraries/base/Control/Monad.hs
+++ b/libraries/base/Control/Monad.hs
@@ -81,17 +81,11 @@ import Data.Maybe
 import GHC.List
 import GHC.Base
 
-infixr 1 =<<
 infixl 3 <|>
 
 -- -----------------------------------------------------------------------------
 -- Prelude monad functions
 
--- | Same as '>>=', but with the arguments interchanged.
-{-# SPECIALISE (=<<) :: (a -> [b]) -> [a] -> [b] #-}
-(=<<)           :: Monad m => (a -> m b) -> m a -> m b
-f =<< x         = x >>= f
-
 -- | Evaluate each action in the sequence from left to right,
 -- and collect the results.
 sequence       :: Monad m => [m a] -> m [a] 
diff --git a/libraries/base/GHC/Base.lhs b/libraries/base/GHC/Base.lhs
index 54ba348..14a6957 100644
--- a/libraries/base/GHC/Base.lhs
+++ b/libraries/base/GHC/Base.lhs
@@ -121,6 +121,7 @@ infixr 9  .
 infixr 5  ++
 infixl 4  <$
 infixl 1  >>, >>=
+infixr 1  =<<
 infixr 0  $, $!
 
 infixl 4 <*>, <*, *>, <**>
@@ -487,6 +488,11 @@ original default.
 
 -}
 
+-- | Same as '>>=', but with the arguments interchanged.
+{-# SPECIALISE (=<<) :: (a -> [b]) -> [a] -> [b] #-}
+(=<<)           :: Monad m => (a -> m b) -> m a -> m b
+f =<< x         = x >>= f
+
 -- | Promote a function to a monad.
 liftM   :: (Monad m) => (a1 -> r) -> m a1 -> m r
 liftM f m1              = do { x1 <- m1; return (f x1) }
diff --git a/libraries/base/GHC/Event/Manager.hs b/libraries/base/GHC/Event/Manager.hs
index 9f12ecd..b6c028a 100644
--- a/libraries/base/GHC/Event/Manager.hs
+++ b/libraries/base/GHC/Event/Manager.hs
@@ -52,7 +52,7 @@ module GHC.Event.Manager
 import Control.Concurrent.MVar (MVar, newMVar, readMVar, putMVar,
                                 tryPutMVar, takeMVar, withMVar)
 import Control.Exception (onException)
-import Control.Monad ((=<<), forM_, when, replicateM, void)
+import Control.Monad (forM_, when, replicateM, void)
 import Data.Bits ((.&.))
 import Data.IORef (IORef, atomicModifyIORef', mkWeakIORef, newIORef, readIORef,
                    writeIORef)
diff --git a/libraries/base/GHC/Event/Poll.hsc b/libraries/base/GHC/Event/Poll.hsc
index fd05a13..686bc71 100644
--- a/libraries/base/GHC/Event/Poll.hsc
+++ b/libraries/base/GHC/Event/Poll.hsc
@@ -26,7 +26,7 @@ available = False
 #include <poll.h>
 
 import Control.Concurrent.MVar (MVar, newMVar, swapMVar)
-import Control.Monad ((=<<), unless)
+import Control.Monad (unless)
 import Data.Bits (Bits, FiniteBits, (.|.), (.&.))
 import Data.Word
 import Foreign.C.Types (CInt(..), CShort(..))
diff --git a/libraries/base/GHC/Event/TimerManager.hs b/libraries/base/GHC/Event/TimerManager.hs
index 435693a..e55dddf 100644
--- a/libraries/base/GHC/Event/TimerManager.hs
+++ b/libraries/base/GHC/Event/TimerManager.hs
@@ -39,7 +39,7 @@ module GHC.Event.TimerManager
 -- Imports
 
 import Control.Exception (finally)
-import Control.Monad ((=<<), sequence_, when)
+import Control.Monad (sequence_, when)
 import Data.IORef (IORef, atomicModifyIORef', mkWeakIORef, newIORef, readIORef,
                    writeIORef)
 import GHC.Base
diff --git a/libraries/base/GHC/Stack.hsc b/libraries/base/GHC/Stack.hsc
index 0b30391..91fddfb 100644
--- a/libraries/base/GHC/Stack.hsc
+++ b/libraries/base/GHC/Stack.hsc
@@ -34,8 +34,6 @@ module GHC.Stack (
     renderStack
   ) where
 
-import Control.Monad ( (=<<) )
-
 import Foreign
 import Foreign.C
 



More information about the ghc-commits mailing list