Repository : ssh://darcs.haskell.org//srv/darcs/packages/stm

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/ade6b929cbd6280ebafb7b6452fa88031b21debd

>---------------------------------------------------------------

commit ade6b929cbd6280ebafb7b6452fa88031b21debd
Author: Simon Marlow <[email protected]>
Date:   Wed Jul 4 11:33:11 2012 +0100

    re-export TQueue from Control.Concurrent.STM

>---------------------------------------------------------------

 Control/Concurrent/STM.hs         |    2 ++
 Control/Concurrent/STM/TBQueue.hs |    5 +++--
 2 files changed, 5 insertions(+), 2 deletions(-)

diff --git a/Control/Concurrent/STM.hs b/Control/Concurrent/STM.hs
index 9632c2c..29780e3 100644
--- a/Control/Concurrent/STM.hs
+++ b/Control/Concurrent/STM.hs
@@ -31,6 +31,7 @@ module Control.Concurrent.STM (
        module Control.Concurrent.STM.TMVar,
         module Control.Concurrent.STM.TChan,
         module Control.Concurrent.STM.TQueue,
+        module Control.Concurrent.STM.TBQueue,
 #endif
        module Control.Concurrent.STM.TArray
   ) where
@@ -43,3 +44,4 @@ import Control.Concurrent.STM.TChan
 #endif
 import Control.Concurrent.STM.TArray
 import Control.Concurrent.STM.TQueue
+import Control.Concurrent.STM.TBQueue
diff --git a/Control/Concurrent/STM/TBQueue.hs 
b/Control/Concurrent/STM/TBQueue.hs
index 01aa742..82b46b3 100644
--- a/Control/Concurrent/STM/TBQueue.hs
+++ b/Control/Concurrent/STM/TBQueue.hs
@@ -40,8 +40,8 @@ module Control.Concurrent.STM.TBQueue (
         isEmptyTBQueue,
   ) where
 
-
-import Control.Concurrent.STM
+import Data.Typeable
+import GHC.Conc
 
 #define _UPK_(x) {-# UNPACK #-} !(x)
 
@@ -51,6 +51,7 @@ data TBQueue a
              _UPK_(TVar [a])  -- R:  elements waiting to be read
              _UPK_(TVar Int)  -- CW: write capacity
              _UPK_(TVar [a])  -- W:  elements written (head is most recent)
+  deriving Typeable
 
 instance Eq (TBQueue a) where
   TBQueue a _ _ _ == TBQueue b _ _ _ = a == b



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to