Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC

Commits:

6 changed files:

Changes:

  • libraries/base/changelog.md
    ... ... @@ -11,6 +11,7 @@
    11 11
       * Modify the implementation of `Data.List.sortOn` to use `(>)` instead of `compare`. ([CLC proposal #332](https://github.com/haskell/core-libraries-committee/issues/332))
    
    12 12
       * Add `thenA` and `thenM`. ([CLC proposal #351](https://github.com/haskell/core-libraries-committee/issues/351))
    
    13 13
       * Fix bug where `naturalAndNot` was incorrectly truncating results ([CLC proposal #350](github.com/haskell/core-libraries-committee/issues/350))
    
    14
    +  * generalize `deleteBy` and `deleteFirstsBy` ([CLC proposal 372](https://github.com/haskell/core-libraries-committee/issues/372))
    
    14 15
       * Remove extra laziness from `Data.Bifunctor.Bifunctor` instances for all tuples to have the same laziness as their `Data.Functor.Functor` counterparts (i.e. they became more strict than before) ([CLC proposal #339](https://github.com/haskell/core-libraries-committee/issues/339))
    
    15 16
       * Adjust the strictness of `Data.List.iterate'` to be more reasonable: every element of the output list is forced to WHNF when the `(:)` containing it is forced. ([CLC proposal #335)](https://github.com/haskell/core-libraries-committee/issues/335)
    
    16 17
       * Add `nubOrd` / `nubOrdBy` to `Data.List` and `Data.List.NonEmpty`. ([CLC proposal #336](https://github.com/haskell/core-libraries-committee/issues/336))
    

  • libraries/ghc-internal/src/GHC/Internal/Data/OldList.hs
    ... ... @@ -576,7 +576,7 @@ delete = deleteBy (==)
    576 576
     --
    
    577 577
     -- >>> deleteBy (/=) 5 [5, 5, 4, 3, 5, 2]
    
    578 578
     -- [5,5,3,5,2]
    
    579
    -deleteBy                :: (a -> a -> Bool) -> a -> [a] -> [a]
    
    579
    +deleteBy                :: (a -> b -> Bool) -> a -> [b] -> [b]
    
    580 580
     deleteBy _  _ []        = []
    
    581 581
     deleteBy eq x (y:ys)    = if x `eq` y then ys else y : deleteBy eq x ys
    
    582 582
     
    
    ... ... @@ -1342,7 +1342,7 @@ unzip7 = foldr (\(a,b,c,d,e,f,g) ~(as,bs,cs,ds,es,fs,gs) ->
    1342 1342
     --
    
    1343 1343
     -- >>> deleteFirstsBy (/=) [1..10] [1, 3, 5]
    
    1344 1344
     -- [4,5,6,7,8,9,10]
    
    1345
    -deleteFirstsBy          :: (a -> a -> Bool) -> [a] -> [a] -> [a]
    
    1345
    +deleteFirstsBy          :: (a -> b -> Bool) -> [b] -> [a] -> [b]
    
    1346 1346
     deleteFirstsBy eq       =  foldl (flip (deleteBy eq))
    
    1347 1347
     
    
    1348 1348
     -- | The 'group' function takes a list and returns a list of lists such
    

  • testsuite/tests/interface-stability/base-exports.stdout
    ... ... @@ -1323,8 +1323,8 @@ module Data.List where
    1323 1323
       concatMap :: forall (t :: * -> *) a b. GHC.Internal.Data.Foldable.Foldable t => (a -> [b]) -> t a -> [b]
    
    1324 1324
       cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a]
    
    1325 1325
       delete :: forall a. GHC.Internal.Classes.Eq a => a -> [a] -> [a]
    
    1326
    -  deleteBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> a -> [a] -> [a]
    
    1327
    -  deleteFirstsBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> [a] -> [a] -> [a]
    
    1326
    +  deleteBy :: forall a b. (a -> b -> GHC.Internal.Types.Bool) -> a -> [b] -> [b]
    
    1327
    +  deleteFirstsBy :: forall a b. (a -> b -> GHC.Internal.Types.Bool) -> [b] -> [a] -> [b]
    
    1328 1328
       drop :: forall a. GHC.Internal.Types.Int -> [a] -> [a]
    
    1329 1329
       dropWhile :: forall a. (a -> GHC.Internal.Types.Bool) -> [a] -> [a]
    
    1330 1330
       dropWhileEnd :: forall a. (a -> GHC.Internal.Types.Bool) -> [a] -> [a]
    
    ... ... @@ -8898,8 +8898,8 @@ module GHC.OldList where
    8898 8898
       concatMap :: forall a b. (a -> [b]) -> [a] -> [b]
    
    8899 8899
       cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a]
    
    8900 8900
       delete :: forall a. GHC.Internal.Classes.Eq a => a -> [a] -> [a]
    
    8901
    -  deleteBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> a -> [a] -> [a]
    
    8902
    -  deleteFirstsBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> [a] -> [a] -> [a]
    
    8901
    +  deleteBy :: forall a b. (a -> b -> GHC.Internal.Types.Bool) -> a -> [b] -> [b]
    
    8902
    +  deleteFirstsBy :: forall a b. (a -> b -> GHC.Internal.Types.Bool) -> [b] -> [a] -> [b]
    
    8903 8903
       drop :: forall a. GHC.Internal.Types.Int -> [a] -> [a]
    
    8904 8904
       dropWhile :: forall a. (a -> GHC.Internal.Types.Bool) -> [a] -> [a]
    
    8905 8905
       dropWhileEnd :: forall a. (a -> GHC.Internal.Types.Bool) -> [a] -> [a]
    

  • testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
    ... ... @@ -1323,8 +1323,8 @@ module Data.List where
    1323 1323
       concatMap :: forall (t :: * -> *) a b. GHC.Internal.Data.Foldable.Foldable t => (a -> [b]) -> t a -> [b]
    
    1324 1324
       cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a]
    
    1325 1325
       delete :: forall a. GHC.Internal.Classes.Eq a => a -> [a] -> [a]
    
    1326
    -  deleteBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> a -> [a] -> [a]
    
    1327
    -  deleteFirstsBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> [a] -> [a] -> [a]
    
    1326
    +  deleteBy :: forall a b. (a -> b -> GHC.Internal.Types.Bool) -> a -> [b] -> [b]
    
    1327
    +  deleteFirstsBy :: forall a b. (a -> b -> GHC.Internal.Types.Bool) -> [b] -> [a] -> [b]
    
    1328 1328
       drop :: forall a. GHC.Internal.Types.Int -> [a] -> [a]
    
    1329 1329
       dropWhile :: forall a. (a -> GHC.Internal.Types.Bool) -> [a] -> [a]
    
    1330 1330
       dropWhileEnd :: forall a. (a -> GHC.Internal.Types.Bool) -> [a] -> [a]
    
    ... ... @@ -11944,8 +11944,8 @@ module GHC.OldList where
    11944 11944
       concatMap :: forall a b. (a -> [b]) -> [a] -> [b]
    
    11945 11945
       cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a]
    
    11946 11946
       delete :: forall a. GHC.Internal.Classes.Eq a => a -> [a] -> [a]
    
    11947
    -  deleteBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> a -> [a] -> [a]
    
    11948
    -  deleteFirstsBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> [a] -> [a] -> [a]
    
    11947
    +  deleteBy :: forall a b. (a -> b -> GHC.Internal.Types.Bool) -> a -> [b] -> [b]
    
    11948
    +  deleteFirstsBy :: forall a b. (a -> b -> GHC.Internal.Types.Bool) -> [b] -> [a] -> [b]
    
    11949 11949
       drop :: forall a. GHC.Internal.Types.Int -> [a] -> [a]
    
    11950 11950
       dropWhile :: forall a. (a -> GHC.Internal.Types.Bool) -> [a] -> [a]
    
    11951 11951
       dropWhileEnd :: forall a. (a -> GHC.Internal.Types.Bool) -> [a] -> [a]
    

  • testsuite/tests/interface-stability/base-exports.stdout-mingw32
    ... ... @@ -1323,8 +1323,8 @@ module Data.List where
    1323 1323
       concatMap :: forall (t :: * -> *) a b. GHC.Internal.Data.Foldable.Foldable t => (a -> [b]) -> t a -> [b]
    
    1324 1324
       cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a]
    
    1325 1325
       delete :: forall a. GHC.Internal.Classes.Eq a => a -> [a] -> [a]
    
    1326
    -  deleteBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> a -> [a] -> [a]
    
    1327
    -  deleteFirstsBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> [a] -> [a] -> [a]
    
    1326
    +  deleteBy :: forall a b. (a -> b -> GHC.Internal.Types.Bool) -> a -> [b] -> [b]
    
    1327
    +  deleteFirstsBy :: forall a b. (a -> b -> GHC.Internal.Types.Bool) -> [b] -> [a] -> [b]
    
    1328 1328
       drop :: forall a. GHC.Internal.Types.Int -> [a] -> [a]
    
    1329 1329
       dropWhile :: forall a. (a -> GHC.Internal.Types.Bool) -> [a] -> [a]
    
    1330 1330
       dropWhileEnd :: forall a. (a -> GHC.Internal.Types.Bool) -> [a] -> [a]
    
    ... ... @@ -9116,8 +9116,8 @@ module GHC.OldList where
    9116 9116
       concatMap :: forall a b. (a -> [b]) -> [a] -> [b]
    
    9117 9117
       cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a]
    
    9118 9118
       delete :: forall a. GHC.Internal.Classes.Eq a => a -> [a] -> [a]
    
    9119
    -  deleteBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> a -> [a] -> [a]
    
    9120
    -  deleteFirstsBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> [a] -> [a] -> [a]
    
    9119
    +  deleteBy :: forall a b. (a -> b -> GHC.Internal.Types.Bool) -> a -> [b] -> [b]
    
    9120
    +  deleteFirstsBy :: forall a b. (a -> b -> GHC.Internal.Types.Bool) -> [b] -> [a] -> [b]
    
    9121 9121
       drop :: forall a. GHC.Internal.Types.Int -> [a] -> [a]
    
    9122 9122
       dropWhile :: forall a. (a -> GHC.Internal.Types.Bool) -> [a] -> [a]
    
    9123 9123
       dropWhileEnd :: forall a. (a -> GHC.Internal.Types.Bool) -> [a] -> [a]
    

  • testsuite/tests/interface-stability/base-exports.stdout-ws-32
    ... ... @@ -1323,8 +1323,8 @@ module Data.List where
    1323 1323
       concatMap :: forall (t :: * -> *) a b. GHC.Internal.Data.Foldable.Foldable t => (a -> [b]) -> t a -> [b]
    
    1324 1324
       cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a]
    
    1325 1325
       delete :: forall a. GHC.Internal.Classes.Eq a => a -> [a] -> [a]
    
    1326
    -  deleteBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> a -> [a] -> [a]
    
    1327
    -  deleteFirstsBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> [a] -> [a] -> [a]
    
    1326
    +  deleteBy :: forall a b. (a -> b -> GHC.Internal.Types.Bool) -> a -> [b] -> [b]
    
    1327
    +  deleteFirstsBy :: forall a b. (a -> b -> GHC.Internal.Types.Bool) -> [b] -> [a] -> [b]
    
    1328 1328
       drop :: forall a. GHC.Internal.Types.Int -> [a] -> [a]
    
    1329 1329
       dropWhile :: forall a. (a -> GHC.Internal.Types.Bool) -> [a] -> [a]
    
    1330 1330
       dropWhileEnd :: forall a. (a -> GHC.Internal.Types.Bool) -> [a] -> [a]
    
    ... ... @@ -8898,8 +8898,8 @@ module GHC.OldList where
    8898 8898
       concatMap :: forall a b. (a -> [b]) -> [a] -> [b]
    
    8899 8899
       cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a]
    
    8900 8900
       delete :: forall a. GHC.Internal.Classes.Eq a => a -> [a] -> [a]
    
    8901
    -  deleteBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> a -> [a] -> [a]
    
    8902
    -  deleteFirstsBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> [a] -> [a] -> [a]
    
    8901
    +  deleteBy :: forall a b. (a -> b -> GHC.Internal.Types.Bool) -> a -> [b] -> [b]
    
    8902
    +  deleteFirstsBy :: forall a b. (a -> b -> GHC.Internal.Types.Bool) -> [b] -> [a] -> [b]
    
    8903 8903
       drop :: forall a. GHC.Internal.Types.Int -> [a] -> [a]
    
    8904 8904
       dropWhile :: forall a. (a -> GHC.Internal.Types.Bool) -> [a] -> [a]
    
    8905 8905
       dropWhileEnd :: forall a. (a -> GHC.Internal.Types.Bool) -> [a] -> [a]