11{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
22{-# LANGUAGE CPP, DeriveDataTypeable #-}
3+ {-# LANGUAGE BangPatterns #-}
34
45#if __GLASGOW_HASKELL__ >= 701
56{-# LANGUAGE Trustworthy #-}
1718--
1819-- A 'TQueue' is like a 'TChan', with two important differences:
1920--
20- -- * it has faster throughput than both 'TChan' and 'Chan' (although
21- -- the costs are amortised, so the cost of individual operations
22- -- can vary a lot).
21+ -- * it has faster throughput than both 'TChan' and 'Chan'
2322--
2423-- * it does /not/ provide equivalents of the 'dupTChan' and
2524-- 'cloneTChan' operations.
2625--
27- -- The implementation is based on the traditional purely-functional
28- -- queue representation that uses two lists to obtain amortised /O(1)/
29- -- enqueue and dequeue operations .
26+ -- The implementation is based on Okasaki's scheduled banker's queues,
27+ -- but it uses * two* schedules so there's only contention between the
28+ -- reader and writer when the queue needs to be rotated .
3029--
3130-- @since 2.4
3231-----------------------------------------------------------------------------
@@ -44,63 +43,107 @@ module Control.Concurrent.STM.TQueue (
4443 writeTQueue ,
4544 unGetTQueue ,
4645 isEmptyTQueue ,
47- ) where
46+ ) where
4847
4948import GHC.Conc
5049import Control.Monad (unless )
5150import Data.Typeable (Typeable )
5251
52+ data End a =
53+ End [a ] -- list
54+ [a ] -- schedule
55+
5356-- | 'TQueue' is an abstract type representing an unbounded FIFO channel.
5457--
5558-- @since 2.4
56- data TQueue a = TQueue {- # UNPACK #-} !(TVar [ a ] )
57- {- # UNPACK #-} !(TVar [ a ] )
59+ data TQueue a = TQueue {- # UNPACK #-} !(TVar ( End a ) )
60+ {- # UNPACK #-} !(TVar ( End a ) )
5861 deriving Typeable
62+ {-
63+ Invariant:
64+
65+ Given front list, rear list, front schedule, and rear schedule called
66+ front, rear, fsched, and rsched, respectively,
67+
68+ 2 * (|front| - |rear|) = |fsched| + |rsched|
69+
70+ Note that because lengths cannot be negative, this implies that
71+
72+ |front| >= |rear|
73+
74+ We rotate the queue when either schedule is empty. This preserves
75+ the invariant and ensures that the spine of the front list is
76+ fully realized when a rotation occurs.
77+ -}
5978
6079instance Eq (TQueue a ) where
6180 TQueue a _ == TQueue b _ = a == b
6281
63- -- | Build and returns a new instance of 'TQueue'
82+ -- | Build and returns a new instance of 'TQueue'
6483newTQueue :: STM (TQueue a )
6584newTQueue = do
66- read <- newTVar []
67- write <- newTVar []
85+ read <- newTVar ( End [] [] )
86+ write <- newTVar ( End [] [] )
6887 return (TQueue read write)
6988
70- -- | @IO@ version of 'newTQueue'. This is useful for creating top-level
89+ -- | @IO@ version of 'newTQueue'. This is useful for creating top-level
7190-- 'TQueue's using 'System.IO.Unsafe.unsafePerformIO', because using
7291-- 'atomically' inside 'System.IO.Unsafe.unsafePerformIO' isn't
7392-- possible.
7493newTQueueIO :: IO (TQueue a )
7594newTQueueIO = do
76- read <- newTVarIO []
77- write <- newTVarIO []
95+ read <- newTVarIO ( End [] [] )
96+ write <- newTVarIO ( End [] [] )
7897 return (TQueue read write)
7998
80- -- | Write a value to a 'TQueue'.
99+ -- rotate front end = front ++ reverse rear, but the reverse is performed
100+ -- incrementally as the append proceeds.
101+ --
102+ -- Precondition: |front| + 1 >= |rear|. This ensures that when the front
103+ -- list is empty, the rear list has at most one element, so we don't need
104+ -- to reverse it.
105+ rotate :: [a ] -> [a ] -> [a ]
106+ rotate = go []
107+ where
108+ go acc [] rear = rear ++ acc
109+ go acc (x: xs) (r: rs)
110+ = x : go (r: acc) xs rs
111+ go acc xs [] = xs ++ acc
112+
113+ -- | Write a value to a 'TQueue'.
81114writeTQueue :: TQueue a -> a -> STM ()
82- writeTQueue (TQueue _read write) a = do
83- listend <- readTVar write
84- writeTVar write (a: listend)
85-
86- -- | Read the next value from the 'TQueue'.
115+ writeTQueue (TQueue read write) a = do
116+ End listend rsched <- readTVar write
117+ let listend' = a : listend
118+ case rsched of
119+ -- Reduce |front|-|rear| by 1; reduce |fsched|+|rsched| by 2
120+ _: _: rsched' -> writeTVar write (End listend' rsched')
121+
122+ -- Rotate the queue; the invariant holds trivially.
123+ _ -> do
124+ End listfront _fsched <- readTVar read
125+ let ! front' = rotate listfront listend'
126+ writeTVar read (End front' front')
127+ writeTVar write (End [] front')
128+
129+ -- | Read the next value from the 'TQueue'.
87130readTQueue :: TQueue a -> STM a
88131readTQueue (TQueue read write) = do
89- xs <- readTVar read
90- case xs of
91- (x : xs') -> do
92- writeTVar read xs'
93- return x
94- [] -> do
95- ys <- readTVar write
96- case ys of
97- [] -> retry
98- _ -> do
99- let (z : zs) = reverse ys -- NB. lazy: we want the transaction to be
100- -- short, otherwise it will conflict
101- writeTVar write []
102- writeTVar read zs
103- return z
132+ End listfront fsched <- readTVar read
133+ case listfront of
134+ [] -> retry
135+ x : front' ->
136+ case fsched of
137+ -- Reduce |front|-|rear| by 1; reduce |fsched|+|rsched| by 2
138+ _ : _ : fsched' -> writeTVar read ( End front' fsched') >> return x
139+
140+ -- Rotate the queue; the invariant holds trivially.
141+ _ -> do
142+ End listend _rsched <- readTVar write
143+ let ! front'' = rotate front' listend
144+ writeTVar read ( End front'' front'')
145+ writeTVar write ( End [] front'')
146+ return x
104147
105148-- | A version of 'readTQueue' which does not retry. Instead it
106149-- returns @Nothing@ if no value is available.
@@ -113,44 +156,38 @@ tryReadTQueue c = fmap Just (readTQueue c) `orElse` return Nothing
113156-- @since 2.4.5
114157flushTQueue :: TQueue a -> STM [a ]
115158flushTQueue (TQueue read write) = do
116- xs <- readTVar read
117- ys <- readTVar write
118- unless (null xs ) $ writeTVar read []
119- unless (null ys ) $ writeTVar write []
120- return (xs ++ reverse ys )
159+ End front fsched <- readTVar read
160+ End rear rsched <- readTVar write
161+ unless (null front && null fsched ) $ writeTVar read ( End [] [] )
162+ unless (null rear && null rsched ) $ writeTVar write ( End [] [] )
163+ return (rotate front rear )
121164
122165-- | Get the next value from the @TQueue@ without removing it,
123166-- retrying if the channel is empty.
124167peekTQueue :: TQueue a -> STM a
125- peekTQueue c = do
126- x <- readTQueue c
127- unGetTQueue c x
128- return x
168+ peekTQueue (TQueue read _write) = do
169+ End front _fsched <- readTVar read
170+ case front of
171+ x: _ -> return x
172+ [] -> retry
129173
130174-- | A version of 'peekTQueue' which does not retry. Instead it
131175-- returns @Nothing@ if no value is available.
132176tryPeekTQueue :: TQueue a -> STM (Maybe a )
133- tryPeekTQueue c = do
134- m <- tryReadTQueue c
135- case m of
136- Nothing -> return Nothing
137- Just x -> do
138- unGetTQueue c x
139- return m
140-
141- -- | Put a data item back onto a channel, where it will be the next item read.
177+ tryPeekTQueue (TQueue read _write) = do
178+ End front _fsched <- readTVar read
179+ case front of
180+ x: _ -> return (Just x)
181+ [] -> return Nothing
182+
183+ -- | Put a data item back onto a channel, where it will be the next item read.
142184unGetTQueue :: TQueue a -> a -> STM ()
143185unGetTQueue (TQueue read _write) a = do
144- xs <- readTVar read
145- writeTVar read (a : xs )
186+ End front fsched <- readTVar read
187+ writeTVar read (End (a : front) (a : a : fsched) )
146188
147- -- | Returns 'True' if the supplied 'TQueue' is empty.
189+ -- | Returns 'True' if the supplied 'TQueue' is empty.
148190isEmptyTQueue :: TQueue a -> STM Bool
149- isEmptyTQueue (TQueue read write) = do
150- xs <- readTVar read
151- case xs of
152- (_: _) -> return False
153- [] -> do ys <- readTVar write
154- case ys of
155- [] -> return True
156- _ -> return False
191+ isEmptyTQueue (TQueue read _write) = do
192+ End front _fsched <- readTVar read
193+ return $! null front
0 commit comments