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

I try to mimic Erlang like this: -------------------------------------------------------------------------------- {-# LANGUAGE FlexibleInstances #-} import Prelude hiding ( catch ) import Control.Monad import Control.Concurrent import Control.Exception spawn = forkIO wait = forever $ threadDelay (maxBound :: Int) receive = catch wait (!) = throwTo instance Exception String test = do let actor = receive putStrLn p <- spawn actor p ! "1" p ! "2" p ! "3" -- > test -- 1 -- <interactive>: "2" -------------------------------------------------------------------------------- but raise an exception terminates the thread. This is quite natural, of course. What I need is a messages -- something that works just like exceptions but don't stop a thread's computations. I mean, the scheduler knows about asynchronous exceptions, adding the message queue (with Chan, MVar or STM) for each process will not help in this kind of imitation. It's possible to solve this problem with the exceptions or with something? Or the message communication should be implemented as a new feature in the RTS?

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

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: -------------------------------------------------------------------------------- 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 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. * Caller and callee need to perform synchronizations (for the @Chan@) or atomically transactions (for the @TChan@). With exception-like messages one can write: -------------------------------------------------------------------------------- actor = receive $ \message -> case message of -- ... PM over message constructors ... -------------------------------------------------------------------------------- and then: -------------------------------------------------------------------------------- child <- spawn actor child ! MessageCon1 child ! MessageCon2 -- ... -------------------------------------------------------------------------------- where @receive@ is similar to @catch@ and (!) is similar to @throwTo@. Scheduler will be the one who will wake the actor and give him the message (well, like the @catch@ function passes an exception to a thread). No need for busy waiting on the channel or it synchronization. I can say that Erlang's concurrency works like this. As well as GHC exceptions, but they stop threads. I'm just interested in whether it is their fundamental limitation?

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

2012/1/23, Edward Z. Yang
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?

Excerpts from Heka Treep's message of Mon Jan 23 16:20:51 -0500 2012:
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
There are several things wrong with this: - You're only synchronizing over one variable: use an Chan, not a TChan (if you make that change, btw, it will automatically start working.) - You don't want the transaction to succeed in all cases; you only want the transaction to succeed if you manage to get something from the TChan. What you've done is convert the interface from blocking to non-blocking, but in a busy-loop. - You don't even need to run isEmptyTChan. Just do a readTChan. It will block if there is nothing in the chan (technically, it will ask the STM transaction to retry, but STM is clever enough not to try running again unless any of the touched STM variables changes.) Edward

On 1/23/12 3:19 PM, Edward Z. Yang wrote:
Excerpts from Heka Treep's message of Mon Jan 23 15:11:51 -0500 2012:
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?
Why are you writing a busy loop? STM is designed such that if you have a single transaction that tries to read from an empty TChan then that thread will be put to sleep and awakened only once there's some activity on that TChan. Using STM is not the same as lock-based code; you shouldn't treat it like it is. -- Live well, ~wren

Quoting Heka Treep
actor mbox = do empty <- atomically $ isEmptyTChan mbox if empty then actor mbox else do val <- atomically $ readTChan mbox putStrLn val actor mbox
This looks a bit silly. Why not just this? actor mbox = forever $ atomically (readTChan mbox) >>= putStrLn ~d
participants (4)
-
Edward Z. Yang
-
Heka Treep
-
wagnerdm@seas.upenn.edu
-
wren ng thornton