RTS's (old?) invariant regarding OS blocking

Sergei Trofimovich slyich at gmail.com
Thu Mar 3 09:52:07 UTC 2016


On Wed, 2 Mar 2016 16:38:56 +0200
Dan Aloni <dan at kernelim.com> wrote:

> Hi,
> 
> While trying to gain insights into the RTS, I've noticed the following in
> the Wiki page [1] on the topic of the scheduler:
> 
>     Invariant: a task that holds a capability is not blocked in the operating system.
> 
>     This makes some parts of the system simpler - for example, we can use spin locks that spin indefinitely, because we can ensure that the spin lock is only held by a currently executing CPU, and will therefore be released in a finite (and short) amount of time.
> 
> Does it still apply to modern day GHC, or was it addressed by [2]?

It still does apply. Foreign calls are by default 'safe' and executed
after Capability is released to a separate OS thread.
Capability release is needed as foreign calls can reenter haskell RTS.

You can break that invariant and observe the negative effect.
For example 'unsafe' foreign call to a blocking function stops
all haskell threads happened to be queued on that Capability.

Illustration of adverse effect. [1] runs 2 threads:
- main thread issues 'safe' and 'unsafe' FFI sleeps
- auxiliary thread prints a message on screen every second.

'unsafe_sleep' blocks unrelated haskell thread for 5 seconds
while 'safe_sleep' doesn't.

We disable SIGVTALARM to not interfere with sleep() system call
and use threaded RTS as non-threaded RTS uses SIGVTALARM
for thread switching as well.

$ ghc --make a.hs -o ./a -rtsopts -threaded && ./a +RTS -V0 -N1
[1 of 1] Compiling Main             ( a.hs, a.o )
Linking ./a ...

"start unsafe sleep"
"thread: enter"
"done unsafe sleep"
"entering safe sleep"
"*** thread: tick"
"*** thread: tick"
"*** thread: tick"
"*** thread: tick"
"done safe sleep"
"*** thread: tick"
"*** thread: tick"
"*** thread: tick"
"*** thread: tick"
"*** thread: tick"
"*** thread: tick"
"thread: exit"

-- [1]: example program a.hs:
import Control.Concurrent
import Control.Monad
import Foreign.C

foreign import ccall safe "unistd.h sleep"
    safe_sleep :: CInt -> IO CInt
foreign import ccall unsafe "unistd.h sleep"
    unsafe_sleep :: CInt -> IO CInt

-- sleep for n * 100ms
s :: Int -> IO ()
s slices = threadDelay $ slices * 10^6

main = do
    t1_lock <- newEmptyMVar
    t1 <- forkIO $ do
        print "thread: enter"
        replicateM_ 10 $ do
            s 1
            print "*** thread: tick"
        print "thread: exit"
        putMVar t1_lock ()

    yield -- switch to the ticker

    print "start unsafe sleep"
    unsafe_sleep 5
    print "done unsafe sleep"

    print "entering safe sleep"
    safe_sleep 5
    print "done safe sleep"

    takeMVar t1_lock

-- 

  Sergei
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 181 bytes
Desc: not available
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20160303/1d314b47/attachment.sig>


More information about the ghc-devs mailing list