> Oh I see; the problem is the GHC RTS is attempting to shut down,
> and in order to do this it needs to grab all of the capabilities.

Thanks, again. However, the program doesn't seem to be blocking when
the main thread finishes, but rather in the "takeMVar mv1" line. I'm
copying the modified version with a print call that never manages to
print in the console for me.

btw, I'm using ghc 7.6.3.

Best,
Facundo

-----

import Control.Concurrent
import Control.Monad
import System.Environment

main :: IO ()
main = do
  y <- getArgs
  mv0 <- newEmptyMVar
  mv1 <- newEmptyMVar
  forkIO $ do
    takeMVar mv0
    putMVar mv1 ()
    loop (y == ["yield"])
  putMVar mv0 ()
  takeMVar mv1
     >>= print

loop :: Bool -> IO ()
loop cooperative = go
  where
    go = when cooperative yield >> go

On Sun, Oct 20, 2013 at 2:37 AM, Edward Z. Yang <ezy...@mit.edu> wrote:
> Oh I see; the problem is the GHC RTS is attempting to shut down,
> and in order to do this it needs to grab all of the capabilities. However,
> one of them is in an uninterruptible loop, so the program hangs (e.g.
> if you change the program as follows:
>
>     main :: IO ()
>     main = do
>       forkIO $ do
>         loop (y == ["yield"])
>       threadDelay 1000
> )
>
> With a sufficiently recent version of GHC, if you compile with 
> -fno-omit-yields,
> that should fix the problem.
>
> Edward
>
> Excerpts from Facundo Domínguez's message of Sat Oct 19 16:05:15 -0700 2013:
>> Thanks. I just tried that. Unfortunately, it doesn't seem to help.
>>
>> Facundo
>>
>> On Sat, Oct 19, 2013 at 8:47 PM, Edward Z. Yang <ezy...@mit.edu> wrote:
>> > Hello Facundo,
>> >
>> > The reason is that you have compiled the program to be multithreaded, but 
>> > it
>> > is not running with multiple cores. Compile also with -rtsopts and then
>> > pass +RTS -N2 to the program.
>> >
>> > Excerpts from Facundo Domínguez's message of Sat Oct 19 15:19:22 -0700 
>> > 2013:
>> >> Hello,
>> >>    Below is a program that seems to block indefinitely with ghc in a
>> >> multicore machine. This program has a loop that does not produce
>> >> allocations, and I understand that this may grab one of the cores. The
>> >> question is, why can't the other cores take the blocked thread?
>> >>
>> >> The program was compiled with:
>> >>
>> >> $ ghc --make -O -threaded test.hs
>> >>
>> >> and it is run with:
>> >>
>> >> $ ./test
>> >>
>> >> Program text follows.
>> >>
>> >> Thanks,
>> >> Facundo
>> >>
>> >> --------
>> >>
>> >> import Control.Concurrent
>> >> import Control.Monad
>> >> import System.Environment
>> >>
>> >> main :: IO ()
>> >> main = do
>> >>   y <- getArgs
>> >>   mv0 <- newEmptyMVar
>> >>   mv1 <- newEmptyMVar
>> >>   forkIO $ do
>> >>     takeMVar mv0
>> >>     putMVar mv1 ()
>> >>     loop (y == ["yield"])
>> >>   putMVar mv0 ()
>> >>   takeMVar mv1
>> >>
>> >> loop :: Bool -> IO ()
>> >> loop cooperative = go
>> >>   where
>> >>     go = when cooperative yield >> go
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to