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

Heka Treep zena.treep at gmail.com
Mon Jan 23 19:56:47 CET 2012


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?



More information about the Glasgow-haskell-users mailing list