Simon may have gone home for the weekend, so just
to let you know that he's checked in a fix for this
problem in the current CVS sources.

--sigbjorn

----- Original Message -----
From: "Peter White" <[EMAIL PROTECTED]>
To: "Simon Marlow" <[EMAIL PROTECTED]>;
<[EMAIL PROTECTED]>
Sent: Friday, February 15, 2002 09:05
Subject: RE: PAP_Entry: CATCH_FRAME


> I have managed to create a small program that reproduces the error the way
I
> get to it. The output it produces is:
>
> Handler got: 1
> Exception: 1st
> Handler got: 2
> Error1: fatal error: PAP_entry: CATCH_FRAME
>
> The program was in a file "Error1.hs", that is why the fatal error begins
> with "Error1". The program follows, I hope this is helpful.
>
> module Main where
>
> import Concurrent
> import qualified Exception as E
>
> trapHandler :: MVar Int -> IO ()
> trapHandler inVar =
>   (do { trapMsg <- takeMVar inVar
>       ; putStrLn ("Handler got: " ++ show trapMsg)
>       ; trapHandler inVar
>       }
>   )
>   `E.catch`
>   (trapExc inVar)
>
> trapExc :: MVar Int -> E.Exception -> IO ()
> trapExc inVar e =
>   do { putStrLn ("Exception: " ++ show e)
>      ; trapHandler inVar
>      }
>
> main :: IO ()
> main =
>   do { inVar <- newEmptyMVar
>      ; tid <- forkIO (trapHandler inVar)
>      ; yield
>      ; putMVar inVar 1
>      ; threadDelay 1000
>      ; throwTo tid (E.UserError "1st")
>      ; threadDelay 1000
>      ; putMVar inVar 2
>      ; threadDelay 1000
>      ; throwTo tid (E.UserError "2nd")
>      ; threadDelay 1000
>      ; putStrLn "All done"
>      }
>
>
>
> -----Original Message-----
> From: Simon Marlow [mailto:[EMAIL PROTECTED]]
> Sent: Friday, February 15, 2002 2:55 AM
> To: Peter White; [EMAIL PROTECTED]
> Subject: RE: PAP_Entry: CATCH_FRAME
>
>
> > What does it mean when you get the fatal error "PAP_Entry:
> > CATCH_FRAME". I
> > am using ghc version 5.03.20020204. I looked in the ghc
> > source code and the
> > comment next to this error message says that it cannot happen.
>
> Well, you must be imagining it then :-)
>
> Seriously, I've seen this error too.  Try 'interact (unlines.lines)' in
GHCi
> and press ^C to see it (this works in 5.02.2 too).  I've been meaning to
> look at it, hopefully I'll get around to it today.
>
> Cheers,
> Simon
>
>
> _______________________________________________
> Glasgow-haskell-bugs mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to