[Git][ghc/ghc][wip/data-list-nonempty-unzip] Data.List.NonEmpty.unzip: use WARNING with category insted of DEPRECATED
Bodigrim (@Bodigrim)
gitlab at gitlab.haskell.org
Thu Feb 29 23:09:50 UTC 2024
Bodigrim pushed to branch wip/data-list-nonempty-unzip at Glasgow Haskell Compiler / GHC
Commits:
36be5531 by Andrew Lelechenko at 2024-03-01T00:09:42+01:00
Data.List.NonEmpty.unzip: use WARNING with category insted of DEPRECATED
CLC proposal: https://github.com/haskell/core-libraries-committee/issues/258
- - - - -
4 changed files:
- compiler/GHC/Data/Bag.hs
- compiler/GHC/HsToCore/Match/Constructor.hs
- libraries/base/changelog.md
- libraries/base/src/Data/List/NonEmpty.hs
Changes:
=====================================
compiler/GHC/Data/Bag.hs
=====================================
@@ -7,7 +7,7 @@ Bag: an unordered collection with duplicates
-}
{-# LANGUAGE ScopedTypeVariables, DeriveTraversable, TypeFamilies #-}
-{-# OPTIONS_GHC -Wno-deprecations #-}
+{-# OPTIONS_GHC -Wno-x-data-list-nonempty-unzip #-}
module GHC.Data.Bag (
Bag, -- abstract type
=====================================
compiler/GHC/HsToCore/Match/Constructor.hs
=====================================
@@ -2,7 +2,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
-{-# OPTIONS_GHC -Wno-deprecations #-}
+{-# OPTIONS_GHC -Wno-x-data-list-nonempty-unzip #-}
{-
(c) The University of Glasgow 2006
=====================================
libraries/base/changelog.md
=====================================
@@ -17,7 +17,10 @@
* Always use `safe` call to `read` for regular files and block devices on unix if the RTS is multi-threaded, regardless of `O_NONBLOCK`.
([CLC proposal #166](https://github.com/haskell/core-libraries-committee/issues/166))
* Export List from Data.List ([CLC proposal #182](https://github.com/haskell/core-libraries-committee/issues/182)).
- * Deprecate `Data.List.NonEmpty.unzip` ([CLC proposal #86](https://github.com/haskell/core-libraries-committee/issues/86))
+ * Add `{-# WARNING in "x-data-list-nonempty-unzip" #-}` to `Data.List.NonEmpty.unzip`.
+ Use `{-# OPTIONS_GHC -Wno-x-data-list-nonempty-unzip #-}` to disable it.
+ ([CLC proposal #86](https://github.com/haskell/core-libraries-committee/issues/86)
+ and [CLC proposal #258](https://github.com/haskell/core-libraries-committee/issues/258))
* Add `System.Mem.performMajorGC` ([CLC proposal #230](https://github.com/haskell/core-libraries-committee/issues/230))
* Fix exponent overflow/underflow bugs in the `Read` instances for `Float` and `Double` ([CLC proposal #192](https://github.com/haskell/core-libraries-committee/issues/192))
* Implement `many` and `some` methods of `instance Alternative (Compose f g)` explicitly. ([CLC proposal #181](https://github.com/haskell/core-libraries-committee/issues/181))
=====================================
libraries/base/src/Data/List/NonEmpty.hs
=====================================
@@ -534,7 +534,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 GHC.Internal.Data.Functor.unzip" #-}
+{-# WARNING in "x-data-list-nonempty-unzip" 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.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/36be5531633db021eb3844b56ca41b6f13009819
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/36be5531633db021eb3844b56ca41b6f13009819
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/20240229/38af82f6/attachment-0001.html>
More information about the ghc-commits
mailing list