Forked IORef reader function seems to stall main thread
Asked Answered
C

2

5

I was doing some experiments with concurrency and memory visibility and ran into this strange behavior (see comments inline):

module Main
    where

import Data.IORef
import Control.Concurrent
import System.CPUTime

import System.IO

main = do
    hSetBuffering stdout NoBuffering

    r <- newIORef False
    putStrLn "forking..."  -- PRINTED
    forkIO $ f r
    threadDelay 1000000

    putStrLn "writeIORef"  -- NEVER PRINTED
    writeIORef r True

    threadDelay maxBound

f :: IORef Bool -> IO ()
f r = readIORef r >>= \b-> if b then print "NEVER PRINTED" else f r

I was expecting perhaps the writeIORef not to be visible to the child thread, but not for the main thread to simply (apparently) stall.

Compiled on ghc 7.8.3

 cabal exec ghc -- --make -fforce-recomp -O2 -threaded visibility.hs  

and run with

./visibility +RTS -N

What's happening here?

EDIT: So my machine has two real cores and two hyperthreading cores, so with +RTS -N GHC sees 4 capabilities. Per Gabriel Gonzalez's answer I tried out the following to see if maybe the scheduler was putting both threads on the same physical processor:

module Main
    where

import Data.IORef
import Control.Concurrent    
import GHC.Conc(threadCapability,myThreadId,forkOn)

main = do    
    r <- newIORef False
    putStrLn "going..."

    (cap,_) <- threadCapability =<< myThreadId
    forkOn (cap+1) $ f r                    -- TRIED cap+1, +2, +3....
    threadDelay 1000000

    putStrLn "writeIORef"                   -- BUT THIS STILL NEVER RUNS
    writeIORef r True

    threadDelay maxBound

f :: IORef Bool -> IO ()
f r = readIORef r >>= \b-> if b then print "A" else f r
Cumae answered 31/8, 2014 at 23:16 Comment(0)
C
0

It looks like this is probably an ancient ghc bug #367.

Cumae answered 2/9, 2014 at 3:2 Comment(0)
B
3

ghc only suspends threads at well-defined safe points, which are only when memory is allocated. I believe your forked thread never allocates memory, so it never relinquishes control to other threads. Therefore, your main thread never progresses once the compiler schedules the forked thread (sometime in the middle of your threadDelay).

You can learn more about safe points here in the section on "Lightweight Threads and Parallelism".

Edit: As Thomas mentioned, you can use Control.Concurrent.yield to explicitly relinquish control when you encounter situations like these.

Blandish answered 1/9, 2014 at 2:57 Comment(4)
Exactly. One solution is to use yield to break up blocks with no allocations or other such points. So for the busy wait in the question we would have ... else yield >> f r. Obviously busy loops are generally a bad idea in the first place. One alternative is to use MVar and takeMVar for signaling instead.Amberambergris
Sorry, maybe I'm being dense... why should I need the forked thread to yield control back to the main thread in order for putStrLn "writeIORef" to run? I'm running with +RTS -N, compiled with -threaded; shouldn't the two threads run... concurrently?Cumae
@Cumae Try inserting yield in your forked thread's loopBlandish
Yes, I would guess that would work. Adding a putStrLn in the loop fixed the behavior when I tried that, so it certainly appears related to the tight loop without allocations. But I don't understand why the forked thread should ever need to be suspended for the main thread to proceedCumae
C
0

It looks like this is probably an ancient ghc bug #367.

Cumae answered 2/9, 2014 at 3:2 Comment(0)

© 2022 - 2024 — McMap. All rights reserved.