Good evening,

I just stumbled across a segfault caused when running the
following small program. (During an attempt to implement
single-assignment variables.)

> module Main where
> 
> import Control.Concurrent
> import System.IO.Unsafe (unsafeInterleaveIO)
> 
> main = do
>     v <- newEmptyMVar
>     a <- unsafeInterleaveIO (readMVar v)
>     t <- forkIO (print a)
>     threadDelay (1000*1000)
>     killThread t
>     forkIO (print a)
>     putMVar v ()

The crucial part about it seems to be the interruption of the
lazy IO. Typing Ctl-c while running the first "print a" by hand
from ghci instead of the forkIO+killThread doesn't change
behaviour:

 Prelude System.IO.Unsafe Control.Concurrent> v <- newEmptyMVar
 Prelude System.IO.Unsafe Control.Concurrent> a <-
 unsafeInterleaveIO (readMVar v)
 Prelude System.IO.Unsafe Control.Concurrent> print a
 Interrupted.
 Prelude System.IO.Unsafe Control.Concurrent> forkIO (print a)
 Prelude System.IO.Unsafe Control.Concurrent> putMVar v ()
 zsh: segmentation fault (core dumped)  ghci

Both 6.4 and 6.2.1 crash when running main from ghci.
When running it as a compiled executable everything is fine.

Although I'm pretty sure I've seen 6.2.1 crashing 
on it when run with -e main, I cannot reproduce it anymore. 6.4
certainly happily runs it with -e main. (A serious lack of sleep
the last week may play a role too.. :-/)

Whether the module is compiled before being loaded into ghci has
no effect.

Core-dumps etc can of course be sent if necessary.

Good night,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.

Attachment: pgp0yqAd3iNbi.pgp
Description: PGP signature

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

Reply via email to