merge upstream HEAD
[ghc-hetmet.git] / compiler / main / DynFlags.hs
index 854b83a..70358ee 100644 (file)
@@ -32,7 +32,7 @@ module DynFlags (
         Option(..), showOpt,
         DynLibLoader(..),
         fFlags, fLangFlags, xFlags,
-        DPHBackend(..), dphPackage,
+        DPHBackend(..), dphPackageMaybe,
         wayNames,
 
         -- ** Manipulating DynFlags
@@ -40,7 +40,7 @@ module DynFlags (
         initDynFlags,                   -- DynFlags -> IO DynFlags
 
         getOpts,                        -- DynFlags -> (DynFlags -> [a]) -> [a]
-        getVerbFlag,
+        getVerbFlags,
         updOptLevel,
         setTmpDir,
         setPackageName,
@@ -101,6 +101,7 @@ import Data.Char
 import Data.List
 import Data.Map (Map)
 import qualified Data.Map as Map
+import Data.Maybe
 import System.FilePath
 import System.IO        ( stderr, hPutChar )
 
@@ -112,6 +113,7 @@ data DynFlag
 
    -- debugging flags
    = Opt_D_dump_cmm
+   | Opt_D_dump_raw_cmm
    | Opt_D_dump_cmmz
    | Opt_D_dump_cmmz_pretty
    | Opt_D_dump_cps_cmm
@@ -126,6 +128,7 @@ data DynFlag
    | Opt_D_dump_asm_stats
    | Opt_D_dump_asm_expanded
    | Opt_D_dump_llvm
+   | Opt_D_dump_core_stats
    | Opt_D_dump_cpranal
    | Opt_D_dump_deriv
    | Opt_D_dump_ds
@@ -153,8 +156,10 @@ data DynFlag
    | Opt_D_dump_rn_stats
    | Opt_D_dump_opt_cmm
    | Opt_D_dump_simpl_stats
+   | Opt_D_dump_cs_trace       -- Constraint solver in type checker
    | Opt_D_dump_tc_trace
    | Opt_D_dump_if_trace
+   | Opt_D_dump_vt_trace
    | Opt_D_dump_splices
    | Opt_D_dump_BCOs
    | Opt_D_dump_vect
@@ -176,11 +181,16 @@ data DynFlag
    | Opt_DoCmmLinting
    | Opt_DoAsmLinting
 
+   | Opt_F_coqpass                      -- run the core-to-core   coqPass (does whatever CoqPass.hs says)
+   | Opt_D_coqpass                      -- run the core-to-string coqPass and dumps the result
+   | Opt_D_dump_coqpass                 -- dumps the output of the core-to-core coqPass
+
    | Opt_WarnIsError                    -- -Werror; makes warnings fatal
    | Opt_WarnDuplicateExports
    | Opt_WarnHiShadows
    | Opt_WarnImplicitPrelude
    | Opt_WarnIncompletePatterns
+   | Opt_WarnIncompleteUniPatterns
    | Opt_WarnIncompletePatternsRecUpd
    | Opt_WarnMissingFields
    | Opt_WarnMissingImportList
@@ -246,7 +256,6 @@ data DynFlag
    | Opt_Pp
    | Opt_ForceRecomp
    | Opt_DryRun
-   | Opt_DoAsmMangling
    | Opt_ExcessPrecision
    | Opt_EagerBlackHoling
    | Opt_ReadUserPackageConf
@@ -283,7 +292,6 @@ data DynFlag
    | Opt_KeepHiDiffs
    | Opt_KeepHcFiles
    | Opt_KeepSFiles
-   | Opt_KeepRawSFiles
    | Opt_KeepTmpFiles
    | Opt_KeepRawTokenStream
    | Opt_KeepLlvmFiles
@@ -307,6 +315,7 @@ data ExtensionFlag
    | Opt_GHCForeignImportPrim
    | Opt_ParallelArrays                 -- Syntactic support for parallel arrays
    | Opt_Arrows                         -- Arrow-notation syntax
+   | Opt_ModalTypes                     -- Heterogeneous Metaprogramming (modal types, brackets, escape, CSP)
    | Opt_TemplateHaskell
    | Opt_QuasiQuotes
    | Opt_ImplicitParams
@@ -392,7 +401,6 @@ data DynFlags = DynFlags {
 #ifndef OMIT_NATIVE_CODEGEN
   targetPlatform       :: Platform,    -- ^ The platform we're compiling for. Used by the NCG.
 #endif
-  stolen_x86_regs       :: Int,
   cmdlineHcIncludes     :: [String],    -- ^ @\-\#includes@
   importPaths           :: [FilePath],
   mainModIs             :: Module,
@@ -463,7 +471,6 @@ data DynFlags = DynFlags {
   pgm_P                 :: (String,[Option]),
   pgm_F                 :: String,
   pgm_c                 :: (String,[Option]),
-  pgm_m                 :: (String,[Option]),
   pgm_s                 :: (String,[Option]),
   pgm_a                 :: (String,[Option]),
   pgm_l                 :: (String,[Option]),
@@ -621,6 +628,7 @@ data DynLibLoader
   deriving Eq
 
 data RtsOptsEnabled = RtsOptsNone | RtsOptsSafeOnly | RtsOptsAll
+  deriving (Show)
 
 -- | Used by 'GHC.newSession' to partially initialize a new 'DynFlags' value
 initDynFlags :: DynFlags -> IO DynFlags
@@ -662,7 +670,6 @@ defaultDynFlags =
 #ifndef OMIT_NATIVE_CODEGEN
         targetPlatform          = defaultTargetPlatform,
 #endif
-        stolen_x86_regs         = 4,
         cmdlineHcIncludes       = [],
         importPaths             = ["."],
         mainModIs               = mAIN,
@@ -727,7 +734,6 @@ defaultDynFlags =
         pgm_P                   = panic "defaultDynFlags: No pgm_P",
         pgm_F                   = panic "defaultDynFlags: No pgm_F",
         pgm_c                   = panic "defaultDynFlags: No pgm_c",
-        pgm_m                   = panic "defaultDynFlags: No pgm_m",
         pgm_s                   = panic "defaultDynFlags: No pgm_s",
         pgm_a                   = panic "defaultDynFlags: No pgm_a",
         pgm_l                   = panic "defaultDynFlags: No pgm_l",
@@ -805,7 +811,14 @@ languageExtensions (Just Haskell98)
     = [Opt_ImplicitPrelude,
        Opt_MonomorphismRestriction,
        Opt_NPlusKPatterns,
-       Opt_DatatypeContexts]
+       Opt_DatatypeContexts,
+       Opt_NondecreasingIndentation
+           -- strictly speaking non-standard, but we always had this
+           -- on implicitly before the option was added in 7.1, and
+           -- turning it off breaks code, so we're keeping it on for
+           -- backwards compatibility.  Cabal uses -XHaskell98 by
+           -- default unless you specify another language.
+      ]
 
 languageExtensions (Just Haskell2010)
     = [Opt_ImplicitPrelude,
@@ -865,10 +878,10 @@ getOpts dflags opts = reverse (opts dflags)
 
 -- | Gets the verbosity flag for the current verbosity level. This is fed to
 -- other tools, so GHC-specific verbosity flags like @-ddump-most@ are not included
-getVerbFlag :: DynFlags -> String
-getVerbFlag dflags
-  | verbosity dflags >= 3  = "-v"
-  | otherwise =  ""
+getVerbFlags :: DynFlags -> [String]
+getVerbFlags dflags
+  | verbosity dflags >= 4 = ["-v"]
+  | otherwise             = []
 
 setObjectDir, setHiDir, setStubDir, setOutputDir, setDylibInstallName,
          setObjectSuf, setHiSuf, setHcSuf, parseDynLibLoaderMode,
@@ -882,7 +895,8 @@ setObjectDir  f d = d{ objectDir  = Just f}
 setHiDir      f d = d{ hiDir      = Just f}
 setStubDir    f d = d{ stubDir    = Just f, includePaths = f : includePaths d }
   -- -stubdir D adds an implicit -I D, so that gcc can find the _stub.h file
-  -- \#included from the .hc file when compiling with -fvia-C.
+  -- \#included from the .hc file when compiling via C (i.e. unregisterised
+  -- builds).
 setOutputDir  f = setObjectDir f . setHiDir f . setStubDir f
 setDylibInstallName  f d = d{ dylibInstallName = Just f}
 
@@ -1043,16 +1057,7 @@ parseDynamicFlags_ dflags0 args pkg_flags = do
           = runCmdLine (processArgs flag_spec args') dflags0
   when (not (null errs)) $ ghcError $ errorsToGhcException errs
 
-  -- Cannot use -fPIC with registerised -fvia-C, because the mangler
-  -- isn't up to the job.  We know that if hscTarget == HscC, then the
-  -- user has explicitly used -fvia-C, because -fasm is the default,
-  -- unless there is no NCG on this platform.  The latter case is
-  -- checked when the -fPIC flag is parsed.
-  --
   let (pic_warns, dflags2)
-        | opt_PIC && hscTarget dflags1 == HscC && cGhcUnregisterised == "NO"
-        = ([L noSrcSpan $ "Warning: -fvia-C is incompatible with -fPIC; ignoring -fvia-C"],
-                dflags1{ hscTarget = HscAsm })
 #if !(x86_64_TARGET_ARCH && linux_TARGET_OS)
         | (not opt_Static || opt_PIC) && hscTarget dflags1 == HscLlvm
         = ([L noSrcSpan $ "Warning: -fllvm is incompatible with -fPIC and -"
@@ -1101,7 +1106,7 @@ dynamic_flags = [
   , Flag "pgmP"           (hasArg setPgmP)
   , Flag "pgmF"           (hasArg (\f d -> d{ pgm_F   = f}))
   , Flag "pgmc"           (hasArg (\f d -> d{ pgm_c   = (f,[])}))
-  , Flag "pgmm"           (hasArg (\f d -> d{ pgm_m   = (f,[])}))
+  , Flag "pgmm"           (HasArg (\_ -> addWarn "The -keep-raw-s-files flag does nothing; it will be removed in a future GHC release"))
   , Flag "pgms"           (hasArg (\f d -> d{ pgm_s   = (f,[])}))
   , Flag "pgma"           (hasArg (\f d -> d{ pgm_a   = (f,[])}))
   , Flag "pgml"           (hasArg (\f d -> d{ pgm_l   = (f,[])}))
@@ -1172,8 +1177,8 @@ dynamic_flags = [
   , Flag "keep-hc-files"    (NoArg (setDynFlag Opt_KeepHcFiles))
   , Flag "keep-s-file"      (NoArg (setDynFlag Opt_KeepSFiles))
   , Flag "keep-s-files"     (NoArg (setDynFlag Opt_KeepSFiles))
-  , Flag "keep-raw-s-file"  (NoArg (setDynFlag Opt_KeepRawSFiles))
-  , Flag "keep-raw-s-files" (NoArg (setDynFlag Opt_KeepRawSFiles))
+  , Flag "keep-raw-s-file"  (NoArg (addWarn "The -keep-raw-s-file flag does nothing; it will be removed in a future GHC release"))
+  , Flag "keep-raw-s-files" (NoArg (addWarn "The -keep-raw-s-files flag does nothing; it will be removed in a future GHC release"))
   , Flag "keep-llvm-file"   (NoArg (setDynFlag Opt_KeepLlvmFiles))
   , Flag "keep-llvm-files"  (NoArg (setDynFlag Opt_KeepLlvmFiles))
      -- This only makes sense as plural
@@ -1211,8 +1216,10 @@ dynamic_flags = [
   , Flag "dstg-stats"     (NoArg (setDynFlag Opt_StgStats))
 
   , Flag "ddump-cmm"               (setDumpFlag Opt_D_dump_cmm)
+  , Flag "ddump-raw-cmm"           (setDumpFlag Opt_D_dump_raw_cmm)
   , Flag "ddump-cmmz"              (setDumpFlag Opt_D_dump_cmmz)
   , Flag "ddump-cmmz-pretty"       (setDumpFlag Opt_D_dump_cmmz_pretty)
+  , Flag "ddump-core-stats"        (setDumpFlag Opt_D_dump_core_stats)
   , Flag "ddump-cps-cmm"           (setDumpFlag Opt_D_dump_cps_cmm)
   , Flag "ddump-cvt-cmm"           (setDumpFlag Opt_D_dump_cvt_cmm)
   , Flag "ddump-asm"               (setDumpFlag Opt_D_dump_asm)
@@ -1251,7 +1258,9 @@ dynamic_flags = [
   , Flag "ddump-worker-wrapper"    (setDumpFlag Opt_D_dump_worker_wrapper)
   , Flag "ddump-rn-trace"          (setDumpFlag Opt_D_dump_rn_trace)
   , Flag "ddump-if-trace"          (setDumpFlag Opt_D_dump_if_trace)
+  , Flag "ddump-cs-trace"          (setDumpFlag Opt_D_dump_cs_trace)
   , Flag "ddump-tc-trace"          (setDumpFlag Opt_D_dump_tc_trace)
+  , Flag "ddump-vt-trace"          (setDumpFlag Opt_D_dump_vt_trace)
   , Flag "ddump-splices"           (setDumpFlag Opt_D_dump_splices)
   , Flag "ddump-rn-stats"          (setDumpFlag Opt_D_dump_rn_stats)
   , Flag "ddump-opt-cmm"           (setDumpFlag Opt_D_dump_opt_cmm)
@@ -1278,11 +1287,16 @@ dynamic_flags = [
                                               setVerbosity (Just 2)))
   , Flag "dfaststring-stats"       (NoArg (setDynFlag Opt_D_faststring_stats))
 
+        ------ Coq-in-GHC ---------------------------
+  , Flag "dcoqpass"                (NoArg (setDynFlag Opt_D_coqpass))
+  , Flag "ddump-coqpass"           (NoArg (setDynFlag Opt_D_dump_coqpass))
+  , Flag "fcoqpass"                (NoArg (setDynFlag Opt_F_coqpass))
+
         ------ Machine dependant (-m<blah>) stuff ---------------------------
 
-  , Flag "monly-2-regs" (noArg (\s -> s{stolen_x86_regs = 2}))
-  , Flag "monly-3-regs" (noArg (\s -> s{stolen_x86_regs = 3}))
-  , Flag "monly-4-regs" (noArg (\s -> s{stolen_x86_regs = 4}))
+  , Flag "monly-2-regs" (NoArg (addWarn "The -monly-2-regs flag does nothing; it will be removed in a future GHC release"))
+  , Flag "monly-3-regs" (NoArg (addWarn "The -monly-3-regs flag does nothing; it will be removed in a future GHC release"))
+  , Flag "monly-4-regs" (NoArg (addWarn "The -monly-4-regs flag does nothing; it will be removed in a future GHC release"))
   , Flag "msse2"        (NoArg (setDynFlag Opt_SSE2))
 
      ------ Warning opts -------------------------------------------------
@@ -1339,10 +1353,10 @@ dynamic_flags = [
         ------ Compiler flags -----------------------------------------------
 
   , Flag "fasm"             (NoArg (setObjTarget HscAsm))
-  , Flag "fvia-c"           (NoArg (setObjTarget HscC >>
-         (addWarn "The -fvia-c flag will be removed in a future GHC release")))
-  , Flag "fvia-C"           (NoArg (setObjTarget HscC >>
-         (addWarn "The -fvia-C flag will be removed in a future GHC release")))
+  , Flag "fvia-c"           (NoArg
+         (addWarn "The -fvia-c flag does nothing; it will be removed in a future GHC release"))
+  , Flag "fvia-C"           (NoArg
+         (addWarn "The -fvia-C flag does nothing; it will be removed in a future GHC release"))
   , Flag "fllvm"            (NoArg (setObjTarget HscLlvm))
 
   , Flag "fno-code"         (NoArg (do upd $ \d -> d{ ghcLink=NoLink }
@@ -1420,6 +1434,7 @@ fFlags = [
   ( "warn-hi-shadowing",                Opt_WarnHiShadows, nop ),
   ( "warn-implicit-prelude",            Opt_WarnImplicitPrelude, nop ),
   ( "warn-incomplete-patterns",         Opt_WarnIncompletePatterns, nop ),
+  ( "warn-incomplete-uni-patterns",     Opt_WarnIncompleteUniPatterns, nop ),
   ( "warn-incomplete-record-updates",   Opt_WarnIncompletePatternsRecUpd, nop ),
   ( "warn-missing-fields",              Opt_WarnMissingFields, nop ),
   ( "warn-missing-import-lists",        Opt_WarnMissingImportList, nop ),
@@ -1468,7 +1483,6 @@ fFlags = [
   ( "dicts-cheap",                      Opt_DictsCheap, nop ),
   ( "excess-precision",                 Opt_ExcessPrecision, nop ),
   ( "eager-blackholing",                Opt_EagerBlackHoling, nop ),
-  ( "asm-mangling",                     Opt_DoAsmMangling, nop ),
   ( "print-bind-result",                Opt_PrintBindResult, nop ),
   ( "force-recomp",                     Opt_ForceRecomp, nop ),
   ( "hpc-no-auto",                      Opt_Hpc_No_Auto, nop ),
@@ -1577,6 +1591,7 @@ xFlags = [
     deprecatedForExtension "DoRec"),
   ( "DoRec",                            Opt_DoRec, nop ),
   ( "Arrows",                           Opt_Arrows, nop ),
+  ( "ModalTypes",                      Opt_ModalTypes, nop ),
   ( "ParallelArrays",                   Opt_ParallelArrays, nop ),
   ( "TemplateHaskell",                  Opt_TemplateHaskell, checkTemplateHaskellOk ),
   ( "QuasiQuotes",                      Opt_QuasiQuotes, nop ),
@@ -1640,10 +1655,12 @@ defaultFlags
   = [ Opt_AutoLinkPackages,
       Opt_ReadUserPackageConf,
 
-      Opt_DoAsmMangling,
-
       Opt_SharedImplib,
 
+#if GHC_DEFAULT_NEW_CODEGEN
+      Opt_TryNewCodeGen,
+#endif
+
       Opt_GenManifest,
       Opt_EmbedManifest,
       Opt_PrintBindContents,
@@ -1665,6 +1682,12 @@ impliedFlags
     , (Opt_ExistentialQuantification, turnOn, Opt_ExplicitForAll)
     , (Opt_PolymorphicComponents,     turnOn, Opt_ExplicitForAll)
     , (Opt_FlexibleInstances,         turnOn, Opt_TypeSynonymInstances)
+    , (Opt_FunctionalDependencies,    turnOn, Opt_MultiParamTypeClasses)
+
+    , (Opt_ModalTypes,                 turnOn,  Opt_RankNTypes)
+    , (Opt_ModalTypes,                 turnOn,  Opt_ExplicitForAll)
+    --, (Opt_ModalTypes,                 turnOn,  Opt_RebindableSyntax)
+    , (Opt_ModalTypes,                 turnOff, Opt_MonomorphismRestriction)
 
     , (Opt_RebindableSyntax, turnOff, Opt_ImplicitPrelude)      -- NB: turn off!
 
@@ -1742,6 +1765,7 @@ standardWarnings
       ]
 
 minusWOpts :: [DynFlag]
+-- Things you get with -W
 minusWOpts
     = standardWarnings ++
       [ Opt_WarnUnusedBinds,
@@ -1753,6 +1777,7 @@ minusWOpts
       ]
 
 minusWallOpts :: [DynFlag]
+-- Things you get with -Wall
 minusWallOpts
     = minusWOpts ++
       [ Opt_WarnTypeDefaults,
@@ -1760,21 +1785,21 @@ minusWallOpts
         Opt_WarnMissingSigs,
         Opt_WarnHiShadows,
         Opt_WarnOrphans,
-        Opt_WarnUnusedDoBind,
-        Opt_WarnIdentities
+        Opt_WarnUnusedDoBind
       ]
 
--- minuswRemovesOpts should be every warning option
 minuswRemovesOpts :: [DynFlag]
+-- minuswRemovesOpts should be every warning option 
 minuswRemovesOpts
     = minusWallOpts ++
-      [Opt_WarnImplicitPrelude,
+      [Opt_WarnTabs,
        Opt_WarnIncompletePatternsRecUpd,
+       Opt_WarnIncompleteUniPatterns,
        Opt_WarnMonomorphism,
        Opt_WarnUnrecognisedPragmas,
        Opt_WarnAutoOrphans,
-       Opt_WarnTabs
-      ]
+       Opt_WarnImplicitPrelude
+     ]       
 
 enableGlasgowExts :: DynP ()
 enableGlasgowExts = do setDynFlag Opt_PrintExplicitForalls
@@ -1957,8 +1982,8 @@ setTarget l = upd set
      | otherwise = dfs
 
 -- Changes the target only if we're compiling object code.  This is
--- used by -fasm and -fvia-C, which switch from one to the other, but
--- not from bytecode to object-code.  The idea is that -fasm/-fvia-C
+-- used by -fasm and -fllvm, which switch from one to the other, but
+-- 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
@@ -2001,18 +2026,15 @@ data DPHBackend = DPHPar    -- "dph-par"
 setDPHBackend :: DPHBackend -> DynP ()
 setDPHBackend backend = upd $ \dflags -> dflags { dphBackend = backend }
 
--- Query the DPH backend package to be used by the vectoriser.
+-- Query the DPH backend package to be used by the vectoriser and desugaring of DPH syntax.
 --
-dphPackage :: DynFlags -> PackageId
-dphPackage dflags 
+dphPackageMaybe :: DynFlags -> Maybe PackageId
+dphPackageMaybe dflags 
   = case dphBackend dflags of
-      DPHPar  -> dphParPackageId
-      DPHSeq  -> dphSeqPackageId
-      DPHThis -> thisPackage dflags
-      DPHNone -> ghcError (CmdLineError dphBackendError)
-
-dphBackendError :: String
-dphBackendError = "To use -fvectorise select a DPH backend with -fdph-par or -fdph-seq"
+      DPHPar  -> Just dphParPackageId
+      DPHSeq  -> Just dphSeqPackageId
+      DPHThis -> Just (thisPackage dflags)
+      DPHNone -> Nothing
 
 setMainIs :: String -> DynP ()
 setMainIs arg
@@ -2143,20 +2165,17 @@ 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
-                              [String]) -- for registerised HC compilations
-machdepCCOpts dflags = let (flagsAll, flagsRegHc) = machdepCCOpts' dflags
-                       in (cCcOpts ++ flagsAll, flagsRegHc)
+machdepCCOpts :: DynFlags -> [String] -- flags for all C compilations
+machdepCCOpts dflags = cCcOpts ++ machdepCCOpts'
 
-machdepCCOpts' :: DynFlags -> ([String], -- flags for all C compilations
-                               [String]) -- for registerised HC compilations
-machdepCCOpts' _dflags
+machdepCCOpts' :: [String] -- flags for all C compilations
+machdepCCOpts'
 #if alpha_TARGET_ARCH
-        =       ( ["-w", "-mieee"
+        =       ["-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.
@@ -2164,71 +2183,17 @@ machdepCCOpts' _dflags
 #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 m68k_TARGET_ARCH
-      -- -fno-defer-pop : for the .hc files, we want all the pushing/
-      --    popping of args to routines to be explicit; if we let things
-      --    be deferred 'til after an STGJUMP, imminent death is certain!
-      --
-      -- -fomit-frame-pointer : *don't*
-      --     It's better to have a6 completely tied up being a frame pointer
-      --     rather than let GCC pick random things to do with it.
-      --     (If we want to steal a6, then we would try to do things
-      --     as on iX86, where we *do* steal the frame pointer [%ebp].)
-        = ( [], ["-fno-defer-pop", "-fno-omit-frame-pointer"] )
+        = ["-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.
-        =  let n_regs = stolen_x86_regs _dflags
-           in
-                    (
-                      [ if opt_Static then "-DDONT_WANT_WIN32_DLL_SUPPORT" else ""
-                      ],
-                      [ "-fno-defer-pop",
-                        "-fomit-frame-pointer",
-                        -- we want -fno-builtin, because when gcc inlines
-                        -- built-in functions like memcpy() it tends to
-                        -- run out of registers, requiring -monly-n-regs
-                        "-fno-builtin",
-                        "-DSTOLEN_X86_REGS="++show n_regs ]
-                    )
-
-#elif ia64_TARGET_ARCH
-        = ( [], ["-fomit-frame-pointer", "-G0"] )
-
-#elif x86_64_TARGET_ARCH
-        = (
-                [],
-                ["-fomit-frame-pointer",
-                 "-fno-asynchronous-unwind-tables",
-                        -- the unwind tables are unnecessary for HC code,
-                        -- and get in the way of -split-objs.  Another option
-                        -- would be to throw them away in the mangler, but this
-                        -- is easier.
-                 "-fno-builtin"
-                        -- calling builtins like strlen() using the FFI can
-                        -- cause gcc to run out of regs, so use the external
-                        -- version.
-                ] )
-
-#elif sparc_TARGET_ARCH
-        = ( [], ["-w"] )
-        -- 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.
+        =  if opt_Static then ["-DDONT_WANT_WIN32_DLL_SUPPORT"] else []
 
-#elif powerpc_apple_darwin_TARGET
-      -- -no-cpp-precomp:
-      --     Disable Apple's precompiling preprocessor. It's a great thing
-      --     for "normal" programs, but it doesn't support register variable
-      --     declarations.
-        = ( [], ["-no-cpp-precomp"] )
 #else
-        = ( [], [] )
+        = []
 #endif
 
 picCCOpts :: DynFlags -> [String]
@@ -2268,7 +2233,7 @@ picCCOpts _dflags
 -- Splitting
 
 can_split :: Bool
-can_split = cSplitObjs == "YES"
+can_split = cSupportsSplitObjs == "YES"
 
 -- -----------------------------------------------------------------------------
 -- Compiler Info
@@ -2285,7 +2250,7 @@ compilerInfo = [("Project name",                String cProjectName),
                 ("Host platform",               String cHostPlatformString),
                 ("Target platform",             String cTargetPlatformString),
                 ("Have interpreter",            String cGhcWithInterpreter),
-                ("Object splitting",            String cSplitObjs),
+                ("Object splitting supported",  String cSupportsSplitObjs),
                 ("Have native code generator",  String cGhcWithNativeCodeGen),
                 ("Support SMP",                 String cGhcWithSMP),
                 ("Unregisterised",              String cGhcUnregisterised),
@@ -2296,6 +2261,7 @@ compilerInfo = [("Project name",                String cProjectName),
                 ("LibDir",                      FromDynFlags topDir),
                 ("Global Package DB",           FromDynFlags systemPackageConfig),
                 ("C compiler flags",            String (show cCcOpts)),
-                ("Linker flags",                String (show cLdOpts))
+                ("Gcc Linker flags",            String (show cGccLinkerOpts)),
+                ("Ld Linker flags",             String (show cLdLinkerOpts))
                ]