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

Heka Treep zena.treep at gmail.com
Mon Jan 23 22:20:51 CET 2012


2012/1/23, Edward Z. Yang <ezyang at mit.edu>:
> Excerpts from Heka Treep's message of Mon Jan 23 15:11:51 -0500 2012:
>> --------------------------------------------------------------------------------
>> import Control.Monad.STM
>> import Control.Concurrent
>> import Control.Concurrent.STM.TChan
>>
>> spawn f = do
>>   mbox <- newTChanIO
>>   forkIO $ f mbox
>>   return mbox
>>
>> (!) = writeTChan
>>
>> actor mbox = do
>>   empty <- atomically $ isEmptyTChan mbox
>>   if empty
>>     then actor mbox
>>     else do
>>       val <- atomically $ readTChan mbox
>
> Uh, don't you want to combine isEmptyChan and readTChan into
> one single atomic action?
>
>>       putStrLn val
>>       actor mbox
>>
>> test = do
>>   mbox <- spawn actor
>>   atomically $ mbox ! "1"
>>   atomically $ mbox ! "2"
>>   atomically $ mbox ! "3"
>>
>> -- > test
>> -- 1
>> -- 2
>> -- 3
>> --------------------------------------------------------------------------------
>>
>> But there are several problems:
>>
>> * The @actor@ function is busy checking the channel all the time.
>
> GHC's runtime system is clever. It will block appropriately.
>
>> * Caller and callee need to perform synchronizations (for the @Chan@)
>> or atomically transactions (for the @TChan@).
>
> The synchronization for Chan is very cheap, and you would have needed
> to synchronize anyway in Erlang (Erlang message queues are not lock free!)
>
> Cheers,
> Edward
>

Ok, I have tried to write the test:

--------------------------------------------------------------------------------
import Data.Maybe

import Control.Monad
import Control.Monad.STM
import Control.Concurrent
import Control.Concurrent.STM.TChan

actor :: TChan String -> IO ()
actor mbox = forever $ do
  putStrLn "call to actor..."
  msg <- atomically $ do
    isEmpty <- isEmptyTChan mbox
    if isEmpty then return Nothing else readTChan mbox >>= return . Just
  when (isJust msg) $ putStrLn $ fromJust msg

main :: IO ()
main = do
  -- spawn
  mbox <- newTChanIO
  tid <- forkIO $ actor mbox
  -- communicate
  atomically $ mbox `writeTChan` "1"
  threadDelay (10 ^ 6)
  atomically $ mbox `writeTChan` "2"
  threadDelay (10 ^ 6)
  atomically $ mbox `writeTChan` "3"
  threadDelay (10 ^ 6)
  killThread tid
--------------------------------------------------------------------------------
--------------------------------------------------------------------------------
$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 7.4.0.20111219
$ ghc -O2 -rtsopts -threaded --make test.hs
[1 of 1] Compiling Main             ( test.hs, test.o )
Linking test ...
$ ./test +RTS -N8 -RTS > test.log
$ wc -l test.log
220804 test.log
--------------------------------------------------------------------------------

looks like it performs thousands of calls to the `actor' function.
When I think about an asynchronous messaging approach, then forward
just a call, or at least three. Maybe I'm missing something, or just
doing it wrong?



More information about the Glasgow-haskell-users mailing list