Bugs item #1235728, was opened at 2005-07-10 22:41
Message generated for change (Comment added) made by simonmar
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=1235728&group_id=8032

Please note that this message will contain a full copy of the comment thread,
including the initial issue submission, for this request,
not just the latest update.
Category: Runtime System
Group: None
Status: Open
Resolution: None
>Priority: 2
Submitted By: Remi Turk (remit)
Assigned to: Nobody/Anonymous (nobody)
Summary: unsafeInterleaveIO + Ctrl-C/killThread related segfault

Initial Comment:
[copy-pasting my original mail
(http://www.haskell.org/pipermail/glasgow-haskell-bugs/2005-June/005235.html)]

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

----------------------------------------------------------------------

>Comment By: Simon Marlow (simonmar)
Date: 2005-07-11 12:38

Message:
Logged In: YES 
user_id=48280

Interesting bug.  I've installed a workaround for the crash.
 It's tickled by having a thread blocked in takeMVar (or a
similar blocking operation), inside Exception.block (which
print does), inside unsafePerformIO (or unsafeInterleaveIO),
and sending the thread an exception.  When the
unsafePerformIO thunk is restarted again by another thread,
the Exception.block isn't re-instated properly.  This is a
bug, but highly unlikely to cause any real problems in
practice.  Besides I suspect we'll redesign this part of the
system in the light of STM at some point.


----------------------------------------------------------------------

Comment By: Remi Turk (remit)
Date: 2005-07-10 22:49

Message:
Logged In: YES 
user_id=26642

A few new datapoints. Using -threaded, 6.2.1 compiled
executables still survive, while 6.4 dies.

% ghc-6.4 -no-recomp foo.hs                 
% ./a.out                                   
% ghc-6.2.1 -no-recomp foo.hs 
% ./a.out                    

% ghc-6.4 -no-recomp -threaded foo.hs
% ./a.out                            
zsh: segmentation fault  ./a.out
% ghc-6.2.1 -no-recomp -threaded foo.hs
% ./a.out                              
% 

Also, the first forkIO can be changed into forkOS without
changing (crashing)behaviour, the second cannot.

Oh, and I won't be upset if this one won't be fixed for 6.4.1 ;)

----------------------------------------------------------------------

You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=1235728&group_id=8032
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to