Bugs item #1370370, was opened at 2005-11-30 21:04
Message generated for change (Comment added) made by kgrapone
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=1370370&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: GHCi
Group: 6.4.1
Status: Open
Resolution: None
Priority: 5
Submitted By: Nobody/Anonymous (nobody)
Assigned to: Nobody/Anonymous (nobody)
Summary: panic! 'impossible' happened, thread blocked indefinitely

Initial Comment:
GHCi, version 6.4.1, crashed with the following error: 
 
ghc-6.4.1: panic! (the `impossible' happened, GHC 
version 6.4.1): 
        thread blocked indefinitely 
 
Please report it as a compiler bug to 
[email protected], 
or http://sourceforge.net/projects/ghc/. 
 
I was calling a test function which was forking a 
Thread which was blocking in an 'atomically' waiting 
on a TChan. 
If I ran the test function a second time, while the 
Thread from the first run is presumably still hanging 
around, I would receive the above error/crash. 
 
If I reloaded the source in GHCi after running the 
test function a single time GHCi would give an error 
message (but not crash): 
 
*** Exception: thread blocked indefinitely 
 
Most of the time after the error message there would 
be no modules loaded.  I could load again, and repeat 
the fun. 
_Very_ occasionaly the modules would remain loaded and 
I could repeat the cycle without having to reload the 
modules. 
 
Since fixing my test function so the forked Thread 
dies at the desired time (ie now it won't be hanging 
around blocked on the TChan) I haven't observed the 
failure. 
 
My email: [EMAIL PROTECTED] 

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

Comment By: kgrapone (kgrapone)
Date: 2005-12-05 22:21

Message:
Logged In: YES 
user_id=1397718

Following is a minimal(ish) test case.  It behaves a little 
differently from the original, seems to be some timing 
issues involved.   
Running "runTest badLoop" multiple times will eventually 
kill GHCi.  Interleaving with "runTest goodLoop" will 
sometimes get you the other effects I mentioned above. 
 
--BEGIN CODE-- 
module Test where 
 
import Control.Concurrent.STM 
import Control.Concurrent 
import Control.Exception 
import Prelude hiding (catch) 
 
 
runTest loop = do 
    (tc1, tc2, tmv) <- atomically (do 
        tmv <- newEmptyTMVar 
        tc1 <- newTChan 
        tc2 <- newTChan 
        return (tc1, tc2, tmv) 
        ) 
    myTId <- myThreadId 
    forkIO (forked loop (tc1, tc2, tmv, myTId)) 
    atomically (writeTChan tc1 "blah") 
    atomically (writeTChan tc1 "blah2") 
    return "done" 
 
 
forked loop args@(tc1, tc2, tmv, hisTId) = catch ((loop 
args) >>= setTMV . Just) hndlr `finally` setTMV Nothing 
        where 
            setTMV x = atomically (tryPutTMVar tmv x >> 
return ()) 
            hndlr (AsyncException ThreadKilled) = return () 
            hndlr e                             = throwTo 
hisTId e 
 
goodLoop args@(tc1, tc2, tmv, hisTId) = do 
    x <- atomically (readTChan tc1) 
    x' <- return $ reverse x 
    atomically (writeTChan tc2 x') 
    if x == "blah2" 
        then return () 
        else goodLoop args 
 
badLoop args@(tc1, tc2, tmv, hisTId) = do 
    x <- atomically (readTChan tc1) 
    x' <- return $ reverse x 
    atomically (writeTChan tc2 x') 
    badLoop args 
--END CODE-- 

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

Comment By: Simon Marlow (simonmar)
Date: 2005-12-02 09:32

Message:
Logged In: YES 
user_id=48280

Please can you supply code to reproduce the bug.

This might be the same bug as #1274506.


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

Comment By: Nobody/Anonymous (nobody)
Date: 2005-11-30 21:10

Message:
Logged In: NO 

Oh, yeah: Running a 32bit Linux 2.6 kernel 

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

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

Reply via email to