[Git][ghc/ghc][wip/clc-86] Deprecate Data.List.NonEmpty.unzip
Melanie Brown (@mixphix)
gitlab at gitlab.haskell.org
Sun Jun 25 00:55:11 UTC 2023
Melanie Brown pushed to branch wip/clc-86 at Glasgow Haskell Compiler / GHC
Commits:
89b03b54 by Melanie Phoenix at 2023-06-24T20:54:48-04:00
Deprecate Data.List.NonEmpty.unzip
- - - - -
4 changed files:
- compiler/GHC/Data/Bag.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
=====================================
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
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/89b03b548bb1d5866eff4f621c686831777f04c5
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/89b03b548bb1d5866eff4f621c686831777f04c5
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/455f175f/attachment-0001.html>
More information about the ghc-commits
mailing list