[commit: ghc] master: Preserve argument order to (==)/eq in nub and nubBy (a2e7bbf)

git at git.haskell.org git at git.haskell.org
Fri Nov 7 16:48:59 UTC 2014


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

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

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

commit a2e7bbfe7656cf7dbf1af4da5c077ac0b5d41127
Author: Thomas Miedema <thomasmiedema at gmail.com>
Date:   Fri Nov 7 17:38:59 2014 +0100

    Preserve argument order to (==)/eq in nub and nubBy
    
    This makes nub and nubBy behave as specified in the Haskell 98 Report.
    
    This reverts 0ad9def53842e86fb292eccb810190711c42d7c5, and
    fixes #3280, #7913 and #2528 (properly).
    
    Before this change, the output of `T2528` was (4x wrong):
    ```
    [A,B]
    [1,2]
    False
    False
    ```
    
    Reviewed By: dfeuer, ekmett, austin, hvr
    
    Differential Revision: https://phabricator.haskell.org/D238


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

a2e7bbfe7656cf7dbf1af4da5c077ac0b5d41127
 libraries/base/Data/OldList.hs    | 17 +++++------------
 libraries/base/changelog.md       |  4 ++++
 libraries/base/tests/.gitignore   |  1 +
 libraries/base/tests/T2528.hs     | 27 +++++++++++++++++++++++++++
 libraries/base/tests/T2528.stdout |  4 ++++
 libraries/base/tests/all.T        |  2 ++
 6 files changed, 43 insertions(+), 12 deletions(-)

diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs
index e1de19a..caad044 100644
--- a/libraries/base/Data/OldList.hs
+++ b/libraries/base/Data/OldList.hs
@@ -338,17 +338,7 @@ isInfixOf needle haystack = any (isPrefixOf needle) (tails haystack)
 -- It is a special case of 'nubBy', which allows the programmer to supply
 -- their own equality test.
 nub                     :: (Eq a) => [a] -> [a]
-#ifdef USE_REPORT_PRELUDE
 nub                     =  nubBy (==)
-#else
--- stolen from HBC
-nub l                   = nub' l []             -- '
-  where
-    nub' [] _           = []                    -- '
-    nub' (x:xs) ls                              -- '
-        | x `elem` ls   = nub' xs ls            -- '
-        | otherwise     = x : nub' xs (x:ls)    -- '
-#endif
 
 -- | The 'nubBy' function behaves just like 'nub', except it uses a
 -- user-supplied equality predicate instead of the overloaded '=='
@@ -358,6 +348,7 @@ nubBy                   :: (a -> a -> Bool) -> [a] -> [a]
 nubBy eq []             =  []
 nubBy eq (x:xs)         =  x : nubBy eq (filter (\ y -> not (eq x y)) xs)
 #else
+-- stolen from HBC
 nubBy eq l              = nubBy' l []
   where
     nubBy' [] _         = []
@@ -367,12 +358,14 @@ nubBy eq l              = nubBy' l []
 
 -- Not exported:
 -- Note that we keep the call to `eq` with arguments in the
--- same order as in the reference implementation
+-- same order as in the reference (prelude) implementation,
+-- and that this order is different from how `elem` calls (==).
+-- See #2528, #3280 and #7913.
 -- 'xs' is the list of things we've seen so far,
 -- 'y' is the potential new element
 elem_by :: (a -> a -> Bool) -> a -> [a] -> Bool
 elem_by _  _ []         =  False
-elem_by eq y (x:xs)     =  y `eq` x || elem_by eq y xs
+elem_by eq y (x:xs)     =  x `eq` y || elem_by eq y xs
 #endif
 
 
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index 86595d6..2fa25ae 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -93,6 +93,10 @@
 
   * Add `isSubsequenceOf` to `Data.List` (#9767)
 
+  * The arguments to `==` and `eq` in `Data.List.nub` and `Data.List.nubBy`
+    are swapped, such that `Data.List.nubBy (<) [1,2]` now returns `[1]`
+    instead of `[1,2]` (#2528, #3280, #7913)
+
 ## 4.7.0.1  *Jul 2014*
 
   * Bundled with GHC 7.8.3
diff --git a/libraries/base/tests/.gitignore b/libraries/base/tests/.gitignore
index 973ab9d..af90b5e 100644
--- a/libraries/base/tests/.gitignore
+++ b/libraries/base/tests/.gitignore
@@ -190,6 +190,7 @@
 /System/getArgs001
 /System/getEnv001
 /System/system001
+/T2528
 /T4006
 /T5943
 /T5962
diff --git a/libraries/base/tests/T2528.hs b/libraries/base/tests/T2528.hs
new file mode 100644
index 0000000..f1568db
--- /dev/null
+++ b/libraries/base/tests/T2528.hs
@@ -0,0 +1,27 @@
+module Main where
+
+import qualified Data.List as L
+
+-- USE_REPORT_PRELUDE versions of nub and nubBy, copied from
+-- libraries/base/Data/OldList.hs.
+nub                     :: (Eq a) => [a] -> [a]
+nub                     =  nubBy (==)
+
+nubBy                   :: (a -> a -> Bool) -> [a] -> [a]
+nubBy eq []             =  []
+nubBy eq (x:xs)         =  x : nubBy eq (filter (\ y -> not (eq x y)) xs)
+
+data Asymmetric = A | B deriving Show
+
+instance Eq Asymmetric where
+  A == _ = True
+  B == _ = False
+
+main :: IO()
+main = do
+  print $ L.nub [A,B]
+  print $ L.nubBy (<) [1,2]
+  -- The implementation from Data.List and the one from the Prelude defined in
+  -- the Haskell 98 report should have the same behavior.
+  print $ L.nub [A,B] == nub [A,B]
+  print $ L.nubBy (<) [1,2] == nubBy (<) [1,2]
diff --git a/libraries/base/tests/T2528.stdout b/libraries/base/tests/T2528.stdout
new file mode 100644
index 0000000..4f90091
--- /dev/null
+++ b/libraries/base/tests/T2528.stdout
@@ -0,0 +1,4 @@
+[A]
+[1]
+True
+True
diff --git a/libraries/base/tests/all.T b/libraries/base/tests/all.T
index f7944f4..d4005b7 100644
--- a/libraries/base/tests/all.T
+++ b/libraries/base/tests/all.T
@@ -110,6 +110,8 @@ test('stableptr005', normal, compile_and_run, [''])
 
 test('weak001', normal, compile_and_run, [''])
 
+test('T2528', normal, compile_and_run, [''])
+
 # In the 65001 codepage, we can't even cat the expected output on msys:
 #     $ cat 4006.stdout
 #     It works here



More information about the ghc-commits mailing list