#7104: Add tryWriteTBQueue to Control.Concurrent.STM.TBQueue
------------------------------+---------------------------------------------
 Reporter:  joeyadams         |          Owner:                   
     Type:  feature request   |         Status:  new              
 Priority:  normal            |      Component:  libraries (other)
  Version:  7.4.2             |       Keywords:  stm              
       Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple 
  Failure:  None/Unknown      |       Testcase:                   
Blockedby:                    |       Blocking:                   
  Related:                    |  
------------------------------+---------------------------------------------
 I'd like a "try" variant of writeTBQueue, so part of my application can
 react to the queue overflowing by returning a "queue is full" status.

 Attached is a series of patches, the last of which adds
 {{{writeTBQueue}}}.  The other patches fix a couple minor issues:

  * Force capacity computations, so a long series of {{{readTBQueue}}}
 calls won't lead to a stack overflow.

  * Guard against negative queue size given to {{{newTBQueue}}} and
 {{{newTBQueueIO}}}.

 ----

 While we're at it, I have a couple general questions about retry and
 orElse:

  * Is {{{atomically (retry `orElse` return ())}}} guaranteed to not be
 interruptible by an asynchronous exception when exceptions are masked?

  * Is there a performance benefit to avoiding retry when possible?  I'd
 imagine not, since this should only involve throwing away a few
 transaction log entries.

 If {{{atomically (retry `orElse` return ())}}} is guaranteed to not be
 interruptible, and if there is no performance benefit to avoiding retry,
 then it seems there's little point in having any of the try* functions.

 In the documentation for Control.Exception, it lists operations that are
 guaranteed to not be interruptible.  One of them is:

  * STM transactions that do not use retry

 This is a useful property, and is expected of any "try" function.
 However, {{{tryReadTBQueue}}} "uses" {{{retry}}}.

 I did a quick test, and it looks like {{{atomically (retry `orElse` return
 ())}}} is not interruptible:

 {{{
 import Control.Concurrent
 import Control.Concurrent.STM
 import Control.Exception
 import Control.Monad

 repeatSTM :: STM () -> IO ()
 repeatSTM = replicateM_ 50000000 . atomically

 main :: IO ()
 main = do
     finished <- newEmptyMVar

     tid <- mask_ $ forkOS $ do
         repeatSTM (retry `orElse` return ())
         putMVar finished ()

     threadDelay 100000
     killThread tid  -- should wait for the thread to run to completion

     putStrLn "Let's see if the thread finished..."
     takeMVar finished
     putStrLn "Yes, it did."
 }}}

 Is this guaranteed in general?  That is, if the transaction does retry
 calls, but the transaction as a whole does not retry due to orElse, is the
 transaction guaranteed to not be interruptible?

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7104>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to