diff options
| author | Tom Smeding <tom@tomsmeding.com> | 2025-11-03 22:43:40 +0100 |
|---|---|---|
| committer | Tom Smeding <tom@tomsmeding.com> | 2025-11-03 22:49:26 +0100 |
| commit | e95a6d1c4f5f979bee12ee8e7d34af8b108e6adb (patch) | |
| tree | 179e9558b24667f5bb5b1097871bf65909fa5759 /test-framework | |
| parent | 3d1b4b9c2aec604513f04aaae8534936432c8918 (diff) | |
test: Proper intermixing of GCC warnings with test output
Diffstat (limited to 'test-framework')
| -rw-r--r-- | test-framework/Test/Framework.hs | 77 |
1 files changed, 55 insertions, 22 deletions
diff --git a/test-framework/Test/Framework.hs b/test-framework/Test/Framework.hs index 80711b2..b7d0dc2 100644 --- a/test-framework/Test/Framework.hs +++ b/test-framework/Test/Framework.hs @@ -1,9 +1,12 @@ +{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE DerivingVia #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE ImplicitParams #-} {-# LANGUAGE ImportQualifiedPost #-} {-# LANGUAGE LambdaCase #-} +{-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} module Test.Framework ( @@ -11,12 +14,16 @@ module Test.Framework ( testGroup, groupSetCollapse, testProperty, - withResource, - withResource', runTests, defaultMain, Options(..), + -- * Resources + withResource, + withResource', + TestCtx, + outputWarningText, + -- * Compatibility TestName, ) where @@ -29,11 +36,13 @@ import Control.Monad (forM, when, forM_) import Control.Monad.IO.Class import Data.IORef import Data.List (isInfixOf, intercalate) -import Data.Maybe (isJust, mapMaybe, fromJust) +import Data.Maybe (mapMaybe, fromJust) +import Data.Monoid (All(..), Any(..), Sum(..)) import Data.PQueue.Prio.Min qualified as PQ import Data.String (fromString) import Data.Time.Clock import GHC.Conc (getNumProcessors) +import GHC.Generics (Generic, Generically(..)) import System.Console.ANSI qualified as ANSI import System.Console.Concurrent (outputConcurrent) import System.Console.Regions @@ -57,10 +66,16 @@ type TestName = String data TestTree = Group GroupOpts String [TestTree] - | forall a. Resource String (IO a) (a -> IO ()) (a -> TestTree) + | forall a. Resource String ((?testCtx :: TestCtx) => IO a) ((?testCtx :: TestCtx) => a -> IO ()) (a -> TestTree) -- ^ Name is not specified by user, but inherited from the tree below | HP String H.Property +data TestCtx = TestCtx + { tctxOutput :: String -> IO () } + +outputWarningText :: (?testCtx :: TestCtx) => String -> IO () +outputWarningText = tctxOutput ?testCtx + -- Not exported because a Resource is not supposed to have a name in the first place treeName :: TestTree -> String treeName (Group _ name _) = name @@ -82,13 +97,13 @@ groupSetCollapse (Group opts name trees) = Group opts { goCollapse = True } name groupSetCollapse _ = error "groupSetCollapse: not called on a Group" -- | The @a -> TestTree@ function must use the @a@ only inside properties: the --- functoin will be passed 'undefined' when exploring the test tree (without +-- function will be passed 'undefined' when exploring the test tree (without -- running properties). -withResource :: IO a -> (a -> IO ()) -> (a -> TestTree) -> TestTree +withResource :: ((?testCtx :: TestCtx) => IO a) -> ((?testCtx :: TestCtx) => a -> IO ()) -> (a -> TestTree) -> TestTree withResource make cleanup fun = Resource (treeName (fun undefined)) make cleanup fun -- | Same caveats as 'withResource'. -withResource' :: IO a -> (a -> TestTree) -> TestTree +withResource' :: ((?testCtx :: TestCtx) => IO a) -> (a -> TestTree) -> TestTree withResource' make fun = withResource make (\_ -> return ()) fun testProperty :: String -> H.Property -> TestTree @@ -226,7 +241,7 @@ runTests options = \tree' -> successVar <- newEmptyMVar runTreePar Nothing [] [] tree successVar readMVar successVar - else isJust <$> runTreeSeq 0 [] tree + else getAll . seqresAllSuccess <$> runTreeSeq 0 [] tree stats <- readIORef statsRef endtm <- getCurrentTime let ?istty = isterm in printStats (treeNumTests tree) stats (diffUTCTime endtm starttm) @@ -284,6 +299,9 @@ runTreePar topmparregion revidxlist revpath toptree@Resource{} topoutvar = runRe let pathitem = '[' : show depth ++ "](" ++ inhname ++ ")" path = intercalate "/" (reverse (pathitem : revpath)) idxlist = reverse revidxlist + let ?testCtx = TestCtx (\str -> + outputConcurrent (ansiYellow ++ "## Warning for " ++ path ++ ":" ++ ansiReset ++ + "\n" ++ str ++ "\n")) submitOrRunIn mparregion idxlist Nothing $ \makeRegion -> do setConsoleRegion makeRegion ('|' : path ++ " [R] making...") @@ -337,37 +355,51 @@ submitOrRunIn (Just reg) _idxlist outvar fun = do result <- fun reg forM_ outvar $ \mvar -> putMVar mvar result +data SeqRes = SeqRes + { seqresHaveWarnings :: Any + , seqresAllSuccess :: All + , seqresNumLines :: Sum Int } + deriving (Generic) + deriving (Semigroup, Monoid) via Generically SeqRes + -- | If all tests are successful, returns the number of output lines produced runTreeSeq :: (?options :: Options, ?stats :: IORef Stats, ?maxlen :: Int, ?istty :: Bool) - => Int -> [String] -> TestTree -> IO (Maybe Int) + => Int -> [String] -> TestTree -> IO SeqRes runTreeSeq indent revpath (Group opts name trees) = do putStrLn (replicate (2 * indent) ' ' ++ name) >> hFlush stdout starttm <- getCurrentTime - mlns <- fmap (fmap sum . sequence) . forM trees $ - runTreeSeq (indent + 1) (name : revpath) + res <- fmap mconcat . forM trees $ + runTreeSeq (indent + 1) (name : revpath) endtm <- getCurrentTime - case mlns of - Just lns | goCollapse opts, ?istty -> do + if not (getAny (seqresHaveWarnings res)) && getAll (seqresAllSuccess res) && goCollapse opts && ?istty + then do let thislen = 2*indent + length name + let Sum lns = seqresNumLines res putStrLn $ concat (replicate (lns+1) (ANSI.cursorUpCode 1 ++ ANSI.clearLineCode)) ++ ANSI.setCursorColumnCode 0 ++ replicate (2 * indent) ' ' ++ name ++ ": " ++ replicate (?maxlen - thislen) ' ' ++ ansiGreen ++ "OK" ++ ansiReset ++ prettyDuration False (realToFrac (diffUTCTime endtm starttm)) - return (Just 1) - _ -> return ((+1) <$> mlns) + return (mempty { seqresNumLines = 1 }) + else return (res <> (mempty { seqresNumLines = 1 })) runTreeSeq indent path (Resource _ make cleanup fun) = do + outputted <- newIORef False + let ?testCtx = TestCtx (\str -> do + atomicModifyIORef' outputted (\_ -> (True, ())) + putStrLn (ansiYellow ++ "## Warning for " ++ (intercalate "/" (reverse path)) ++ + ":" ++ ansiReset ++ "\n" ++ str)) value <- make - success <- runTreeSeq indent path (fun value) + res <- runTreeSeq indent path (fun value) cleanup value - return success + warnings <- readIORef outputted + return (res <> (mempty { seqresHaveWarnings = Any warnings })) runTreeSeq indent path (HP name prop) = do let thislen = 2*indent + length name let prefix = replicate (2*indent) ' ' ++ name ++ ": " ++ replicate (?maxlen - thislen) ' ' when ?istty $ putStr prefix >> hFlush stdout (ok, rendered) <- runHP (outputProgress (?maxlen + 2)) path name prop putStrLn ((if ?istty then ANSI.clearFromCursorToLineEndCode else prefix) ++ rendered) >> hFlush stdout - return (if ok then Just 1 else Nothing) + return (mempty { seqresAllSuccess = All ok, seqresNumLines = 1 }) runHP :: (?options :: Options, ?stats :: IORef Stats, ?maxlen :: Int) => (H.Report H.Progress -> IO ()) @@ -489,10 +521,11 @@ ansi :: (?istty :: Bool) => String -> String ansi | ?istty = id | otherwise = const "" -ansiRed, ansiGreen, ansiReset :: (?istty :: Bool) => String -ansiRed = ansi (ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Dull ANSI.Red]) -ansiGreen = ansi (ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Dull ANSI.Green]) -ansiReset = ansi (ANSI.setSGRCode [ANSI.Reset]) +ansiRed, ansiYellow, ansiGreen, ansiReset :: (?istty :: Bool) => String +ansiRed = ansi (ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Dull ANSI.Red]) +ansiYellow = ansi (ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Vivid ANSI.Yellow]) +ansiGreen = ansi (ANSI.setSGRCode [ANSI.SetColor ANSI.Foreground ANSI.Dull ANSI.Green]) +ansiReset = ansi (ANSI.setSGRCode [ANSI.Reset]) -- getTermIsDark :: IO Bool -- getTermIsDark = do |
