On Mon, Oct 09, 2000 at 05:40:29AM -0700, Simon Marlow wrote:
> Ok.  Is it possible to cut down the example to maybe 2 concurrent threads,
> so we could try to fix the problem here?  There aren't any obvious bugs in
> the signal handling code (at least, not obvious to me :).

I think I found the most simple version to reproduce this bug.

> module Main where
> import Posix
> import IO
> main = do
>   _ <- installHandler sigUSR1 (Catch (return ())) Nothing -- will fail
>   -- _ <- installHandler sigUSR1 Ignore Nothing -- will work
>   loop
> loop = do
>   putStr "> "
>   msg <- getLine
>   print msg
>   loop

Sample run:

tests@monster [10:23:09]> ./sigTest 
> ^Z
[2]+  Stopped                 ./sigTest
tests@monster [10:23:11]> kill -USR1 %2

[2]+  Stopped                 ./sigTest
tests@monster [10:23:17]> fg
./sigTest
test
"test"
> ^Z
[2]+  Stopped                 ./sigTest
tests@monster [10:23:21]> kill -USR1 %2

[2]+  Stopped                 ./sigTest
tests@monster [10:23:23]> fg
./sigTest

Fail: failed
Action: hGetChar
Reason: (error code: 0)

Or is this some intended Posix-feature?
-- 
Volker Stolz * [EMAIL PROTECTED] * PGP + S/MIME

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

Reply via email to