diff options
Diffstat (limited to 'compiler/main')
| -rw-r--r-- | compiler/main/CodeOutput.lhs | 22 | ||||
| -rw-r--r-- | compiler/main/DriverPipeline.hs | 133 | ||||
| -rw-r--r-- | compiler/main/DynFlags.hs | 129 | ||||
| -rw-r--r-- | compiler/main/SysTools.lhs | 19 |
4 files changed, 137 insertions, 166 deletions
diff --git a/compiler/main/CodeOutput.lhs b/compiler/main/CodeOutput.lhs index f5030777cb..f5e339440b 100644 --- a/compiler/main/CodeOutput.lhs +++ b/compiler/main/CodeOutput.lhs @@ -8,9 +8,7 @@ module CodeOutput( codeOutput, outputForeignStubs ) where #include "HsVersions.h" -#ifndef OMIT_NATIVE_CODEGEN -import AsmCodeGen ( nativeCodeGen ) -#endif +import AsmCodeGen ( nativeCodeGen ) import LlvmCodeGen ( llvmCodeGen ) import UniqSupply ( mkSplitUniqSupply ) @@ -149,24 +147,16 @@ outputC dflags filenm flat_absC packages \begin{code} outputAsm :: DynFlags -> FilePath -> [RawCmm] -> IO () - -#ifndef OMIT_NATIVE_CODEGEN - outputAsm dflags filenm flat_absC + | cGhcWithNativeCodeGen == "YES" = do ncg_uniqs <- mkSplitUniqSupply 'n' {-# SCC "OutputAsm" #-} doOutput filenm $ - \f -> {-# SCC "NativeCodeGen" #-} - nativeCodeGen dflags f ncg_uniqs flat_absC - where + \f -> {-# SCC "NativeCodeGen" #-} + nativeCodeGen dflags f ncg_uniqs flat_absC -#else /* OMIT_NATIVE_CODEGEN */ - -outputAsm _ _ _ - = pprPanic "This compiler was built without a native code generator" - (text "Use -fvia-C instead") - -#endif + | otherwise + = panic "This compiler was built without a native code generator" \end{code} diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index f92a4110b9..03e3cf6c56 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -55,6 +55,7 @@ import MonadUtils -- import Data.Either import Exception import Data.IORef ( readIORef ) +import Distribution.System -- import GHC.Exts ( Int(..) ) import System.Directory import System.FilePath @@ -269,11 +270,11 @@ link :: GhcLink -- interactive or batch -- exports main, i.e., we have good reason to believe that linking -- will succeed. -#ifdef GHCI link LinkInMemory _ _ _ - = do -- Not Linking...(demand linker will do the job) - return Succeeded -#endif + = if cGhcWithInterpreter == "YES" + then -- Not Linking...(demand linker will do the job) + return Succeeded + else panicBadLink LinkInMemory link NoLink _ _ _ = return Succeeded @@ -284,11 +285,6 @@ link LinkBinary dflags batch_attempt_linking hpt link LinkDynLib dflags batch_attempt_linking hpt = link' dflags batch_attempt_linking hpt -#ifndef GHCI --- warning suppression -link other _ _ _ = panicBadLink other -#endif - panicBadLink :: GhcLink -> a panicBadLink other = panic ("link: GHC not built to link this way: " ++ show other) @@ -1027,7 +1023,6 @@ runPhase cc_phase input_fn dflags let include_paths = foldr (\ x xs -> "-I" : x : xs) [] (cmdline_include_paths ++ pkg_include_dirs) - let md_c_flags = machdepCCOpts dflags let gcc_extra_viac_flags = extraGccViaCFlags dflags let pic_c_flags = picCCOpts dflags @@ -1062,15 +1057,14 @@ runPhase cc_phase input_fn dflags let more_hcc_opts = -#if i386_TARGET_ARCH -- on x86 the floating point regs have greater precision -- than a double, which leads to unpredictable results. -- By default, we turn this off with -ffloat-store unless -- the user specified -fexcess-precision. - (if dopt Opt_ExcessPrecision dflags - then [] - else [ "-ffloat-store" ]) ++ -#endif + (if cTargetArch == I386 && + not (dopt Opt_ExcessPrecision dflags) + then [ "-ffloat-store" ] + else []) ++ -- gcc's -fstrict-aliasing allows two accesses to memory -- to be considered non-aliasing if they have different types. @@ -1092,29 +1086,28 @@ runPhase cc_phase input_fn dflags , SysTools.FileOption "" output_fn ] ++ map SysTools.Option ( - md_c_flags - ++ pic_c_flags + pic_c_flags -#if defined(mingw32_TARGET_OS) -- Stub files generated for foreign exports references the runIO_closure -- and runNonIO_closure symbols, which are defined in the base package. -- These symbols are imported into the stub.c file via RtsAPI.h, and the -- way we do the import depends on whether we're currently compiling -- the base package or not. - ++ (if thisPackage dflags == basePackageId + ++ (if cTargetOS == Windows && + thisPackage dflags == basePackageId then [ "-DCOMPILING_BASE_PACKAGE" ] else []) -#endif -#ifdef sparc_TARGET_ARCH -- We only support SparcV9 and better because V8 lacks an atomic CAS -- instruction. Note that the user can still override this -- (e.g., -mcpu=ultrasparc) as GCC picks the "best" -mcpu flag -- regardless of the ordering. -- -- This is a temporary hack. - ++ ["-mcpu=v9"] -#endif + ++ (if cTargetArch == Sparc + then ["-mcpu=v9"] + else []) + ++ (if hcc then gcc_extra_viac_flags ++ more_hcc_opts else []) @@ -1178,11 +1171,10 @@ runPhase As input_fn dflags -- might be a hierarchical module. io $ createDirectoryHierarchy (takeDirectory output_fn) - let md_c_flags = machdepCCOpts dflags io $ SysTools.runAs dflags (map SysTools.Option as_opts ++ [ SysTools.Option ("-I" ++ p) | p <- cmdline_include_paths ] -#ifdef sparc_TARGET_ARCH + -- We only support SparcV9 and better because V8 lacks an atomic CAS -- instruction so we have to make sure that the assembler accepts the -- instruction set. Note that the user can still override this @@ -1190,14 +1182,15 @@ runPhase As input_fn dflags -- regardless of the ordering. -- -- This is a temporary hack. - ++ [ SysTools.Option "-mcpu=v9" ] -#endif + ++ (if cTargetArch == Sparc + then [SysTools.Option "-mcpu=v9"] + else []) + ++ [ SysTools.Option "-c" , SysTools.FileOption "" input_fn , SysTools.Option "-o" , SysTools.FileOption "" output_fn - ] - ++ map SysTools.Option md_c_flags) + ]) return (next_phase, output_fn) @@ -1233,11 +1226,10 @@ runPhase SplitAs _input_fn dflags split_obj n = split_odir </> takeFileName base_o ++ "__" ++ show n <.> osuf - let md_c_flags = machdepCCOpts dflags let assemble_file n = SysTools.runAs dflags (map SysTools.Option as_opts ++ -#ifdef sparc_TARGET_ARCH + -- We only support SparcV9 and better because V8 lacks an atomic CAS -- instruction so we have to make sure that the assembler accepts the -- instruction set. Note that the user can still override this @@ -1245,14 +1237,15 @@ runPhase SplitAs _input_fn dflags -- regardless of the ordering. -- -- This is a temporary hack. - [ SysTools.Option "-mcpu=v9" ] ++ -#endif + (if cTargetArch == Sparc + then [SysTools.Option "-mcpu=v9"] + else []) ++ + [ SysTools.Option "-c" , SysTools.Option "-o" , SysTools.FileOption "" (split_obj n) , SysTools.FileOption "" (split_s n) - ] - ++ map SysTools.Option md_c_flags) + ]) io $ mapM_ assemble_file [1..n] @@ -1322,11 +1315,9 @@ runPhase LlvmLlc input_fn dflags = do let lc_opts = getOpts dflags opt_lc let opt_lvl = max 0 (min 2 $ optLevel dflags) -#if darwin_TARGET_OS - let nphase = LlvmMangle -#else - let nphase = As -#endif + let nphase = if cTargetOS == OSX + then LlvmMangle + else As let rmodel | opt_PIC = "pic" | not opt_Static = "dynamic-no-pic" | otherwise = "static" @@ -1342,11 +1333,9 @@ runPhase LlvmLlc input_fn dflags return (nphase, output_fn) where -#if darwin_TARGET_OS - llvmOpts = ["-O1", "-O2", "-O2"] -#else - llvmOpts = ["-O1", "-O2", "-O3"] -#endif + llvmOpts = if cTargetOS == OSX + then ["-O1", "-O2", "-O2"] + else ["-O1", "-O2", "-O3"] ----------------------------------------------------------------------------- @@ -1419,14 +1408,12 @@ mkExtraCObj dflags xs oFile <- newTempName dflags "o" writeFile cFile xs let rtsDetails = getPackageDetails (pkgState dflags) rtsPackageId - md_c_flags = machdepCCOpts dflags SysTools.runCc dflags ([Option "-c", FileOption "" cFile, Option "-o", FileOption "" oFile] ++ - map (FileOption "-I") (includeDirs rtsDetails) ++ - map Option md_c_flags) + map (FileOption "-I") (includeDirs rtsDetails)) return oFile mkExtraObjToLinkIntoBinary :: DynFlags -> [PackageId] -> IO FilePath @@ -1654,20 +1641,20 @@ linkBinary dflags o_files dep_packages = do rc_objs <- maybeCreateManifest dflags output_fn - let md_c_flags = machdepCCOpts dflags SysTools.runLink dflags ( map SysTools.Option verbFlags ++ [ SysTools.Option "-o" , SysTools.FileOption "" output_fn ] ++ map SysTools.Option ( - md_c_flags + [] -#ifdef mingw32_TARGET_OS -- Permit the linker to auto link _symbol to _imp_symbol. -- This lets us link against DLLs without needing an "import library". - ++ ["-Wl,--enable-auto-import"] -#endif + ++ (if cTargetOS == Windows + then ["-Wl,--enable-auto-import"] + else []) + ++ o_files ++ extra_ld_inputs ++ lib_path_opts @@ -1698,19 +1685,15 @@ linkBinary dflags o_files dep_packages = do exeFileName :: DynFlags -> FilePath exeFileName dflags | Just s <- outputFile dflags = -#if defined(mingw32_HOST_OS) - if null (takeExtension s) - then s <.> "exe" - else s -#else - s -#endif + if cTargetOS == Windows + then if null (takeExtension s) + then s <.> "exe" + else s + else s | otherwise = -#if defined(mingw32_HOST_OS) - "main.exe" -#else - "a.out" -#endif + if cTargetOS == Windows + then "main.exe" + else "a.out" maybeCreateManifest :: DynFlags @@ -1806,7 +1789,6 @@ linkDynLib dflags o_files dep_packages = do -- probably _stub.o files extra_ld_inputs <- readIORef v_Ld_inputs - let md_c_flags = machdepCCOpts dflags let extra_ld_opts = getOpts dflags opt_l extraLinkObj <- mkExtraObjToLinkIntoBinary dflags dep_packages @@ -1828,11 +1810,10 @@ linkDynLib dflags o_files dep_packages = do ] ++ map (SysTools.FileOption "") o_files ++ map SysTools.Option ( - md_c_flags -- Permit the linker to auto link _symbol to _imp_symbol -- This lets us link against DLLs without needing an "import library" - ++ ["-Wl,--enable-auto-import"] + ["-Wl,--enable-auto-import"] ++ extra_ld_inputs ++ lib_path_opts @@ -1884,8 +1865,7 @@ linkDynLib dflags o_files dep_packages = do , SysTools.FileOption "" output_fn ] ++ map SysTools.Option ( - md_c_flags - ++ o_files + o_files ++ [ "-undefined", "dynamic_lookup", "-single_module", #if !defined(x86_64_TARGET_ARCH) "-Wl,-read_only_relocs,suppress", @@ -1919,8 +1899,7 @@ linkDynLib dflags o_files dep_packages = do , SysTools.FileOption "" output_fn ] ++ map SysTools.Option ( - md_c_flags - ++ o_files + o_files ++ [ "-shared" ] ++ bsymbolicFlag -- Set the library soname. We use -h rather than -soname as @@ -1949,11 +1928,8 @@ doCpp dflags raw include_cc_opts input_fn output_fn = do let verbFlags = getVerbFlags dflags let cc_opts - | not include_cc_opts = [] - | otherwise = (optc ++ md_c_flags) - where - optc = getOpts dflags opt_c - md_c_flags = machdepCCOpts dflags + | include_cc_opts = getOpts dflags opt_c + | otherwise = [] let cpp_prog args | raw = SysTools.runCpp dflags args | otherwise = SysTools.runCc dflags (SysTools.Option "-E" : args) @@ -2005,7 +1981,6 @@ joinObjectFiles dflags o_files output_fn = do SysTools.Option ld_x_flag, SysTools.Option "-o", SysTools.FileOption "" output_fn ] - ++ map SysTools.Option md_c_flags ++ args) ld_x_flag | null cLD_X = "" @@ -2017,8 +1992,6 @@ joinObjectFiles dflags o_files output_fn = do ld_build_id | cLdHasBuildId == "YES" = "-Wl,--build-id=none" | otherwise = "" - md_c_flags = machdepCCOpts dflags - if cLdIsGNULd == "YES" then do script <- newTempName dflags "ldscript" diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 9b5670e526..ed64fd0ad9 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -60,7 +60,7 @@ module DynFlags ( supportedLanguagesAndExtensions, -- ** DynFlag C compiler options - machdepCCOpts, picCCOpts, + picCCOpts, -- * Configuration of the stg-to-stg passes StgToDo(..), @@ -77,9 +77,7 @@ module DynFlags ( #include "HsVersions.h" -#ifndef OMIT_NATIVE_CODEGEN import Platform -#endif import Module import PackageConfig import PrelNames ( mAIN ) @@ -110,7 +108,7 @@ import Data.Char import Data.List import Data.Map (Map) import qualified Data.Map as Map --- import Data.Maybe +import Distribution.System import System.FilePath import System.IO ( stderr, hPutChar ) @@ -403,9 +401,7 @@ data DynFlags = DynFlags { floatLamArgs :: Maybe Int, -- ^ Arg count for lambda floating -- See CoreMonad.FloatOutSwitches -#ifndef OMIT_NATIVE_CODEGEN - targetPlatform :: Platform, -- ^ The platform we're compiling for. Used by the NCG. -#endif + targetPlatform :: Platform.Platform, -- ^ The platform we're compiling for. Used by the NCG. cmdlineHcIncludes :: [String], -- ^ @\-\#includes@ importPaths :: [FilePath], mainModIs :: Module, @@ -631,6 +627,14 @@ data HscTarget | HscNothing -- ^ Don't generate any code. See notes above. deriving (Eq, Show) +showHscTargetFlag :: HscTarget -> String +showHscTargetFlag HscC = "-fvia-c" +showHscTargetFlag HscAsm = "-fasm" +showHscTargetFlag HscLlvm = "-fllvm" +showHscTargetFlag HscJava = panic "No flag for HscJava" +showHscTargetFlag HscInterpreted = "-fbyte-code" +showHscTargetFlag HscNothing = "-fno-code" + -- | Will this target result in an object file on the disk? isObjectTarget :: HscTarget -> Bool isObjectTarget HscC = True @@ -693,8 +697,9 @@ defaultHscTarget = defaultObjectTarget -- object files on the current platform. defaultObjectTarget :: HscTarget defaultObjectTarget + | cGhcUnregisterised == "YES" = HscC | cGhcWithNativeCodeGen == "YES" = HscAsm - | otherwise = HscC + | otherwise = HscLlvm data DynLibLoader = Deployable @@ -741,9 +746,7 @@ defaultDynFlags mySettings = floatLamArgs = Just 0, -- Default: float only if no fvs strictnessBefore = [], -#ifndef OMIT_NATIVE_CODEGEN targetPlatform = defaultTargetPlatform, -#endif cmdlineHcIncludes = [], importPaths = ["."], mainModIs = mAIN, @@ -1100,12 +1103,13 @@ parseDynamicFlags_ dflags0 args pkg_flags = do when (not (null errs)) $ ghcError $ errorsToGhcException errs let (pic_warns, dflags2) -#if !(x86_64_TARGET_ARCH && linux_TARGET_OS) - | (not opt_Static || opt_PIC) && hscTarget dflags1 == HscLlvm + | not (cTargetArch == X86_64 && cTargetOS == Linux) && + (not opt_Static || opt_PIC) && + hscTarget dflags1 == HscLlvm = ([L noSrcSpan $ "Warning: -fllvm is incompatible with -fPIC and -" - ++ "dynamic on this platform;\n ignoring -fllvm"], - dflags1{ hscTarget = HscAsm }) -#endif + ++ "dynamic on this platform;\n" + ++ " using " ++ showHscTargetFlag defaultObjectTarget ++ " instead"], + dflags1{ hscTarget = defaultObjectTarget }) | otherwise = ([], dflags1) return (dflags2, leftover, pic_warns ++ warns) @@ -1346,10 +1350,11 @@ dynamic_flags = [ , Flag "w" (NoArg (mapM_ unSetDynFlag minuswRemovesOpts)) ------ Optimisation flags ------------------------------------------ - , Flag "O" (noArg (setOptLevel 1)) - , Flag "Onot" (noArgDF (setOptLevel 0) "Use -O0 instead") - , Flag "Odph" (noArg setDPHOpt) - , Flag "O" (OptIntSuffix (\mb_n -> upd (setOptLevel (mb_n `orElse` 1)))) + , Flag "O" (noArgM (setOptLevel 1)) + , Flag "Onot" (noArgM (\dflags -> do deprecate "Use -O0 instead" + setOptLevel 0 dflags)) + , Flag "Odph" (noArgM setDPHOpt) + , Flag "O" (optIntSuffixM (\mb_n -> setOptLevel (mb_n `orElse` 1))) -- If the number is missing, use 1 , Flag "fsimplifier-phases" (intSuffix (\n d -> d{ simplPhases = n })) @@ -1907,13 +1912,21 @@ checkTemplateHaskellOk _ = return () type DynP = EwM (CmdLineP DynFlags) upd :: (DynFlags -> DynFlags) -> DynP () -upd f = liftEwM (do { dfs <- getCmdLineState - ; putCmdLineState $! (f dfs) }) +upd f = liftEwM (do dflags <- getCmdLineState + putCmdLineState $! f dflags) + +updM :: (DynFlags -> DynP DynFlags) -> DynP () +updM f = do dflags <- liftEwM getCmdLineState + dflags' <- f dflags + liftEwM $ putCmdLineState $! dflags' --------------- Constructor functions for OptKind ----------------- noArg :: (DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags) noArg fn = NoArg (upd fn) +noArgM :: (DynFlags -> DynP DynFlags) -> OptKind (CmdLineP DynFlags) +noArgM fn = NoArg (updM fn) + noArgDF :: (DynFlags -> DynFlags) -> String -> OptKind (CmdLineP DynFlags) noArgDF fn deprec = NoArg (upd fn >> deprecate deprec) @@ -1927,6 +1940,10 @@ hasArgDF fn deprec = HasArg (\s -> do { upd (fn s) intSuffix :: (Int -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags) intSuffix fn = IntSuffix (\n -> upd (fn n)) +optIntSuffixM :: (Maybe Int -> DynFlags -> DynP DynFlags) + -> OptKind (CmdLineP DynFlags) +optIntSuffixM fn = OptIntSuffix (\mi -> updM (fn mi)) + setDumpFlag :: DynFlag -> OptKind (CmdLineP DynFlags) setDumpFlag dump_flag = NoArg (setDumpFlag' dump_flag) @@ -2025,20 +2042,36 @@ setTarget l = upd set -- not from bytecode to object-code. The idea is that -fasm/-fllvm -- can be safely used in an OPTIONS_GHC pragma. setObjTarget :: HscTarget -> DynP () -setObjTarget l = upd set +setObjTarget l = updM set where - set dfs - | isObjectTarget (hscTarget dfs) = dfs { hscTarget = l } - | otherwise = dfs - -setOptLevel :: Int -> DynFlags -> DynFlags + set dflags + | isObjectTarget (hscTarget dflags) + = case l of + HscC + | cGhcUnregisterised /= "YES" -> + do addWarn ("Compiler not unregisterised, so ignoring " ++ + showHscTargetFlag l) + return dflags + HscAsm + | cGhcWithNativeCodeGen /= "YES" -> + do addWarn ("Compiler has no native codegen, so ignoring " ++ + showHscTargetFlag l) + return dflags + HscLlvm + | cGhcUnregisterised == "YES" -> + do addWarn ("Compiler unregisterised, so ignoring " ++ + showHscTargetFlag l) + return dflags + _ -> return $ dflags { hscTarget = l } + | otherwise = return dflags + +setOptLevel :: Int -> DynFlags -> DynP DynFlags setOptLevel n dflags | hscTarget dflags == HscInterpreted && n > 0 - = dflags - -- not in IO any more, oh well: - -- putStr "warning: -O conflicts with --interactive; -O ignored.\n" + = do addWarn "-O conflicts with --interactive; -O ignored." + return dflags | otherwise - = updOptLevel n dflags + = return (updOptLevel n dflags) -- -Odph is equivalent to @@ -2047,7 +2080,7 @@ setOptLevel n dflags -- -fmax-simplifier-iterations20 this is necessary sometimes -- -fsimplifier-phases=3 we use an additional simplifier phase for fusion -- -setDPHOpt :: DynFlags -> DynFlags +setDPHOpt :: DynFlags -> DynP DynFlags setDPHOpt dflags = setOptLevel 2 (dflags { maxSimplIterations = 20 , simplPhases = 3 }) @@ -2203,37 +2236,6 @@ setOptHpcDir arg = upd $ \ d -> d{hpcDir = arg} -- The options below are not dependent on the version of gcc, only the -- platform. -machdepCCOpts :: DynFlags -> [String] -- flags for all C compilations -machdepCCOpts _ = cCcOpts ++ machdepCCOpts' - -machdepCCOpts' :: [String] -- flags for all C compilations -machdepCCOpts' -#if alpha_TARGET_ARCH - = ["-w", "-mieee" -#ifdef HAVE_THREADED_RTS_SUPPORT - , "-D_REENTRANT" -#endif - ] - -- For now, to suppress the gcc warning "call-clobbered - -- register used for global register variable", we simply - -- disable all warnings altogether using the -w flag. Oh well. - -#elif hppa_TARGET_ARCH - -- ___HPUX_SOURCE, not _HPUX_SOURCE, is #defined if -ansi! - -- (very nice, but too bad the HP /usr/include files don't agree.) - = ["-D_HPUX_SOURCE"] - -#elif i386_TARGET_ARCH - -- -fno-defer-pop : basically the same game as for m68k - -- - -- -fomit-frame-pointer : *must* in .hc files; because we're stealing - -- the fp (%ebp) for our register maps. - = if opt_Static then ["-DDONT_WANT_WIN32_DLL_SUPPORT"] else [] - -#else - = [] -#endif - picCCOpts :: DynFlags -> [String] picCCOpts _dflags #if darwin_TARGET_OS @@ -2303,7 +2305,6 @@ compilerInfo dflags ("Debug on", show debugIsOn), ("LibDir", topDir dflags), ("Global Package DB", systemPackageConfig dflags), - ("C compiler flags", show cCcOpts), ("Gcc Linker flags", show cGccLinkerOpts), ("Ld Linker flags", show cLdLinkerOpts) ] diff --git a/compiler/main/SysTools.lhs b/compiler/main/SysTools.lhs index 2529dbff48..97a6514746 100644 --- a/compiler/main/SysTools.lhs +++ b/compiler/main/SysTools.lhs @@ -182,6 +182,9 @@ initSysTools mbMinusB -- to make that possible, so for now you can't. ; gcc_prog <- if isWindowsHost then return $ installed_mingw_bin "gcc" else getSetting "C compiler command" + ; gcc_args_str <- if isWindowsHost then return [] + else getSetting "C compiler flags" + ; let gcc_args = map Option (words gcc_args_str) ; perl_path <- if isWindowsHost then return $ installed_perl_bin "perl" else getSetting "perl command" @@ -224,12 +227,16 @@ initSysTools mbMinusB -- cpp is derived from gcc on all platforms -- HACK, see setPgmP below. We keep 'words' here to remember to fix -- Config.hs one day. - ; let cpp_path = (gcc_prog, - (Option "-E"):(map Option (words cRAWCPP_FLAGS))) + ; let cpp_prog = gcc_prog + cpp_args = Option "-E" + : map Option (words cRAWCPP_FLAGS) + ++ gcc_args -- Other things being equal, as and ld are simply gcc ; let as_prog = gcc_prog + as_args = gcc_args ld_prog = gcc_prog + ld_args = gcc_args -- figure out llvm location. (TODO: Acutally implement). ; let lc_prog = "llc" @@ -244,12 +251,12 @@ initSysTools mbMinusB sExtraGccViaCFlags = words myExtraGccViaCFlags, sSystemPackageConfig = pkgconfig_path, sPgm_L = unlit_path, - sPgm_P = cpp_path, + sPgm_P = (cpp_prog, cpp_args), sPgm_F = "", - sPgm_c = (gcc_prog,[]), + sPgm_c = (gcc_prog, gcc_args), sPgm_s = (split_prog,split_args), - sPgm_a = (as_prog,[]), - sPgm_l = (ld_prog,[]), + sPgm_a = (as_prog, as_args), + sPgm_l = (ld_prog, ld_args), sPgm_dll = (mkdll_prog,mkdll_args), sPgm_T = touch_path, sPgm_sysman = top_dir ++ "/ghc/rts/parallel/SysMan", |
