[Git][ghc/ghc][wip/clc-86] Deprecate Data.List.NonEmpty.unzip

Melanie Brown (@mixphix) gitlab at gitlab.haskell.org
Sat Jun 24 22:07:13 UTC 2023



Melanie Brown pushed to branch wip/clc-86 at Glasgow Haskell Compiler / GHC


Commits:
d80325d2 by Melanie Phoenix at 2023-06-24T18:06:51-04:00
Deprecate Data.List.NonEmpty.unzip

- - - - -


10 changed files:

- compiler/GHC/Data/Bag.hs
- libraries/Cabal
- libraries/base/Control/Monad/Zip.hs
- libraries/base/Data/List/NonEmpty.hs
- libraries/base/changelog.md
- libraries/hpc
- libraries/process
- libraries/stm
- utils/haddock
- utils/hsc2hs


Changes:

=====================================
compiler/GHC/Data/Bag.hs
=====================================
@@ -7,6 +7,7 @@ Bag: an unordered collection with duplicates
 -}
 
 {-# LANGUAGE ScopedTypeVariables, DeriveTraversable, TypeFamilies #-}
+{-# OPTIONS_GHC -Wno-deprecations #-}
 
 module GHC.Data.Bag (
         Bag, -- abstract type


=====================================
libraries/Cabal
=====================================
@@ -1 +1 @@
-Subproject commit e71f6f263aa4d7ce7a145eb5ac417f2f580f2288
+Subproject commit 280a7a71e495da8f25ae33dbc6e743526b9106f9


=====================================
libraries/base/Control/Monad/Zip.hs
=====================================
@@ -20,6 +20,7 @@ module Control.Monad.Zip where
 
 import Control.Monad (liftM, liftM2)
 import Data.Functor.Identity
+import qualified Data.Functor
 import Data.Monoid
 import Data.Ord ( Down(..) )
 import Data.Proxy
@@ -65,7 +66,7 @@ instance MonadZip [] where
 instance MonadZip NE.NonEmpty where
   mzip     = NE.zip
   mzipWith = NE.zipWith
-  munzip   = NE.unzip
+  munzip   = Data.Functor.unzip
 
 -- | @since 4.8.0.0
 instance MonadZip Identity where


=====================================
libraries/base/Data/List/NonEmpty.hs
=====================================
@@ -472,6 +472,7 @@ zipWith f ~(x :| xs) ~(y :| ys) = f x y :| List.zipWith f xs ys
 -- | The 'unzip' function is the inverse of the 'zip' function.
 unzip :: Functor f => f (a,b) -> (f a, f b)
 unzip xs = (fst <$> xs, snd <$> xs)
+{-# DEPRECATED unzip "This function will be made monomorphic in base-4.22, consider switching to Data.Functor.unzip" #-}
 
 -- | The 'nub' function removes duplicate elements from a list. In
 -- particular, it keeps only the first occurrence of each element.


=====================================
libraries/base/changelog.md
=====================================
@@ -33,6 +33,7 @@
   * Implement `GHC.IORef.atomicSwapIORef` via a new dedicated primop `atomicSwapMutVar#` ([CLC proposal #139](https://github.com/haskell/core-libraries-committee/issues/139))
   * Change codebuffers to use an unboxed implementation, while providing a compatibility layer using pattern synonyms. ([CLC proposal #134](https://github.com/haskell/core-libraries-committee/issues/134))
   * Add nominal role annotations to SNat/SSymbol/SChar ([CLC proposal #170](https://github.com/haskell/core-libraries-committee/issues/170))
+  * Deprecate `Data.List.NonEmpty.unzip` ([CLC proposal #86](https://github.com/haskell/core-libraries-committee/issues/86))
 
 ## 4.18.0.0 *March 2023*
   * Shipped with GHC 9.6.1


=====================================
libraries/hpc
=====================================
@@ -1 +1 @@
-Subproject commit efd3826085953f618a1626b6c701c0314ba8b9bc
+Subproject commit bb5c55d697b0d0e6b8cce5ff5037273241de3239


=====================================
libraries/process
=====================================
@@ -1 +1 @@
-Subproject commit 6092a13f6bf2ef76105683c7f9e278c0dcadceec
+Subproject commit e60ab049b92238b0111654589f17b6ee68249f01


=====================================
libraries/stm
=====================================
@@ -1 +1 @@
-Subproject commit 86172e75bd4f5c400b3a6f0cd3945bdb7c03bcdd
+Subproject commit cfb7e775c5f6df281b7052b7b4e4a51dafda10d2


=====================================
utils/haddock
=====================================
@@ -1 +1 @@
-Subproject commit 495c0655dcb9a9482054c5e48c0106f57f5ddb06
+Subproject commit 03ba53ca764f56a13d12607c110f923f129e809a


=====================================
utils/hsc2hs
=====================================
@@ -1 +1 @@
-Subproject commit f70b360b295298e4da10afe02ebf022b21342008
+Subproject commit 1ba092932f86c1fda15091d355ba7975b8554437



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d80325d2c2ea8908342577068286df7d741907e2

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d80325d2c2ea8908342577068286df7d741907e2
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230624/429d0a89/attachment-0001.html>


More information about the ghc-commits mailing list