Skip to content
Snippets Groups Projects
Unverified Commit e48386c0 authored by mergify[bot]'s avatar mergify[bot] Committed by GitHub
Browse files

Merge pull request #8763 from haskell/Show-TestEnv

cabal-testsuite: new `instance Show TestEnv`
parents 90a2f335 6885fa7a
No related branches found
No related tags found
No related merge requests found
......@@ -336,7 +336,6 @@ runTestM mode m = withSystemTempDirectory "cabal-testsuite" $ \tmp_dir -> do
testPlan = Nothing,
testRecordDefaultMode = DoNotRecord,
testRecordUserMode = Nothing,
testRecordNormalizer = id,
testSourceCopyRelativeDir = "source"
}
let go = do cleanup
......@@ -527,12 +526,11 @@ data TestEnv = TestEnv
, testRecordDefaultMode :: RecordMode
-- | User explicitly set record mode. Not implemented ATM.
, testRecordUserMode :: Maybe RecordMode
-- | Function to normalize recorded output
, testRecordNormalizer :: String -> String
-- | Name of the subdirectory we copied the test's sources to,
-- relative to 'testSourceDir'
, testSourceCopyRelativeDir :: FilePath
}
deriving Show
testRecordMode :: TestEnv -> RecordMode
testRecordMode env = fromMaybe (testRecordDefaultMode env) (testRecordUserMode env)
......
......@@ -19,11 +19,13 @@ import Control.Monad
-- TODO: index this
data Plan = Plan { planInstallPlan :: [InstallItem] }
deriving Show
data InstallItem
= APreExisting
| AConfiguredGlobal ConfiguredGlobal
| AConfiguredInplace ConfiguredInplace
deriving Show
-- local or inplace package
data ConfiguredInplace = ConfiguredInplace
......@@ -31,11 +33,13 @@ data ConfiguredInplace = ConfiguredInplace
, configuredInplaceBuildInfo :: Maybe FilePath
, configuredInplacePackageName :: PackageName
, configuredInplaceComponentName :: Maybe ComponentName }
deriving Show
data ConfiguredGlobal = ConfiguredGlobal
{ configuredGlobalBinFile :: Maybe FilePath
, configuredGlobalPackageName :: PackageName
, configuredGlobalComponentName :: Maybe ComponentName }
deriving Show
instance FromJSON Plan where
parseJSON (Object v) = fmap Plan (v .: "install-plan")
......
......@@ -679,7 +679,7 @@ recordHeader args = do
env <- getTestEnv
let mode = testRecordMode env
str_header = "# " ++ intercalate " " args ++ "\n"
header = C.pack (testRecordNormalizer env str_header)
header = C.pack str_header
case mode of
DoNotRecord -> return ()
_ -> do
......@@ -696,7 +696,7 @@ recordLog res = do
liftIO $ C.appendFile (testWorkDir env </> "test.log")
(C.pack $ "+ " ++ resultCommand res ++ "\n"
++ resultOutput res ++ "\n\n")
liftIO . C.appendFile (testActualFile env) . C.pack . testRecordNormalizer env $
liftIO . C.appendFile (testActualFile env) . C.pack $
case mode of
RecordAll -> unlines (lines (resultOutput res))
RecordMarked -> getMarkedOutput (resultOutput res)
......@@ -787,10 +787,6 @@ recordMode mode = withReaderT (\env -> env {
testRecordUserMode = Just mode
})
recordNormalizer :: (String -> String) -> TestM a -> TestM a
recordNormalizer f =
withReaderT (\env -> env { testRecordNormalizer = testRecordNormalizer env . f })
assertOutputContains :: MonadIO m => WithCallStack (String -> Result -> m ())
assertOutputContains needle result =
withFrozenCallStack $
......
......@@ -37,6 +37,7 @@ data ScriptEnv = ScriptEnv
, runnerPackages :: [(OpenUnitId, ModuleRenaming)]
, runnerWithSharedLib :: Bool
}
deriving Show
{-
......
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