[commit: ghc] master: Generalise Data.List/Control.Monad to Foldable/Traversable (1f7f46f)

git at git.haskell.org git at git.haskell.org
Sun Sep 21 17:17:06 UTC 2014


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/1f7f46f94a95ab7fc6f3101da7c02529e1964f24/ghc

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

commit 1f7f46f94a95ab7fc6f3101da7c02529e1964f24
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Sun Sep 21 19:15:46 2014 +0200

    Generalise Data.List/Control.Monad to Foldable/Traversable
    
    This flips the switch and replaces the entities in
    `Data.List`/`Control.Monad` conflicting with
    `Data.{Foldable,Traversable}` with re-exports of the more general
    versions.
    
    As of this commit, the code below (which is also added as a test-case)
    compiles w/o error.
    
        module XPrelude (module X) where
    
        import Control.Monad     as X
        import Data.Foldable     as X
        import Data.List         as X
        import Data.Monoid       as X
        import Data.Traversable  as X
        import Prelude           as X
    
    This addresses #9568
    
    Reviewed By: ekmett, austin
    
    Differential Revision: https://phabricator.haskell.org/D235


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

1f7f46f94a95ab7fc6f3101da7c02529e1964f24
 libraries/base/Control/Monad.hs                    |  9 ++-------
 libraries/base/Data/Foldable.hs                    |  6 ------
 libraries/base/Data/List.hs                        |  8 ++++----
 libraries/base/Data/Traversable.hs                 |  5 -----
 libraries/base/changelog.md                        | 20 ++++++++++++--------
 libraries/base/tests/T9586.hs                      |  8 ++++++++
 libraries/base/tests/all.T                         |  1 +
 testsuite/tests/rename/should_compile/T1972.stderr |  2 +-
 8 files changed, 28 insertions(+), 31 deletions(-)

diff --git a/libraries/base/Control/Monad.hs b/libraries/base/Control/Monad.hs
index c04c4a8..561d40d 100644
--- a/libraries/base/Control/Monad.hs
+++ b/libraries/base/Control/Monad.hs
@@ -78,9 +78,9 @@ module Control.Monad
 
 import Data.Foldable ( sequence_, msum, mapM_, forM_ )
 import Data.Functor ( void )
-import Data.Traversable ()
+import Data.Traversable ( forM, mapM, sequence )
 
-import GHC.Base
+import GHC.Base hiding ( mapM, sequence )
 import GHC.List ( zipWith, unzip, replicate )
 
 -- -----------------------------------------------------------------------------
@@ -101,11 +101,6 @@ filterM p (x:xs) =  do
    ys  <- filterM p xs
    return (if flg then x:ys else ys)
 
--- | 'forM' is 'mapM' with its arguments flipped
-forM            :: Monad m => [a] -> (a -> m b) -> m [b]
-{-# INLINE forM #-}
-forM            = flip mapM
-
 infixr 1 <=<, >=>
 
 -- | Left-to-right Kleisli composition of monads.
diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs
index 726aa6c..2bda827 100644
--- a/libraries/base/Data/Foldable.hs
+++ b/libraries/base/Data/Foldable.hs
@@ -13,12 +13,6 @@
 --
 -- Class of data structures that can be folded to a summary value.
 --
--- Many of these functions generalize "Prelude", "Control.Monad" and
--- "Data.List" functions of the same names from lists to any 'Foldable'
--- functor.  To avoid ambiguity, either import those modules hiding
--- these names or qualify uses of these function names with an alias
--- for this module.
---
 -----------------------------------------------------------------------------
 
 module Data.Foldable (
diff --git a/libraries/base/Data/List.hs b/libraries/base/Data/List.hs
index e742cac..795baec 100644
--- a/libraries/base/Data/List.hs
+++ b/libraries/base/Data/List.hs
@@ -208,9 +208,9 @@ module Data.List
    ) where
 
 import Data.Foldable
-import Data.Traversable ()
+import Data.Traversable
 
 import Data.OldList hiding ( all, and, any, concat, concatMap, elem, find,
-                             foldl, foldl1, foldl', foldr, foldr1, maximum,
-                             maximumBy, minimum, minimumBy, notElem, or,
-                             product, sum )
+                             foldl, foldl1, foldl', foldr, foldr1, mapAccumL,
+                             mapAccumR, maximum, maximumBy, minimum, minimumBy,
+                             notElem, or, product, sum )
diff --git a/libraries/base/Data/Traversable.hs b/libraries/base/Data/Traversable.hs
index d050aea..eb5123d 100644
--- a/libraries/base/Data/Traversable.hs
+++ b/libraries/base/Data/Traversable.hs
@@ -31,11 +31,6 @@
 --    in /Mathematically-Structured Functional Programming/, 2012, online at
 --    <http://arxiv.org/pdf/1202.2919>.
 --
--- Note that the functions 'mapM' and 'sequence' generalize "Prelude"
--- functions of the same names from lists to any 'Traversable' functor.
--- To avoid ambiguity, either import the "Prelude" hiding these names
--- or qualify uses of these function names with an alias for this module.
---
 -----------------------------------------------------------------------------
 
 module Data.Traversable (
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index d7e1133..0d95898 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -38,22 +38,26 @@
   * Replace the `Data.List`-exported functions
 
     ```
-    all, and, any, concat, concatMap, elem, find, product, sum
+    all, and, any, concat, concatMap, elem, find, product, sum,
+    mapAccumL, mapAccumR
     ```
 
-    by re-exports of their generalised `Data.Foldable` counterparts.
-    In other words, unqualified imports of `Data.List` and
-    `Data.Foldable` no longer lead to conflicting definitions. (#9586)
+    by re-exports of their generalised `Data.Foldable`/`Data.Traversable`
+    counterparts.  In other words, unqualified imports of `Data.List`
+    and `Data.Foldable`/`Data.Traversable` no longer lead to conflicting
+    definitions. (#9586)
 
   * Replace the `Control.Monad`-exported functions
 
     ```
-    sequence_, msum, mapM_, forM_
+    sequence_, msum, mapM_, forM_,
+    forM, mapM, sequence
     ```
 
-    by re-exports of their generalised `Data.Foldable` counterparts.
-    In other words, unqualified imports of `Control.Monad` and
-    `Data.Foldable` no longer lead to conflicting definitions. (#9586)
+    by re-exports of their generalised `Data.Foldable`/`Data.Traversable`
+    counterparts.  In other words, unqualified imports of `Control.Monad`
+    and `Data.Foldable`/`Data.Traversable` no longer lead to conflicting
+    definitions. (#9586)
 
   * New module `Data.OldList` containing only list-specialised versions of
     the functions from `Data.List` (in other words, `Data.OldList` corresponds
diff --git a/libraries/base/tests/T9586.hs b/libraries/base/tests/T9586.hs
new file mode 100644
index 0000000..8310b99
--- /dev/null
+++ b/libraries/base/tests/T9586.hs
@@ -0,0 +1,8 @@
+module XPrelude (module X) where
+
+import Control.Monad    as X
+import Data.Foldable    as X
+import Data.List        as X
+import Data.Monoid      as X
+import Data.Traversable as X
+import Prelude          as X
diff --git a/libraries/base/tests/all.T b/libraries/base/tests/all.T
index 5fe862f..6520b21 100644
--- a/libraries/base/tests/all.T
+++ b/libraries/base/tests/all.T
@@ -170,3 +170,4 @@ test('T8766',
 test('T9111', normal, compile, [''])
 test('T9395', normal, compile_and_run, [''])
 test('T9532', normal, compile_and_run, [''])
+test('T9586', normal, compile, [''])
diff --git a/testsuite/tests/rename/should_compile/T1972.stderr b/testsuite/tests/rename/should_compile/T1972.stderr
index 38f013e..0f450fc 100644
--- a/testsuite/tests/rename/should_compile/T1972.stderr
+++ b/testsuite/tests/rename/should_compile/T1972.stderr
@@ -7,6 +7,6 @@ T1972.hs:14:3: Warning:
     This binding for ‘mapAccumL’ shadows the existing bindings
       defined at T1972.hs:16:1
       imported from ‘Data.List’ at T1972.hs:7:1-16
-      (and originally defined in ‘Data.OldList’)
+      (and originally defined in ‘Data.Traversable’)
 
 T1972.hs:20:10: Warning: Defined but not used: ‘c’



More information about the ghc-commits mailing list