summaryrefslogtreecommitdiff
path: root/libraries/base/Control/Concurrent
diff options
context:
space:
mode:
Diffstat (limited to 'libraries/base/Control/Concurrent')
-rw-r--r--libraries/base/Control/Concurrent/Chan.hs42
-rw-r--r--libraries/base/Control/Concurrent/MVar.hs12
-rw-r--r--libraries/base/Control/Concurrent/QSem.hs2
-rw-r--r--libraries/base/Control/Concurrent/QSemN.hs2
4 files changed, 14 insertions, 44 deletions
diff --git a/libraries/base/Control/Concurrent/Chan.hs b/libraries/base/Control/Concurrent/Chan.hs
index ebbec7ea99..874e48a1a1 100644
--- a/libraries/base/Control/Concurrent/Chan.hs
+++ b/libraries/base/Control/Concurrent/Chan.hs
@@ -1,13 +1,12 @@
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE CPP #-}
-{-# LANGUAGE StandaloneDeriving #-}
-----------------------------------------------------------------------------
-- |
-- Module : Control.Concurrent.Chan
-- Copyright : (c) The University of Glasgow 2001
-- License : BSD-style (see the file libraries/base/LICENSE)
---
+--
-- Maintainer : libraries@haskell.org
-- Stability : experimental
-- Portability : non-portable (concurrency)
@@ -22,7 +21,7 @@
-----------------------------------------------------------------------------
module Control.Concurrent.Chan
- (
+ (
-- * The 'Chan' type
Chan, -- abstract
@@ -31,8 +30,6 @@ module Control.Concurrent.Chan
writeChan,
readChan,
dupChan,
- unGetChan,
- isEmptyChan,
-- * Stream interface
getChanContents,
@@ -53,7 +50,7 @@ import Control.Exception (mask_)
data Chan a
= Chan _UPK_(MVar (Stream a))
_UPK_(MVar (Stream a)) -- Invariant: the Stream a is always an empty MVar
- deriving (Eq)
+ deriving Eq -- ^ @since 4.4.0.0
type Stream a = MVar (ChItem a)
@@ -105,25 +102,16 @@ writeChan (Chan _ writeVar) val = do
-- guarantees of 'MVar's (e.g. threads blocked in this operation are woken up in
-- FIFO order).
--
--- Throws 'BlockedIndefinitelyOnMVar' when the channel is empty and no other
--- thread holds a reference to the channel.
+-- Throws 'Control.Exception.BlockedIndefinitelyOnMVar' when the channel is
+-- empty and no other thread holds a reference to the channel.
readChan :: Chan a -> IO a
readChan (Chan readVar _) = do
- modifyMVarMasked readVar $ \read_end -> do -- Note [modifyMVarMasked]
+ modifyMVar readVar $ \read_end -> do
(ChItem val new_read_end) <- readMVar read_end
-- Use readMVar here, not takeMVar,
-- else dupChan doesn't work
return (new_read_end, val)
--- Note [modifyMVarMasked]
--- This prevents a theoretical deadlock if an asynchronous exception
--- happens during the readMVar while the MVar is empty. In that case
--- the read_end MVar will be left empty, and subsequent readers will
--- deadlock. Using modifyMVarMasked prevents this. The deadlock can
--- be reproduced, but only by expanding readMVar and inserting an
--- artificial yield between its takeMVar and putMVar operations.
-
-
-- |Duplicate a 'Chan': the duplicate channel begins empty, but data written to
-- either channel from then on will be available from both. Hence this creates
-- a kind of broadcast channel, where data written by anyone is seen by
@@ -137,24 +125,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/Control/Concurrent/MVar.hs b/libraries/base/Control/Concurrent/MVar.hs
index 393fca89e2..df28fe8406 100644
--- a/libraries/base/Control/Concurrent/MVar.hs
+++ b/libraries/base/Control/Concurrent/MVar.hs
@@ -33,16 +33,16 @@
--
-- === Applicability
--
--- 'MVar's offer more flexibility than 'IORef's, but less flexibility
--- than 'STM'. They are appropriate for building synchronization
+-- 'MVar's offer more flexibility than 'Data.IORef.IORef's, but less flexibility
+-- than 'GHC.Conc.STM'. They are appropriate for building synchronization
-- primitives and performing simple interthread communication; however
-- they are very simple and susceptible to race conditions, deadlocks or
-- uncaught exceptions. Do not use them if you need perform larger
--- atomic operations such as reading from multiple variables: use 'STM'
+-- atomic operations such as reading from multiple variables: use 'GHC.Conc.STM'
-- instead.
--
--- In particular, the "bigger" functions in this module ('readMVar',
--- 'swapMVar', 'withMVar', 'modifyMVar_' and 'modifyMVar') are simply
+-- In particular, the "bigger" functions in this module ('swapMVar',
+-- 'withMVar', 'modifyMVar_' and 'modifyMVar') are simply
-- the composition of a 'takeMVar' followed by a 'putMVar' with
-- exception safety.
-- These only have atomicity guarantees if all other threads
@@ -70,7 +70,7 @@
--
-- 'MVar' operations are always observed to take place in the order
-- they are written in the program, regardless of the memory model of
--- the underlying machine. This is in contrast to 'IORef' operations
+-- the underlying machine. This is in contrast to 'Data.IORef.IORef' operations
-- which may appear out-of-order to another thread in some cases.
--
-- === Example
diff --git a/libraries/base/Control/Concurrent/QSem.hs b/libraries/base/Control/Concurrent/QSem.hs
index 51624e4777..ea396255a4 100644
--- a/libraries/base/Control/Concurrent/QSem.hs
+++ b/libraries/base/Control/Concurrent/QSem.hs
@@ -29,7 +29,7 @@ import Control.Concurrent.MVar ( MVar, newEmptyMVar, takeMVar, tryTakeMVar
import Control.Exception
import Data.Maybe
--- | 'QSem' is a quantity semaphore in which the resource is aqcuired
+-- | 'QSem' is a quantity semaphore in which the resource is acquired
-- and released in units of one. It provides guaranteed FIFO ordering
-- for satisfying blocked `waitQSem` calls.
--
diff --git a/libraries/base/Control/Concurrent/QSemN.hs b/libraries/base/Control/Concurrent/QSemN.hs
index 7686d3f327..b8c9274057 100644
--- a/libraries/base/Control/Concurrent/QSemN.hs
+++ b/libraries/base/Control/Concurrent/QSemN.hs
@@ -31,7 +31,7 @@ import Control.Concurrent.MVar ( MVar, newEmptyMVar, takeMVar, tryTakeMVar
import Control.Exception
import Data.Maybe
--- | 'QSemN' is a quantity semaphore in which the resource is aqcuired
+-- | 'QSemN' is a quantity semaphore in which the resource is acquired
-- and released in units of one. It provides guaranteed FIFO ordering
-- for satisfying blocked `waitQSemN` calls.
--