Re: Is it true that an exception is always terminates the thread?

From: Heka Treep
Subject: Re: Is it true that an exception is always terminates the thread? To: "Edward Z. Yang" Cc: glasgow-haskell-users Message-ID: Content-Type: text/plain; charset=ISO-8859-1 2012/1/23, Edward Z. Yang
: Excerpts from Heka Treep's message of Mon Jan 23 13:56:47 -0500 2012:
adding the message queue (with Chan, MVar or STM) for each process will not help in this kind of imitation.
Why not? Instead of returning a thread ID, send the write end of a Chan which the thread is waiting on. You can send messages (normal or errors) using it.
Edward
Yes, one can write this:
(others have commented on your actor implementation already) I'm not certain I understand your comment about synchronization; the STM implementation handles all of that. Unless you mean that you'd rather not write the "atomically"'s when writing to the TChan. But you can define:
! :: TChan a -> a -> IO () chan ! msg = atomically $ writeTChan chan msg
This allows you to write:
test = do mbox <- spawn actor mbox ! "1" mbox ! "2" mbox ! "3"
which seems to be exactly what you want. For the record, it's probably possible to do this with async exceptions, but I would not want to maintain it. For one, async exceptions are how GHC implements a lot of thread management stuff (e.g. the ThreadKilled exception). You would need to be careful that your code doesn't interfere with that. Another concern is the thread mask state, which needs to be handled carefully. For example, if you perform an "interruptable operation" while processing the message (e.g. blocking IO), another message could be received at that point, which I believe would abort processing of the first message. If you use "uninterruptableMask", then as I read the docs you can't block *at all* without making the thread unkillable. Doing this with async exceptions would be tricky to get right. STM is the best approach. John L.

This is related but somewhat tangential -- *Why isn't there a tryReadChan?* It looks like it would be implementable with the current Chan representation in terms of tryTakeMVar. Especially since isEmptyChan is deprecated this would be nice to have. Because of missing tryReadChan there is no non-blocking way to read data resident in a Chan (i.e. flush it -- in this case because I was in an exception handler and wanted to flush out what was left in memory in a Chan). I found myself rolling my own in the form of the following data structure to get around this: -- Chan's don't quite do the trick. Here's something simpler. It -- keeps a buffer of elemnts and an MVar to signal "end of stream". -- This it separates blocking behavior from data access. data Buffer a = Buf (MVar ()) (IORef [a]) newBuffer :: IO (Buffer a) newBuffer = do mv <- newEmptyMVar ref <- newIORef [] return (Buf mv ref) writeBuffer :: Buffer a -> a -> IO () writeBuffer (Buf mv ref) x = do b <- isEmptyMVar mv if b then atomicModifyIORef ref (\ ls -> (x:ls,())) else error "writeBuffer: cannot write to closed Buffer" -- | Signal completion. closeBuffer :: Buffer a -> IO () closeBuffer (Buf mv _) = putMVar mv () peekBuffer :: Buffer a -> IO [a] peekBuffer (Buf _ ref) = liftM reverse $ readIORef ref -- Returns a lazy list, just like getChanContents: getBufferContents :: Buffer a -> IO [a] getBufferContents buf@(Buf mv ref) = do chan <- newChan let loop = do grabbed <- atomicModifyIORef ref (\ ls -> ([], reverse ls)) mapM_ (writeChan chan . Just) grabbed mayb <- tryTakeMVar mv -- Check if we're done. case mayb of Nothing -> threadDelay 10000 >> loop Just () -> writeChan chan Nothing forkIO loop ls <- getChanContents chan return (map fromJust $ takeWhile isJust ls)

Excerpts from Ryan Newton's message of Tue Jan 24 10:25:37 -0500 2012:
This is related but somewhat tangential --
*Why isn't there a tryReadChan?* It looks like it would be implementable with the current Chan representation in terms of tryTakeMVar. Especially since isEmptyChan is deprecated this would be nice to have.
Because of missing tryReadChan there is no non-blocking way to read data resident in a Chan (i.e. flush it -- in this case because I was in an exception handler and wanted to flush out what was left in memory in a Chan). I found myself rolling my own in the form of the following data structure to get around this:
Aw, that's a shame, especially since there does exist a tryReadMVar, so it seems like it ought to be possible (though I haven't checked closely.) Edward

On 24/01/2012 15:59, Edward Z. Yang wrote:
Excerpts from Ryan Newton's message of Tue Jan 24 10:25:37 -0500 2012:
This is related but somewhat tangential --
*Why isn't there a tryReadChan?* It looks like it would be implementable with the current Chan representation in terms of tryTakeMVar. Especially since isEmptyChan is deprecated this would be nice to have.
Because of missing tryReadChan there is no non-blocking way to read data resident in a Chan (i.e. flush it -- in this case because I was in an exception handler and wanted to flush out what was left in memory in a Chan). I found myself rolling my own in the form of the following data structure to get around this:
Aw, that's a shame, especially since there does exist a tryReadMVar, so it seems like it ought to be possible (though I haven't checked closely.)
http://hackage.haskell.org/trac/ghc/ticket/4535 Looks like we didn't get around to adding it. Cheers, Simon

On 1/24/12 10:25 AM, Ryan Newton wrote:
This is related but somewhat tangential --
*Why isn't there a tryReadChan?* It looks like it would be implementable with the current Chan representation in terms of tryTakeMVar. Especially since isEmptyChan is deprecated this would be nice to have.
(A) See stm-chans: http://hackage.haskell.org/packages/archive/stm-chans/1.2.0.1/doc/html/Contr... (B) The reason that module is called Compat is because (optimized versions of) those functions have already been pushed to HEAD. We're just waiting for them to make it out to the public. http://hackage.haskell.org/trac/ghc/ticket/5104 http://www.haskell.org/pipermail/cvs-libraries/2011-April/012914.html -- Live well, ~wren

On 1/26/12 10:01 PM, wren ng thornton wrote:
On 1/24/12 10:25 AM, Ryan Newton wrote:
This is related but somewhat tangential --
*Why isn't there a tryReadChan?* It looks like it would be implementable with the current Chan representation in terms of tryTakeMVar. Especially since isEmptyChan is deprecated this would be nice to have.
(A) See stm-chans:
http://hackage.haskell.org/packages/archive/stm-chans/1.2.0.1/doc/html/Contr...
Er, whoops. I thought you said tryReadTChan. -- Live well, ~wren
participants (5)
-
Edward Z. Yang
-
John Lato
-
Ryan Newton
-
Simon Marlow
-
wren ng thornton