[Git][ghc/ghc][master] Deprecate Data.List.NonEmpty.unzip

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Sat Jul 8 09:06:35 UTC 2023



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


Commits:
ec1c32e2 by Melanie Phoenix at 2023-07-08T05:06:14-04:00
Deprecate Data.List.NonEmpty.unzip

- - - - -


6 changed files:

- compiler/GHC/Data/Bag.hs
- compiler/GHC/HsToCore/Match/Constructor.hs
- hadrian/src/Rules/Dependencies.hs
- libraries/base/Control/Monad/Zip.hs
- libraries/base/Data/List/NonEmpty.hs
- libraries/base/changelog.md


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


=====================================
compiler/GHC/HsToCore/Match/Constructor.hs
=====================================
@@ -2,6 +2,7 @@
 {-# LANGUAGE TypeFamilies #-}
 
 {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
+{-# OPTIONS_GHC -Wno-deprecations #-}
 
 {-
 (c) The University of Glasgow 2006


=====================================
hadrian/src/Rules/Dependencies.hs
=====================================
@@ -1,3 +1,5 @@
+{-# OPTIONS_GHC -Wno-deprecations #-}
+
 module Rules.Dependencies (buildPackageDependencies) where
 
 import Data.Bifunctor


=====================================
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
=====================================
@@ -34,6 +34,7 @@
   * 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))
   * Make `Semigroup`'s `stimes` specializable. ([CLC proposal #8](https://github.com/haskell/core-libraries-committee/issues/8))
+  * 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



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ec1c32e23f47add28ceaca33aba02c277b02496b
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/20230708/d1019a4c/attachment-0001.html>


More information about the ghc-commits mailing list