Bugs item #653694, was opened at 2002-12-14 13:04
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=653694&group_id=8032

Category: Runtime System
Group: None
Status: Open
Resolution: None
Priority: 5
Submitted By: Wolfgang Thaller (wthaller)
Assigned to: Nobody/Anonymous (nobody)
Summary: safe calls in the threaded RTS broken

Initial Comment:
When returning from a "safe" (non-threadsafe) call,
resumeThread uses grabCapability to grab the
capability. If another worker thread is executing
haskell code, the capability is not free, but
grabCapability succeeds anyway.
We cannot use grabReturnCapability either, because we
cannot rely on a worker thread being around to wake us.
The only solution I can think of right now is to do
away with the safe/threadsafe distinction and treat all
safe calls as threadsafe. (After all, if we don't spawn
a new worker thread in suspendThread, we will have to
spawn a new worker thread for a callback anyway [in
scheduleThread_], so we're not losing any performance).


The following code fails with various assertion
failures and segfaults. All of them are due to the fact
that the RTS accidentally runs two pieces of haskell
code at once.

This is with ghc-5.05 (CVS HEAD from 11th or 12th of
December) configured with --enable-threaded-rts.

-------- Main.hs

module Main where

import Control.Concurrent(forkIO)

foreign import ccall safe "foo" foo :: IO ()

foreign export ccall "bar" bar :: IO ()
bar = putStrLn "Hello, world."

fib 0 = 1
fib 1 = 1
fib n = fib (n-1) + fib (n-2)

doSomeWork n = do
        putStrLn ("fib " ++ show n ++ " = " ++ show (fib n))
        doSomeWork (n+1)

main = do
        forkIO (doSomeWork 0)
        foo
        putStrLn "foo finished"
        putStrLn ("main says: fib 30 = " ++ show (fib 30))

//////// foo.c

extern void bar();

void foo()
{
        bar();
}


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

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

Reply via email to