[commit: ghc] master: base: Remove deprecated Chan combinators (361af62)
git at git.haskell.org
git at git.haskell.org
Tue Oct 3 21:56:35 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/361af6280d7025ac3e24d79c209b465db6f231f8/ghc
>---------------------------------------------------------------
commit 361af6280d7025ac3e24d79c209b465db6f231f8
Author: Ben Gamari <bgamari.foss at gmail.com>
Date: Tue Oct 3 15:09:12 2017 -0400
base: Remove deprecated Chan combinators
Removes isEmptyChan and unGetChan, which have been deprecated for a very
long time. See #13561.
Test Plan: Validate
Reviewers: austin, hvr
Subscribers: rwbarton, thomie
GHC Trac Issues: #13561
Differential Revision: https://phabricator.haskell.org/D4060
>---------------------------------------------------------------
361af6280d7025ac3e24d79c209b465db6f231f8
libraries/base/Control/Concurrent/Chan.hs | 21 ---------------------
libraries/base/changelog.md | 3 +++
2 files changed, 3 insertions(+), 21 deletions(-)
diff --git a/libraries/base/Control/Concurrent/Chan.hs b/libraries/base/Control/Concurrent/Chan.hs
index ebbec7e..9bfd40b 100644
--- a/libraries/base/Control/Concurrent/Chan.hs
+++ b/libraries/base/Control/Concurrent/Chan.hs
@@ -1,6 +1,5 @@
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE CPP #-}
-{-# LANGUAGE StandaloneDeriving #-}
-----------------------------------------------------------------------------
-- |
@@ -31,8 +30,6 @@ module Control.Concurrent.Chan
writeChan,
readChan,
dupChan,
- unGetChan,
- isEmptyChan,
-- * Stream interface
getChanContents,
@@ -137,24 +134,6 @@ dupChan (Chan _ writeVar) = do
newReadVar <- newMVar hole
return (Chan newReadVar writeVar)
--- |Put a data item back onto a channel, where it will be the next item read.
-unGetChan :: Chan a -> a -> IO ()
-unGetChan (Chan readVar _) val = do
- new_read_end <- newEmptyMVar
- modifyMVar_ readVar $ \read_end -> do
- putMVar new_read_end (ChItem val read_end)
- return new_read_end
-{-# DEPRECATED unGetChan "if you need this operation, use Control.Concurrent.STM.TChan instead. See <http://ghc.haskell.org/trac/ghc/ticket/4154> for details" #-} -- deprecated in 7.0
-
--- |Returns 'True' if the supplied 'Chan' is empty.
-isEmptyChan :: Chan a -> IO Bool
-isEmptyChan (Chan readVar writeVar) = do
- withMVar readVar $ \r -> do
- w <- readMVar writeVar
- let eq = r == w
- eq `seq` return eq
-{-# DEPRECATED isEmptyChan "if you need this operation, use Control.Concurrent.STM.TChan instead. See <http://ghc.haskell.org/trac/ghc/ticket/4154> for details" #-} -- deprecated in 7.0
-
-- Operators for interfacing with functional streams.
-- |Return a lazy list representing the contents of the supplied
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index 7778ceb..2f42e22 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -56,6 +56,9 @@
* Add `installSEHHandlers` to `MiscFlags` in `GHC.RTS.Flags` to determine if
exception handling is enabled.
+ * The deprecated functions `isEmptyChan` and `unGetChan` in
+ `Control.Concurrent.Chan` have been removed (#13561).
+
* Add `generateCrashDumpFile` to `MiscFlags` in `GHC.RTS.Flags` to determine
if a core dump will be generated on crashes.
More information about the ghc-commits
mailing list