@@ -35,9 +35,8 @@ module Test.Cabal.Monad (
35
35
testSourceCopyDir ,
36
36
testCabalDir ,
37
37
testUserCabalConfigFile ,
38
- testActualFileOut ,
39
- testActualFileStdout ,
40
- testActualFileStderr ,
38
+ FileDescriptor (.. ),
39
+ testActualFile ,
41
40
-- * Skipping tests
42
41
skip ,
43
42
skipIf ,
@@ -354,36 +353,28 @@ runTestM mode m = withSystemTempDirectory "cabal-testsuite" $ \tmp_dir -> do
354
353
check_expect accept = do
355
354
env <- getTestEnv
356
355
norm_env <- mkNormalizerEnv
357
- let testDiff actual actualNormalized expect expectNormalized = when (words actual /= words expect) $ do
358
- -- First try whitespace insensitive diff
359
- -- let actualNormalized = testNormalizedActualFileStdout env
360
- -- expectNormalized = testNormalizedExpectFileStdout env
361
- liftIO $ writeFile actualNormalized actual
362
- liftIO $ writeFile expectNormalized expect
363
- liftIO $ putStrLn " Actual output differs from expected:"
364
- b <- diff [" -uw" ] expectNormalized actualNormalized
365
- unless b . void $ diff [" -u" ] expectNormalized actualNormalized
366
- if accept
367
- then do liftIO $ putStrLn " Accepting new output."
368
- liftIO $ writeFileNoCR (testExpectFileStdout env) actual
369
- else liftIO $ exitWith (ExitFailure 1 )
370
- -- actualOut <- normalizeOutput norm_env <$> liftIO (readFileOrEmpty (testActualFileOut env))
371
- -- expectOut <- liftIO $ readFileOrEmpty (testExpectFileOut env)
372
- -- actualStdout <- normalizeOutput norm_env <$> liftIO (readFileOrEmpty (testActualFileStdout env))
373
- -- expectStdout <- liftIO $ readFileOrEmpty (testExpectFileStdout env)
374
- -- actualStderr <- normalizeOutput norm_env <$> liftIO (readFileOrEmpty (testActualFileStderr env))
375
- -- expectStderr <- liftIO $ readFileOrEmpty (testExpectFileStderr env)
376
- forM_
377
- [ (testActualFileOut env, testNormalizedActualFileOut env , testExpectFileOut env , testNormalizedExpectFileOut env)
378
- , (testActualFileStdout env, testNormalizedActualFileStdout env, testExpectFileStdout env, testNormalizedExpectFileStdout env)
379
- , (testActualFileStderr env, testNormalizedActualFileStderr env, testExpectFileStderr env, testNormalizedExpectFileStderr env)
380
- ] $ \ (actualFile, actualFileNormalized, expectFile, expectFileNormalized) -> do
381
- exists <- liftIO $ doesFileExist expectFile
382
- liftIO $ print (expectFile, exists)
356
+ [Out , Stdout , Stderr ] `forM_` \ fd -> do
357
+ exists <- liftIO $ doesFileExist $ testFile NotNormalized Expect fd env
383
358
when exists $ do
384
- actualOut <- normalizeOutput norm_env <$> liftIO (readFileOrEmpty actualFile)
385
- expectOut <- liftIO $ readFileOrEmpty expectFile
386
- testDiff actualOut actualFileNormalized expectOut expectFileNormalized
359
+ actual <- normalizeOutput norm_env <$> liftIO (readFileOrEmpty (testFile NotNormalized Actual fd env))
360
+ expect <- liftIO $ readFileOrEmpty (testFile NotNormalized Expect fd env)
361
+ when (words actual /= words expect) $ do
362
+ -- First try whitespace insensitive diff
363
+ let
364
+ actualFile = testFile Normalized Actual fd env
365
+ expectFile = testFile Normalized Expect fd env
366
+ liftIO $ do
367
+ writeFile expectFile actual
368
+ writeFile actualFile expect
369
+ putStrLn " Actual output differs from expected:"
370
+ b <- diff [" -uw" ] expectFile actualFile
371
+ unless b . void $ diff [" -u" ] expectFile actualFile
372
+ liftIO $
373
+ if accept
374
+ then do
375
+ putStrLn " Accepting new output."
376
+ writeFileNoCR (testFile NotNormalized Expect Stdout env) actual
377
+ else exitWith (ExitFailure 1 )
387
378
388
379
readFileOrEmpty :: FilePath -> IO String
389
380
readFileOrEmpty f = readFile f `E.catch` \ e ->
@@ -612,66 +603,23 @@ testCabalDir env = testHomeDir env </> ".cabal"
612
603
testUserCabalConfigFile :: TestEnv -> FilePath
613
604
testUserCabalConfigFile env = testCabalDir env </> " config"
614
605
615
- -- data Expected = Expected | Actual
616
- -- data Normalized = Normalized | NotNormalized
617
- -- data FileDescriptor = Out | Stdout | Stderr
618
-
619
- -- testFile :: Expected -> Normalized -> FileDescriptor -> TestEnv -> FilePath
620
- -- testFile e n f env = sourceDir </> testName env <.> suffix
621
- -- where
622
- -- suffix
623
- -- = case e of { Expected -> "comp" ; Actual -> "" }
624
- -- <.> case f of { Out -> "out" ; Stdout -> "stdout" ; Stderr -> "stderr" }
625
- -- <.> case n of { Normalized -> "normalized" ; NotNormalized -> "" }
626
- -- sourceDir = case (e, n) of
627
- -- (_, Normalized) -> testWorkDir env
628
- -- (Actual, _) -> testWorkDir env
629
- -- _ -> testSourceDir env
630
-
631
- -- | The file where the expected output of the test lives
632
- testExpectFileOut :: TestEnv -> FilePath
633
- testExpectFileOut env = testSourceDir env </> testName env <.> " out"
634
-
635
- -- | Where we store the actual output
636
- testActualFileOut :: TestEnv -> FilePath
637
- testActualFileOut env = testWorkDir env </> testName env <.> " comp.out"
638
-
639
- -- | The file where the expected output of the test lives
640
- testExpectFileStdout :: TestEnv -> FilePath
641
- testExpectFileStdout env = testSourceDir env </> testName env <.> " stdout"
642
-
643
- -- | Where we store the actual output
644
- testActualFileStdout :: TestEnv -> FilePath
645
- testActualFileStdout env = testWorkDir env </> testName env <.> " comp.stdout"
646
-
647
- -- | The file where the expected output of the test lives
648
- testExpectFileStderr :: TestEnv -> FilePath
649
- testExpectFileStderr env = testSourceDir env </> testName env <.> " stderr"
650
-
651
- -- | Where we store the actual errput
652
- testActualFileStderr :: TestEnv -> FilePath
653
- testActualFileStderr env = testWorkDir env </> testName env <.> " comp.stderr"
654
-
655
- -- | Where we will write the normalized actual file (for diffing)
656
- testNormalizedActualFileOut :: TestEnv -> FilePath
657
- testNormalizedActualFileOut env = testActualFileOut env <.> " normalized"
658
-
659
- -- | Where we will write the normalized expected file (for diffing)
660
- testNormalizedExpectFileOut :: TestEnv -> FilePath
661
- testNormalizedExpectFileOut env = testWorkDir env </> testName env <.> " out.normalized"
662
-
663
- -- | Where we will write the normalized actual file (for diffing)
664
- testNormalizedActualFileStdout :: TestEnv -> FilePath
665
- testNormalizedActualFileStdout env = testActualFileStdout env <.> " normalized"
666
-
667
- -- | Where we will write the normalized expected file (for diffing)
668
- testNormalizedExpectFileStdout :: TestEnv -> FilePath
669
- testNormalizedExpectFileStdout env = testWorkDir env </> testName env <.> " stdout.normalized"
670
-
671
- -- | Where we will write the normalized actual file (for diffing)
672
- testNormalizedActualFileStderr :: TestEnv -> FilePath
673
- testNormalizedActualFileStderr env = testActualFileStderr env <.> " normalized"
674
-
675
- -- | Where we will write the normalized expected file (for diffing)
676
- testNormalizedExpectFileStderr :: TestEnv -> FilePath
677
- testNormalizedExpectFileStderr env = testWorkDir env </> testName env <.> " stderr.normalized"
606
+ data Expected = Expect | Actual deriving (Show , Eq , Ord , Enum , Read , Bounded )
607
+ data Normalized = Normalized | NotNormalized deriving (Show , Eq , Ord , Enum , Read , Bounded )
608
+ data FileDescriptor = Out | Stdout | Stderr deriving (Show , Eq , Ord , Enum , Read , Bounded )
609
+
610
+ testFile :: Normalized -> Expected -> FileDescriptor -> TestEnv -> FilePath
611
+ testFile n e f = \ env -> sourceDir env </> testName env <.> suffix
612
+ where
613
+ suffix
614
+ = case e of { Expect -> " " ; Actual -> " comp" }
615
+ <.> case f of { Out -> " out" ; Stdout -> " stdout" ; Stderr -> " stderr" }
616
+ <.> case n of { Normalized -> " normalized" ; NotNormalized -> " " }
617
+ sourceDir env = case (e, n) of
618
+ (_, Normalized ) -> testWorkDir env
619
+ (Actual , _) -> testWorkDir env
620
+ _ -> testSourceDir env
621
+ {-# INLINE testFile #-}
622
+
623
+ testActualFile :: FileDescriptor -> TestEnv -> FilePath
624
+ testActualFile fd env = testFile NotNormalized Actual fd env
625
+ {-# INLINE testActualFile #-}
0 commit comments