Skip to content
Snippets Groups Projects
Commit 8116bafe authored by Robert's avatar Robert Committed by Mergify
Browse files

test CmdRun/Terminate: add some debug logging

We've seen some instability in the test, compare

  https://github.com/haskell/cabal/issues/8416

This adds timestamped output to make it easier to
see what goes wrong in case the test fails again.
parent d709e0df
No related branches found
No related tags found
No related merge requests found
......@@ -2,13 +2,21 @@ import Control.Concurrent (killThread, threadDelay, myThreadId)
import Control.Exception (finally)
import qualified System.Posix.Signals as Signal
import System.Exit (exitFailure)
import qualified Data.Time.Clock as Time
import qualified Data.Time.Format as Time
main = do
-- timestamped logging to aid with #8416
let log msg = do
ts <- Time.getCurrentTime
let tsfmt = Time.formatTime Time.defaultTimeLocale "%H:%M:%S.%q" ts
putStrLn $ tsfmt <> " [exe ] " <> msg
mainThreadId <- myThreadId
Signal.installHandler Signal.sigTERM (Signal.Catch $ killThread mainThreadId) Nothing
(do
putStrLn "about to sleep"
log "about to write file"
writeFile "exe.run" "up and running"
log "about to sleep"
threadDelay 10000000 -- 10s
putStrLn "done sleeping")
`finally` putStrLn "exiting"
log "done sleeping")
`finally` log "exiting"
......@@ -5,5 +5,5 @@ cabal-version: >= 1.10
executable exe
default-language: Haskell2010
build-depends: base, process, unix
build-depends: base, process, time, unix
main-is: Main.hs
......@@ -4,6 +4,8 @@ import Control.Concurrent (threadDelay)
import System.Directory (removeFile)
import Control.Exception (catch, throwIO)
import System.IO.Error (isDoesNotExistError)
import qualified Data.Time.Clock as Time
import qualified Data.Time.Format as Time
{-
This test verifies that 'cabal run' terminates its
......@@ -18,16 +20,28 @@ main :: IO ()
main = cabalTest $ do
skipIfWindows -- test project relies on Posix
-- timestamped logging to aid with #8416
let logIO msg = do
ts <- Time.getCurrentTime
let tsfmt = Time.formatTime Time.defaultTimeLocale "%H:%M:%S.%q" ts
putStrLn $ tsfmt <> " [cabal.test] " <> msg
log = liftIO . logIO
dir <- fmap testCurrentDir getTestEnv
let runFile = dir </> "exe.run"
liftIO $ removeFile runFile `catchNoExist` return ()
log "about to v2-build"
cabal_raw_action ["v2-build", "exe"] (\_ -> return ())
log "about to v2-run"
r <- fails $ cabal_raw_action ["v2-run", "exe"] $ \cabalHandle -> do
-- wait for "cabal run" to have started "exe"
logIO "about to wait for file"
waitFile total runFile
-- then kill "cabal run"
logIO "about to terminate cabal"
Process.terminateProcess cabalHandle
log "v2-run done"
-- "exe" should exit, and should have been interrupted before
-- finishing its sleep
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment