Cafe,
Fact 1: ghc{,i} does not crash when executing this code.
Fact 2: I do not want this to crash.
Question: Is there some theoretical window between the 'catchDyn' exception 
handling and the recursive call to 'catchThatDamnError' that could result in an 
unhandled exception? (of type 'DynError', of coarse)

I suppose I am looking for an answer to this question from a language 
standpoint as well as a compiler pov.

As an aside: I see at least one way to be certain of the safty by wrapping the 
call to forkIO in 'catchDyn', reforking if an exception is caught, and passing 
the new ThreadId to throwConstantly via shared mutable state - I'd like to 
avoid all this if my current example is safe.

Thomas

> import Control.Exception (catchDyn, throwDynTo)
> import Control.Concurrent (forkIO, threadDelay)
> import Control.Monad (forever)
> import Data.Dynamic
>
> main = do
>     tid <- forkIO catchThatDamnError
>     forever $ throwConstantly tid
>
> catchThatDamnError = catchDyn start (\DynError -> catchThatDamnError)
>
> start = do
>     threadDelay 5000
>     start
>
> throwConstantly tid = do
>     throwDynTo tid DynError 
>
> data DynError = DynError deriving (Eq, Ord, Show, Typeable)

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to