Re: [Haskell-cafe] Proper exception handling

2008-02-10 Thread Ryan Ingram
If you want to guarantee safety, you can use an MVar () to force
serialization; put something in the MVar inside of catchDyn, and take
from it immediately after starting the thread & after throwing each
exception.

  -- ryan


On Feb 10, 2008 11:49 AM, Thomas DuBuisson <[EMAIL PROTECTED]> wrote:
> 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
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proper exception handling

2008-02-10 Thread Stefan O'Rear
On Sun, Feb 10, 2008 at 02:49:39PM -0500, Thomas DuBuisson wrote:
> 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

Asynchronous exceptions are blocked in handlers, so there is no window -
infact all exceptions after the first won't be delivered at all.
However, you could be unlucky enough to throw the first error before the
first catchDyn, so more synchronisation might be needed.

Stefan

> 
> > 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)


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Proper exception handling

2008-02-10 Thread Thomas DuBuisson
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