Duncan Coutts pushed to branch wip/io-manager-deadlock-detection at Glasgow Haskell Compiler / GHC

Commits:

3 changed files:

Changes:

  • testsuite/tests/rts/T26408.hs
    1
    +import Control.Concurrent
    
    2
    +import Control.Concurrent.STM
    
    3
    +import Control.Exception
    
    4
    +import Control.Monad
    
    5
    +
    
    6
    +-- | Test to make sure that deadlock detection works even when there are other
    
    7
    +-- unrelated threads that are blocked on I\/O or timeouts.
    
    8
    +-- Historically however this did affect things in the non-threaded RTS which
    
    9
    +-- would only do deadlock detection if there were no runnable threads /and/
    
    10
    +-- no pending I\/O. See <https://gitlab.haskell.org/ghc/ghc/-/issues/26408>
    
    11
    +main :: IO ()
    
    12
    +main = do
    
    13
    +  
    
    14
    +  -- Set up two threads that are deadlocked on each other
    
    15
    +  aDone <- newTVarIO False
    
    16
    +  bDone <- newTVarIO False
    
    17
    +  let blockingThread theirDone ourDone =
    
    18
    +        atomically $ do
    
    19
    +          done <- readTVar theirDone
    
    20
    +          guard done
    
    21
    +          writeTVar ourDone True
    
    22
    +  _ <- forkIO (blockingThread bDone aDone)
    
    23
    +  _ <- forkIO (blockingThread aDone bDone)
    
    24
    +
    
    25
    +  -- Set up another thread that is blocked on a long timeout.
    
    26
    +  --
    
    27
    +  -- We use a timeout rather than I/O as it's more portable, whereas I/O waits
    
    28
    +  -- are different between posix and windows I/O managers.
    
    29
    +  --
    
    30
    +  -- One gotcha is that when the timeout completes then the deadlock will be
    
    31
    +  -- detected again (since the bug is about I/O or timeouts masking deadlock
    
    32
    +  -- detection). So for a reliable test the timeout used here must be longer
    
    33
    +  -- than the test framework's own timeout. So we use maxBound, and we adjust
    
    34
    +  -- the test framework's timeout to be short (see run_timeout_multiplier).
    
    35
    +  _ <- forkIO (threadDelay maxBound)
    
    36
    +
    
    37
    +  -- Wait on the deadlocked threads to terminate. We now expect that the threads
    
    38
    +  -- that are deadlocked are detected as such and an exception is raised.
    
    39
    +  -- Note that if this fails, the test itself will effectively deadlock and
    
    40
    +  -- will rely on the test framework's timeout.
    
    41
    +  atomically $ do
    
    42
    +    status <- mapM readTVar [aDone, bDone]
    
    43
    +    guard (or status)

  • testsuite/tests/rts/T26408.stderr
    1
    +T26408: Uncaught exception ghc-internal:GHC.Internal.IO.Exception.BlockedIndefinitelyOnSTM:
    
    2
    +
    
    3
    +thread blocked indefinitely in an STM transaction

  • testsuite/tests/rts/all.T
    ... ... @@ -647,3 +647,5 @@ test('T22859',
    647 647
           when(arch('wasm32'), skip),
    
    648 648
           omit_ways(llvm_ways)],
    
    649 649
          compile_and_run, ['-with-rtsopts -A8K'])
    
    650
    +
    
    651
    +test('T26408', [exit_code(1), run_timeout_multiplier(0.1)], compile_and_run, [''])