Skip to content
Snippets Groups Projects
Commit a243411d authored by Edward Z. Yang's avatar Edward Z. Yang Committed by Edward Z. Yang
Browse files

Add hasProfiledLibraries check for tests using profiling.

parent f7b16cf0
No related branches found
No related tags found
No related merge requests found
import Test.Cabal.Prelude
-- Test building a profiled library/executable which uses Template Haskell
-- (setup has to build the non-profiled version first)
main = setupAndCabalTest $ setup_build ["--enable-library-profiling",
"--enable-profiling"]
main = setupAndCabalTest $ do
skipUnless =<< hasProfiledLibraries
setup_build ["--enable-library-profiling",
"--enable-profiling"]
......@@ -58,7 +58,9 @@ main =
-- Ensure that both .tix file and markup are generated if coverage
-- is enabled.
shared_libs <- hasSharedLibraries
prof_libs <- hasProfiledLibraries
unless ((exeDyn || shared) && not shared_libs) $ do
unless ((libProf || exeProf) && not prof_libs) $ do
isCorrectVersion <- liftIO $ correctHpcVersion
when isCorrectVersion $ do
dist_dir <- fmap testDistDir getTestEnv
......
......@@ -576,6 +576,17 @@ hasSharedLibraries = do
shared_libs_were_removed <- ghcVersionIs (>= mkVersion [7,8])
return (not (buildOS == Windows && shared_libs_were_removed))
hasProfiledLibraries :: TestM Bool
hasProfiledLibraries = do
env <- getTestEnv
initWorkDir
ghc_path <- programPathM ghcProgram
let prof_test_hs = testWorkDir env </> "Prof.hs"
liftIO $ writeFile prof_test_hs "module Prof where"
r <- liftIO $ run (testVerbosity env) (Just (testCurrentDir env))
(testEnvironment env) ghc_path ["-prof", "-c", prof_test_hs]
return (resultExitCode r == ExitSuccess)
-- | Check if the GHC that is used for compiling package tests has
-- a shared library of the cabal library under test in its database.
--
......
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