diff options
author | Ben Gamari <ben@smart-cactus.org> | 2018-10-23 14:20:13 -0400 |
---|---|---|
committer | Ben Gamari <ben@smart-cactus.org> | 2018-10-23 14:20:13 -0400 |
commit | 94756201349685a34c4495addd3484fdfcc8b498 (patch) | |
tree | fd4a9cee20d3c2b79f56ded7e02fb0c01b26b6c9 /hadrian/src/Oracles | |
parent | 575b35f4cdc18045bccd42d341d6f25d95c0696c (diff) | |
parent | 45f3bff7016a2a0cd9a5455a882ced984655e90b (diff) | |
download | haskell-94756201349685a34c4495addd3484fdfcc8b498.tar.gz |
Add 'hadrian/' from commit '45f3bff7016a2a0cd9a5455a882ced984655e90b'
git-subtree-dir: hadrian
git-subtree-mainline: 575b35f4cdc18045bccd42d341d6f25d95c0696c
git-subtree-split: 45f3bff7016a2a0cd9a5455a882ced984655e90b
Diffstat (limited to 'hadrian/src/Oracles')
-rw-r--r-- | hadrian/src/Oracles/Flag.hs | 76 | ||||
-rw-r--r-- | hadrian/src/Oracles/ModuleFiles.hs | 182 | ||||
-rw-r--r-- | hadrian/src/Oracles/Setting.hs | 221 | ||||
-rw-r--r-- | hadrian/src/Oracles/TestSettings.hs | 69 |
4 files changed, 548 insertions, 0 deletions
diff --git a/hadrian/src/Oracles/Flag.hs b/hadrian/src/Oracles/Flag.hs new file mode 100644 index 0000000000..57dbf2decb --- /dev/null +++ b/hadrian/src/Oracles/Flag.hs @@ -0,0 +1,76 @@ +module Oracles.Flag ( + Flag (..), flag, getFlag, platformSupportsSharedLibs, ghcWithSMP, + ghcWithNativeCodeGen, supportsSplitObjects + ) where + +import Hadrian.Oracles.TextFile +import Hadrian.Expression + +import Base +import Oracles.Setting + +data Flag = ArSupportsAtFile + | CrossCompiling + | GccIsClang + | GhcUnregisterised + | LeadingUnderscore + | SolarisBrokenShld + | SplitObjectsBroken + | WithLibdw + | HaveLibMingwEx + | UseSystemFfi + +-- Note, if a flag is set to empty string we treat it as set to NO. This seems +-- fragile, but some flags do behave like this, e.g. GccIsClang. +flag :: Flag -> Action Bool +flag f = do + let key = case f of + ArSupportsAtFile -> "ar-supports-at-file" + CrossCompiling -> "cross-compiling" + GccIsClang -> "gcc-is-clang" + GhcUnregisterised -> "ghc-unregisterised" + LeadingUnderscore -> "leading-underscore" + SolarisBrokenShld -> "solaris-broken-shld" + SplitObjectsBroken -> "split-objects-broken" + WithLibdw -> "with-libdw" + HaveLibMingwEx -> "have-lib-mingw-ex" + UseSystemFfi -> "use-system-ffi" + value <- lookupValueOrError configFile key + when (value `notElem` ["YES", "NO", ""]) . error $ "Configuration flag " + ++ quote (key ++ " = " ++ value) ++ " cannot be parsed." + return $ value == "YES" + +-- | Get a configuration setting. +getFlag :: Flag -> Expr c b Bool +getFlag = expr . flag + +platformSupportsSharedLibs :: Action Bool +platformSupportsSharedLibs = do + badPlatform <- anyTargetPlatform [ "powerpc-unknown-linux" + , "x86_64-unknown-mingw32" + , "i386-unknown-mingw32" ] + solaris <- anyTargetPlatform [ "i386-unknown-solaris2" ] + solarisBroken <- flag SolarisBrokenShld + return $ not (badPlatform || solaris && solarisBroken) + +ghcWithSMP :: Action Bool +ghcWithSMP = do + goodArch <- anyTargetArch ["i386", "x86_64", "sparc", "powerpc", "arm"] + ghcUnreg <- flag GhcUnregisterised + return $ goodArch && not ghcUnreg + +ghcWithNativeCodeGen :: Action Bool +ghcWithNativeCodeGen = do + goodArch <- anyTargetArch ["i386", "x86_64", "sparc", "powerpc"] + badOs <- anyTargetOs ["ios", "aix"] + ghcUnreg <- flag GhcUnregisterised + return $ goodArch && not badOs && not ghcUnreg + +supportsSplitObjects :: Action Bool +supportsSplitObjects = do + broken <- flag SplitObjectsBroken + ghcUnreg <- flag GhcUnregisterised + goodArch <- anyTargetArch [ "i386", "x86_64", "powerpc", "sparc" ] + goodOs <- anyTargetOs [ "mingw32", "cygwin32", "linux", "darwin", "solaris2" + , "freebsd", "dragonfly", "netbsd", "openbsd" ] + return $ not broken && not ghcUnreg && goodArch && goodOs diff --git a/hadrian/src/Oracles/ModuleFiles.hs b/hadrian/src/Oracles/ModuleFiles.hs new file mode 100644 index 0000000000..1e508c0090 --- /dev/null +++ b/hadrian/src/Oracles/ModuleFiles.hs @@ -0,0 +1,182 @@ +{-# LANGUAGE TypeFamilies #-} +module Oracles.ModuleFiles ( + decodeModule, encodeModule, findGenerator, hsSources, hsObjects, + moduleFilesOracle + ) where + +import qualified Data.HashMap.Strict as Map +import Hadrian.Haskell.Cabal.Type as PD + +import Base +import Builder +import Context +import Expression +import Packages + +type ModuleName = String + +newtype ModuleFiles = ModuleFiles (Stage, Package) + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) +type instance RuleResult ModuleFiles = [Maybe FilePath] + +newtype Generator = Generator (Stage, Package, FilePath) + deriving (Binary, Eq, Hashable, NFData, Show, Typeable) +type instance RuleResult Generator = Maybe FilePath + +-- | We scan for the following Haskell source extensions when looking for module +-- files. Note, we do not list "*.(l)hs-boot" files here, as they can never +-- appear by themselves and always have accompanying "*.(l)hs" master files. +haskellExtensions :: [String] +haskellExtensions = [".hs", ".lhs"] + +-- | Non-Haskell source extensions and corresponding builders. +otherExtensions :: Stage -> [(String, Builder)] +otherExtensions stage = [ (".x" , Alex ) + , (".y" , Happy ) + , (".ly" , Happy ) + , (".hsc", Hsc2Hs stage) ] + +-- | We match the following file patterns when looking for module files. +moduleFilePatterns :: Stage -> [FilePattern] +moduleFilePatterns stage = map ("*" ++) $ haskellExtensions ++ map fst (otherExtensions stage) + +-- | Given a FilePath determine the corresponding builder. +determineBuilder :: Stage -> FilePath -> Maybe Builder +determineBuilder stage file = lookup (takeExtension file) (otherExtensions stage) + +-- | Given a non-empty module name extract the directory and file name, e.g.: +-- +-- > decodeModule "Data.Functor.Identity" == ("Data/Functor", "Identity") +-- > decodeModule "Prelude" == ("", "Prelude") +decodeModule :: ModuleName -> (FilePath, String) +decodeModule moduleName = (intercalate "/" (init xs), last xs) + where + xs = words $ replaceEq '.' ' ' moduleName + +-- | Given the directory and file name find the corresponding module name, e.g.: +-- +-- > encodeModule "Data/Functor" "Identity.hs" == "Data.Functor.Identity" +-- > encodeModule "" "Prelude" == "Prelude" +-- > uncurry encodeModule (decodeModule name) == name +encodeModule :: FilePath -> String -> ModuleName +encodeModule dir file + | dir == "" = takeBaseName file + | otherwise = replaceEq '/' '.' dir ++ '.' : takeBaseName file + +-- | Find the generator for a given 'Context' and a source file. For example: +-- findGenerator (Context Stage1 compiler vanilla) +-- "_build/stage1/compiler/build/Lexer.hs" +-- == Just ("compiler/parser/Lexer.x", Alex) +-- findGenerator (Context Stage1 base vanilla) +-- "_build/stage1/base/build/Prelude.hs" +-- == Nothing +findGenerator :: Context -> FilePath -> Action (Maybe (FilePath, Builder)) +findGenerator Context {..} file = do + maybeSource <- askOracle $ Generator (stage, package, file) + return $ do + source <- maybeSource + builder <- determineBuilder stage source + return (source, builder) + +-- | Find all Haskell source files for a given 'Context'. +hsSources :: Context -> Action [FilePath] +hsSources context = do + let modFile (m, Nothing ) = generatedFile context m + modFile (m, Just file ) + | takeExtension file `elem` haskellExtensions = return file + | otherwise = generatedFile context m + mapM modFile =<< contextFiles context + +-- | Find all Haskell object files for a given 'Context'. Note: this is a much +-- simpler function compared to 'hsSources', because all object files live in +-- the build directory regardless of whether they are generated or not. +hsObjects :: Context -> Action [FilePath] +hsObjects context = do + modules <- interpretInContext context (getContextData PD.modules) + mapM (objectPath context . moduleSource) modules + +-- | Generated module files live in the 'Context' specific build directory. +generatedFile :: Context -> ModuleName -> Action FilePath +generatedFile context moduleName = buildPath context <&> (-/- moduleSource moduleName) + +-- | Turn a module name (e.g. @Data.Functor@) to a path (e.g. @Data/Functor.hs@). +moduleSource :: ModuleName -> FilePath +moduleSource moduleName = replaceEq '.' '/' moduleName <.> "hs" + +-- | Module files for a given 'Context'. +contextFiles :: Context -> Action [(ModuleName, Maybe FilePath)] +contextFiles context@Context {..} = do + modules <- fmap sort . interpretInContext context $ + getContextData PD.modules + zip modules <$> askOracle (ModuleFiles (stage, package)) + +-- | This is an important oracle whose role is to find and cache module source +-- files. It takes a 'Stage' and a 'Package', looks up corresponding source +-- directories @dirs@ and a sorted list of module names @modules@, and for each +-- module, e.g. @A.B.C@, returns a 'FilePath' of the form @dir/A/B/C.extension@, +-- such that @dir@ belongs to @dirs@, and file @dir/A/B/C.extension@ exists, or +-- 'Nothing' if there is no such file. If more than one matching file is found +-- an error is raised. For example, for 'Stage1' and 'compiler', @dirs@ will +-- contain ["compiler/codeGen", "compiler/parser"], and @modules@ will contain +-- ["CodeGen.Platform.ARM", "Config", "Lexer"]; the oracle will produce a list +-- containing [Just "compiler/codeGen/CodeGen/Platform/ARM.hs", Nothing, +-- Just "compiler/parser/Lexer.x"]. The oracle ignores @.(l)hs-boot@ files. +moduleFilesOracle :: Rules () +moduleFilesOracle = void $ do + void . addOracleCache $ \(ModuleFiles (stage, package)) -> do + let context = vanillaContext stage package + srcDirs <- interpretInContext context (getContextData PD.srcDirs) + mainIs <- interpretInContext context (getContextData PD.mainIs) + let removeMain = case mainIs of + Just (mod, _) -> delete mod + Nothing -> id + modules <- fmap sort $ interpretInContext context (getContextData PD.modules) + autogen <- autogenPath context + let dirs = autogen : map (pkgPath package -/-) srcDirs + -- Don't resolve the file path for module `Main` twice. + modDirFiles = groupSort $ map decodeModule $ removeMain modules + result <- concatForM dirs $ \dir -> do + todo <- filterM (doesDirectoryExist . (dir -/-) . fst) modDirFiles + forM todo $ \(mDir, mFiles) -> do + let fullDir = unifyPath $ dir -/- mDir + files <- getDirectoryFiles fullDir (moduleFilePatterns stage) + let cmp f = compare (dropExtension f) + found = intersectOrd cmp files mFiles + return (map (fullDir -/-) found, mDir) + + -- For a BuildInfo, it may be a library, which doesn't have the @Main@ + -- module, or an executable, which must have the @Main@ module and the + -- file path of @Main@ module is indicated by the @main-is@ field in its + -- Cabal file. + -- + -- For the Main module, the file name may not be @Main.hs@, unlike other + -- exposed modules. We could get the file path by the module name for + -- other exposed modules, but for @Main@ we must resolve the file path + -- via the @main-is@ field in the Cabal file. + mainpairs <- case mainIs of + Just (mod, filepath) -> + concatForM dirs $ \dir -> do + found <- doesFileExist (dir -/- filepath) + return [(mod, unifyPath $ dir -/- filepath) | found] + Nothing -> return [] + + let pairs = sort $ mainpairs ++ [ (encodeModule d f, f) | (fs, d) <- result, f <- fs ] + multi = [ (m, f1, f2) | (m, f1):(n, f2):_ <- tails pairs, m == n ] + unless (null multi) $ do + let (m, f1, f2) = head multi + error $ "Module " ++ m ++ " has more than one source file: " + ++ f1 ++ " and " ++ f2 ++ "." + return $ lookupAll modules pairs + + -- Optimisation: we discard Haskell files here, because they are never used + -- as generators, and hence would be discarded in 'findGenerator' anyway. + generators <- newCache $ \(stage, package) -> do + let context = vanillaContext stage package + files <- contextFiles context + list <- sequence [ (,src) <$> generatedFile context modName + | (modName, Just src) <- files + , takeExtension src `notElem` haskellExtensions ] + return $ Map.fromList list + + addOracleCache $ \(Generator (stage, package, file)) -> + Map.lookup file <$> generators (stage, package) diff --git a/hadrian/src/Oracles/Setting.hs b/hadrian/src/Oracles/Setting.hs new file mode 100644 index 0000000000..1cdcddf186 --- /dev/null +++ b/hadrian/src/Oracles/Setting.hs @@ -0,0 +1,221 @@ +module Oracles.Setting ( + configFile, Setting (..), SettingList (..), setting, settingList, getSetting, + getSettingList, anyTargetPlatform, anyTargetOs, anyTargetArch, anyHostOs, + ghcWithInterpreter, ghcEnableTablesNextToCode, useLibFFIForAdjustors, + ghcCanonVersion, cmdLineLengthLimit, iosHost, osxHost, windowsHost, + topDirectory, libsuf + ) where + +import Hadrian.Expression +import Hadrian.Oracles.TextFile +import Hadrian.Oracles.Path + +import Base + +-- | Each 'Setting' comes from the file @hadrian/cfg/system.config@, generated +-- by the @configure@ script from the input file @hadrian/cfg/system.config.in@. +-- For example, the line +-- +-- > target-os = mingw32 +-- +-- sets the value of the setting 'TargetOs'. The action 'setting' 'TargetOs' +-- looks up the value of the setting and returns the string @"mingw32"@, +-- tracking the result in the Shake database. +data Setting = BuildArch + | BuildOs + | BuildPlatform + | BuildVendor + | CcClangBackend + | CcLlvmBackend + | CursesLibDir + | DynamicExtension + | FfiIncludeDir + | FfiLibDir + | GhcMajorVersion + | GhcMinorVersion + | GhcPatchLevel + | GhcVersion + | GhcSourcePath + | GmpIncludeDir + | GmpLibDir + | HostArch + | HostOs + | HostPlatform + | HostVendor + | IconvIncludeDir + | IconvLibDir + | LlvmTarget + | ProjectGitCommitId + | ProjectName + | ProjectVersion + | ProjectVersionInt + | ProjectPatchLevel + | ProjectPatchLevel1 + | ProjectPatchLevel2 + | SystemGhc + | TargetArch + | TargetOs + | TargetPlatform + | TargetPlatformFull + | TargetVendor + +-- TODO: Reduce the variety of similar flags (e.g. CPP and non-CPP versions). +-- | Each 'SettingList' comes from the file @hadrian/cfg/system.config@, +-- generated by the @configure@ script from the input file +-- @hadrian/cfg/system.config.in@. For example, the line +-- +-- > hs-cpp-args = -E -undef -traditional +-- +-- sets the value of 'HsCppArgs'. The action 'settingList' 'HsCppArgs' looks up +-- the value of the setting and returns the list of strings +-- @["-E", "-undef", "-traditional"]@, tracking the result in the Shake database. +data SettingList = ConfCcArgs Stage + | ConfCppArgs Stage + | ConfGccLinkerArgs Stage + | ConfLdLinkerArgs Stage + | HsCppArgs + +-- | Look up the value of a 'Setting' in @cfg/system.config@, tracking the +-- result. +setting :: Setting -> Action String +setting key = lookupValueOrError configFile $ case key of + BuildArch -> "build-arch" + BuildOs -> "build-os" + BuildPlatform -> "build-platform" + BuildVendor -> "build-vendor" + CcClangBackend -> "cc-clang-backend" + CcLlvmBackend -> "cc-llvm-backend" + CursesLibDir -> "curses-lib-dir" + DynamicExtension -> "dynamic-extension" + FfiIncludeDir -> "ffi-include-dir" + FfiLibDir -> "ffi-lib-dir" + GhcMajorVersion -> "ghc-major-version" + GhcMinorVersion -> "ghc-minor-version" + GhcPatchLevel -> "ghc-patch-level" + GhcVersion -> "ghc-version" + GhcSourcePath -> "ghc-source-path" + GmpIncludeDir -> "gmp-include-dir" + GmpLibDir -> "gmp-lib-dir" + HostArch -> "host-arch" + HostOs -> "host-os" + HostPlatform -> "host-platform" + HostVendor -> "host-vendor" + IconvIncludeDir -> "iconv-include-dir" + IconvLibDir -> "iconv-lib-dir" + LlvmTarget -> "llvm-target" + ProjectGitCommitId -> "project-git-commit-id" + ProjectName -> "project-name" + ProjectVersion -> "project-version" + ProjectVersionInt -> "project-version-int" + ProjectPatchLevel -> "project-patch-level" + ProjectPatchLevel1 -> "project-patch-level1" + ProjectPatchLevel2 -> "project-patch-level2" + SystemGhc -> "system-ghc" + TargetArch -> "target-arch" + TargetOs -> "target-os" + TargetPlatform -> "target-platform" + TargetPlatformFull -> "target-platform-full" + TargetVendor -> "target-vendor" + +-- | Look up the value of a 'SettingList' in @cfg/system.config@, tracking the +-- result. +settingList :: SettingList -> Action [String] +settingList key = fmap words $ lookupValueOrError configFile $ case key of + ConfCcArgs stage -> "conf-cc-args-" ++ stageString stage + ConfCppArgs stage -> "conf-cpp-args-" ++ stageString stage + ConfGccLinkerArgs stage -> "conf-gcc-linker-args-" ++ stageString stage + ConfLdLinkerArgs stage -> "conf-ld-linker-args-" ++ stageString stage + HsCppArgs -> "hs-cpp-args" + +-- | An expression that looks up the value of a 'Setting' in @cfg/system.config@, +-- tracking the result. +getSetting :: Setting -> Expr c b String +getSetting = expr . setting + +-- | An expression that looks up the value of a 'SettingList' in +-- @cfg/system.config@, tracking the result. +getSettingList :: SettingList -> Args c b +getSettingList = expr . settingList + +-- | Check whether the value of a 'Setting' matches one of the given strings. +matchSetting :: Setting -> [String] -> Action Bool +matchSetting key values = (`elem` values) <$> setting key + +-- | Check whether the target platform setting matches one of the given strings. +anyTargetPlatform :: [String] -> Action Bool +anyTargetPlatform = matchSetting TargetPlatformFull + +-- | Check whether the target OS setting matches one of the given strings. +anyTargetOs :: [String] -> Action Bool +anyTargetOs = matchSetting TargetOs + +-- | Check whether the target architecture setting matches one of the given +-- strings. +anyTargetArch :: [String] -> Action Bool +anyTargetArch = matchSetting TargetArch + +-- | Check whether the host OS setting matches one of the given strings. +anyHostOs :: [String] -> Action Bool +anyHostOs = matchSetting HostOs + +-- | Check whether the host OS setting is set to @"ios"@. +iosHost :: Action Bool +iosHost = anyHostOs ["ios"] + +-- | Check whether the host OS setting is set to @"darwin"@. +osxHost :: Action Bool +osxHost = anyHostOs ["darwin"] + +-- | Check whether the host OS setting is set to @"mingw32"@ or @"cygwin32"@. +windowsHost :: Action Bool +windowsHost = anyHostOs ["mingw32", "cygwin32"] + +-- | Check whether the target supports GHCi. +ghcWithInterpreter :: Action Bool +ghcWithInterpreter = do + goodOs <- anyTargetOs [ "mingw32", "cygwin32", "linux", "solaris2" + , "freebsd", "dragonfly", "netbsd", "openbsd" + , "darwin", "kfreebsdgnu" ] + goodArch <- anyTargetArch [ "i386", "x86_64", "powerpc", "sparc" + , "sparc64", "arm" ] + return $ goodOs && goodArch + +-- | Check whether the target architecture supports placing info tables next to +-- code. See: https://ghc.haskell.org/trac/ghc/wiki/Commentary/Rts/Storage/HeapObjects#TABLES_NEXT_TO_CODE. +ghcEnableTablesNextToCode :: Action Bool +ghcEnableTablesNextToCode = notM $ anyTargetArch ["ia64", "powerpc64", "powerpc64le"] + +-- | Check to use @libffi@ for adjustors. +useLibFFIForAdjustors :: Action Bool +useLibFFIForAdjustors = notM $ anyTargetArch ["i386", "x86_64"] + +-- | Canonicalised GHC version number, used for integer version comparisons. We +-- expand 'GhcMinorVersion' to two digits by adding a leading zero if necessary. +ghcCanonVersion :: Action String +ghcCanonVersion = do + ghcMajorVersion <- setting GhcMajorVersion + ghcMinorVersion <- setting GhcMinorVersion + let leadingZero = [ '0' | length ghcMinorVersion == 1 ] + return $ ghcMajorVersion ++ leadingZero ++ ghcMinorVersion + +-- | Path to the GHC source tree. +topDirectory :: Action FilePath +topDirectory = fixAbsolutePathOnWindows =<< setting GhcSourcePath + +-- | The file suffix used for libraries of a given build 'Way'. For example, +-- @_p.a@ corresponds to a static profiled library, and @-ghc7.11.20141222.so@ +-- is a dynamic vanilly library. Why do we need GHC version number in the +-- dynamic suffix? Here is a possible reason: dynamic libraries are placed in a +-- single giant directory in the load path of the dynamic linker, and hence we +-- must distinguish different versions of GHC. In contrast, static libraries +-- live in their own per-package directory and hence do not need a unique +-- filename. We also need to respect the system's dynamic extension, e.g. @.dll@ +-- or @.so@. +libsuf :: Way -> Action String +libsuf way + | not (wayUnit Dynamic way) = return (waySuffix way ++ ".a") -- e.g., _p.a + | otherwise = do + extension <- setting DynamicExtension -- e.g., .dll or .so + version <- setting ProjectVersion -- e.g., 7.11.20141222 + let suffix = waySuffix (removeWayUnit Dynamic way) + return ("-ghc" ++ version ++ suffix ++ extension) diff --git a/hadrian/src/Oracles/TestSettings.hs b/hadrian/src/Oracles/TestSettings.hs new file mode 100644 index 0000000000..1bf75b527d --- /dev/null +++ b/hadrian/src/Oracles/TestSettings.hs @@ -0,0 +1,69 @@ +-- | We create a file <root>/test/ghcconfig containing configuration of test +-- | compiler. We need to search this file for required keys and setting +-- | required for testsuite e.g. WORDSIZE, HOSTOS etc. + +module Oracles.TestSettings (TestSetting (..), testSetting, testRTSSettings) where + +import Base +import Hadrian.Oracles.TextFile + +testConfigFile :: Action FilePath +testConfigFile = buildRoot <&> (-/- "test/ghcconfig") + +-- | Test settings that are obtained from ghcconfig file. +data TestSetting = TestHostOS + | TestWORDSIZE + | TestTARGETPLATFORM + | TestTargetOS_CPP + | TestTargetARCH_CPP + | TestGhcStage + | TestGhcDebugged + | TestGhcWithNativeCodeGen + | TestGhcWithInterpreter + | TestGhcUnregisterised + | TestGhcWithSMP + | TestGhcDynamicByDefault + | TestGhcDynamic + | TestGhcProfiled + | TestAR + | TestCLANG + | TestLLC + | TestTEST_CC + | TestGhcPackageDbFlag + | TestMinGhcVersion711 + | TestMinGhcVersion801 + deriving (Show) + +-- | Lookup a test setting in @ghcconfig@ file. +-- | To obtain RTS ways supported in @ghcconfig@ file, use 'testRTSSettings'. +testSetting :: TestSetting -> Action String +testSetting key = do + file <- testConfigFile + lookupValueOrError file $ case key of + TestHostOS -> "HostOS" + TestWORDSIZE -> "WORDSIZE" + TestTARGETPLATFORM -> "TARGETPLATFORM" + TestTargetOS_CPP -> "TargetOS_CPP" + TestTargetARCH_CPP -> "TargetARCH_CPP" + TestGhcStage -> "GhcStage" + TestGhcDebugged -> "GhcDebugged" + TestGhcWithNativeCodeGen -> "GhcWithNativeCodeGen" + TestGhcWithInterpreter -> "GhcWithInterpreter" + TestGhcUnregisterised -> "GhcUnregisterised" + TestGhcWithSMP -> "GhcWithSMP" + TestGhcDynamicByDefault -> "GhcDynamicByDefault" + TestGhcDynamic -> "GhcDynamic" + TestGhcProfiled -> "GhcProfiled" + TestAR -> "AR" + TestCLANG -> "CLANG" + TestLLC -> "LLC" + TestTEST_CC -> "TEST_CC" + TestGhcPackageDbFlag -> "GhcPackageDbFlag" + TestMinGhcVersion711 -> "MinGhcVersion711" + TestMinGhcVersion801 -> "MinGhcVersion801" + +-- | Get the RTS ways of the test compiler +testRTSSettings :: Action [String] +testRTSSettings = do + file <- testConfigFile + words <$> lookupValueOrError file "GhcRTSWays" |