merge upstream HEAD
[ghc-hetmet.git] / compiler / main / DynFlags.hs
index fa92d57..70358ee 100644 (file)
@@ -32,7 +32,7 @@ module DynFlags (
         Option(..), showOpt,
         DynLibLoader(..),
         fFlags, fLangFlags, xFlags,
         Option(..), showOpt,
         DynLibLoader(..),
         fFlags, fLangFlags, xFlags,
-        dphPackage,
+        DPHBackend(..), dphPackageMaybe,
         wayNames,
 
         -- ** Manipulating DynFlags
         wayNames,
 
         -- ** Manipulating DynFlags
@@ -40,7 +40,7 @@ module DynFlags (
         initDynFlags,                   -- DynFlags -> IO DynFlags
 
         getOpts,                        -- DynFlags -> (DynFlags -> [a]) -> [a]
         initDynFlags,                   -- DynFlags -> IO DynFlags
 
         getOpts,                        -- DynFlags -> (DynFlags -> [a]) -> [a]
-        getVerbFlag,
+        getVerbFlags,
         updOptLevel,
         setTmpDir,
         setPackageName,
         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.List
 import Data.Map (Map)
 import qualified Data.Map as Map
+import Data.Maybe
 import System.FilePath
 import System.IO        ( stderr, hPutChar )
 
 import System.FilePath
 import System.IO        ( stderr, hPutChar )
 
@@ -112,6 +113,7 @@ data DynFlag
 
    -- debugging flags
    = Opt_D_dump_cmm
 
    -- 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
    | 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_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
    | Opt_D_dump_cpranal
    | Opt_D_dump_deriv
    | Opt_D_dump_ds
@@ -133,6 +136,7 @@ data DynFlag
    | Opt_D_dump_foreign
    | Opt_D_dump_inlinings
    | Opt_D_dump_rule_firings
    | Opt_D_dump_foreign
    | Opt_D_dump_inlinings
    | Opt_D_dump_rule_firings
+   | Opt_D_dump_rule_rewrites
    | Opt_D_dump_occur_anal
    | Opt_D_dump_parsed
    | Opt_D_dump_rn
    | Opt_D_dump_occur_anal
    | Opt_D_dump_parsed
    | Opt_D_dump_rn
@@ -152,8 +156,10 @@ data DynFlag
    | Opt_D_dump_rn_stats
    | Opt_D_dump_opt_cmm
    | Opt_D_dump_simpl_stats
    | 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_tc_trace
    | Opt_D_dump_if_trace
+   | Opt_D_dump_vt_trace
    | Opt_D_dump_splices
    | Opt_D_dump_BCOs
    | Opt_D_dump_vect
    | Opt_D_dump_splices
    | Opt_D_dump_BCOs
    | Opt_D_dump_vect
@@ -175,11 +181,16 @@ data DynFlag
    | Opt_DoCmmLinting
    | Opt_DoAsmLinting
 
    | 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_WarnIsError                    -- -Werror; makes warnings fatal
    | Opt_WarnDuplicateExports
    | Opt_WarnHiShadows
    | Opt_WarnImplicitPrelude
    | Opt_WarnIncompletePatterns
+   | Opt_WarnIncompleteUniPatterns
    | Opt_WarnIncompletePatternsRecUpd
    | Opt_WarnMissingFields
    | Opt_WarnMissingImportList
    | Opt_WarnIncompletePatternsRecUpd
    | Opt_WarnMissingFields
    | Opt_WarnMissingImportList
@@ -199,6 +210,7 @@ data DynFlag
    | Opt_WarnDodgyImports
    | Opt_WarnOrphans
    | Opt_WarnAutoOrphans
    | Opt_WarnDodgyImports
    | Opt_WarnOrphans
    | Opt_WarnAutoOrphans
+   | Opt_WarnIdentities
    | Opt_WarnTabs
    | Opt_WarnUnrecognisedPragmas
    | Opt_WarnDodgyForeignImports
    | Opt_WarnTabs
    | Opt_WarnUnrecognisedPragmas
    | Opt_WarnDodgyForeignImports
@@ -223,7 +235,7 @@ data DynFlag
    | Opt_DoEtaReduction
    | Opt_CaseMerge
    | Opt_UnboxStrictFields
    | Opt_DoEtaReduction
    | Opt_CaseMerge
    | Opt_UnboxStrictFields
-   | Opt_MethodSharing
+   | Opt_MethodSharing -- Now a no-op; remove in GHC 7.2
    | Opt_DictsCheap
    | Opt_EnableRewriteRules            -- Apply rewrite rules during simplification
    | Opt_Vectorise
    | Opt_DictsCheap
    | Opt_EnableRewriteRules            -- Apply rewrite rules during simplification
    | Opt_Vectorise
@@ -244,7 +256,6 @@ data DynFlag
    | Opt_Pp
    | Opt_ForceRecomp
    | Opt_DryRun
    | Opt_Pp
    | Opt_ForceRecomp
    | Opt_DryRun
-   | Opt_DoAsmMangling
    | Opt_ExcessPrecision
    | Opt_EagerBlackHoling
    | Opt_ReadUserPackageConf
    | Opt_ExcessPrecision
    | Opt_EagerBlackHoling
    | Opt_ReadUserPackageConf
@@ -267,6 +278,7 @@ data DynFlag
    | Opt_BuildingCabalPackage
    | Opt_SSE2
    | Opt_GhciSandbox
    | Opt_BuildingCabalPackage
    | Opt_SSE2
    | Opt_GhciSandbox
+   | Opt_HelpfulErrors
 
        -- temporary flags
    | Opt_RunCPS
 
        -- temporary flags
    | Opt_RunCPS
@@ -280,7 +292,6 @@ data DynFlag
    | Opt_KeepHiDiffs
    | Opt_KeepHcFiles
    | Opt_KeepSFiles
    | Opt_KeepHiDiffs
    | Opt_KeepHcFiles
    | Opt_KeepSFiles
-   | Opt_KeepRawSFiles
    | Opt_KeepTmpFiles
    | Opt_KeepRawTokenStream
    | Opt_KeepLlvmFiles
    | Opt_KeepTmpFiles
    | Opt_KeepRawTokenStream
    | Opt_KeepLlvmFiles
@@ -302,8 +313,9 @@ data ExtensionFlag
    | Opt_ForeignFunctionInterface
    | Opt_UnliftedFFITypes
    | Opt_GHCForeignImportPrim
    | Opt_ForeignFunctionInterface
    | Opt_UnliftedFFITypes
    | Opt_GHCForeignImportPrim
-   | Opt_PArr                           -- Syntactic support for parallel arrays
+   | Opt_ParallelArrays                 -- Syntactic support for parallel arrays
    | Opt_Arrows                         -- Arrow-notation syntax
    | Opt_Arrows                         -- Arrow-notation syntax
+   | Opt_ModalTypes                     -- Heterogeneous Metaprogramming (modal types, brackets, escape, CSP)
    | Opt_TemplateHaskell
    | Opt_QuasiQuotes
    | Opt_ImplicitParams
    | Opt_TemplateHaskell
    | Opt_QuasiQuotes
    | Opt_ImplicitParams
@@ -319,6 +331,7 @@ data ExtensionFlag
    | Opt_RecordPuns
    | Opt_ViewPatterns
    | Opt_GADTs
    | Opt_RecordPuns
    | Opt_ViewPatterns
    | Opt_GADTs
+   | Opt_GADTSyntax
    | Opt_NPlusKPatterns
    | Opt_DoAndIfThenElse
    | Opt_RebindableSyntax
    | Opt_NPlusKPatterns
    | Opt_DoAndIfThenElse
    | Opt_RebindableSyntax
@@ -355,11 +368,12 @@ data ExtensionFlag
    | Opt_ImpredicativeTypes
    | Opt_TypeOperators
    | Opt_PackageImports
    | Opt_ImpredicativeTypes
    | Opt_TypeOperators
    | Opt_PackageImports
-   | Opt_NewQualifiedOperators
    | Opt_ExplicitForAll
    | Opt_AlternativeLayoutRule
    | Opt_AlternativeLayoutRuleTransitional
    | Opt_DatatypeContexts
    | Opt_ExplicitForAll
    | Opt_AlternativeLayoutRule
    | Opt_AlternativeLayoutRuleTransitional
    | Opt_DatatypeContexts
+   | Opt_NondecreasingIndentation
+   | Opt_RelaxedLayout
    deriving (Eq, Show)
 
 -- | Contains not only a collection of 'DynFlag's but also a plethora of
    deriving (Eq, Show)
 
 -- | Contains not only a collection of 'DynFlag's but also a plethora of
@@ -381,11 +395,12 @@ data DynFlags = DynFlags {
   specConstrThreshold   :: Maybe Int,   -- ^ Threshold for SpecConstr
   specConstrCount       :: Maybe Int,   -- ^ Max number of specialisations for any one function
   liberateCaseThreshold :: Maybe Int,   -- ^ Threshold for LiberateCase
   specConstrThreshold   :: Maybe Int,   -- ^ Threshold for SpecConstr
   specConstrCount       :: Maybe Int,   -- ^ Max number of specialisations for any one function
   liberateCaseThreshold :: Maybe Int,   -- ^ Threshold for LiberateCase
+  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
 
 #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,
   cmdlineHcIncludes     :: [String],    -- ^ @\-\#includes@
   importPaths           :: [FilePath],
   mainModIs             :: Module,
@@ -456,7 +471,6 @@ data DynFlags = DynFlags {
   pgm_P                 :: (String,[Option]),
   pgm_F                 :: String,
   pgm_c                 :: (String,[Option]),
   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]),
   pgm_s                 :: (String,[Option]),
   pgm_a                 :: (String,[Option]),
   pgm_l                 :: (String,[Option]),
@@ -614,6 +628,7 @@ data DynLibLoader
   deriving Eq
 
 data RtsOptsEnabled = RtsOptsNone | RtsOptsSafeOnly | RtsOptsAll
   deriving Eq
 
 data RtsOptsEnabled = RtsOptsNone | RtsOptsSafeOnly | RtsOptsAll
+  deriving (Show)
 
 -- | Used by 'GHC.newSession' to partially initialize a new 'DynFlags' value
 initDynFlags :: DynFlags -> IO DynFlags
 
 -- | Used by 'GHC.newSession' to partially initialize a new 'DynFlags' value
 initDynFlags :: DynFlags -> IO DynFlags
@@ -649,19 +664,19 @@ defaultDynFlags =
         specConstrThreshold     = Just 200,
         specConstrCount         = Just 3,
         liberateCaseThreshold   = Just 200,
         specConstrThreshold     = Just 200,
         specConstrCount         = Just 3,
         liberateCaseThreshold   = Just 200,
+        floatLamArgs            = Just 0,      -- Default: float only if no fvs
         strictnessBefore        = [],
 
 #ifndef OMIT_NATIVE_CODEGEN
         targetPlatform          = defaultTargetPlatform,
 #endif
         strictnessBefore        = [],
 
 #ifndef OMIT_NATIVE_CODEGEN
         targetPlatform          = defaultTargetPlatform,
 #endif
-        stolen_x86_regs         = 4,
         cmdlineHcIncludes       = [],
         importPaths             = ["."],
         mainModIs               = mAIN,
         mainFunIs               = Nothing,
         ctxtStkDepth            = mAX_CONTEXT_REDUCTION_DEPTH,
 
         cmdlineHcIncludes       = [],
         importPaths             = ["."],
         mainModIs               = mAIN,
         mainFunIs               = Nothing,
         ctxtStkDepth            = mAX_CONTEXT_REDUCTION_DEPTH,
 
-        dphBackend              = DPHPar,
+        dphBackend              = DPHNone,
 
         thisPackage             = mainPackageId,
 
 
         thisPackage             = mainPackageId,
 
@@ -719,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_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",
         pgm_s                   = panic "defaultDynFlags: No pgm_s",
         pgm_a                   = panic "defaultDynFlags: No pgm_a",
         pgm_l                   = panic "defaultDynFlags: No pgm_l",
@@ -781,19 +795,31 @@ flattenExtensionFlags ml = foldr f defaultExtensionFlags
           defaultExtensionFlags = languageExtensions ml
 
 languageExtensions :: Maybe Language -> [ExtensionFlag]
           defaultExtensionFlags = languageExtensions ml
 
 languageExtensions :: Maybe Language -> [ExtensionFlag]
+
 languageExtensions Nothing
 languageExtensions Nothing
+    -- Nothing => the default case
     = Opt_MonoPatBinds   -- Experimentally, I'm making this non-standard
                          -- behaviour the default, to see if anyone notices
                          -- SLPJ July 06
       -- In due course I'd like Opt_MonoLocalBinds to be on by default
       -- But NB it's implied by GADTs etc
       -- SLPJ September 2010
     = Opt_MonoPatBinds   -- Experimentally, I'm making this non-standard
                          -- behaviour the default, to see if anyone notices
                          -- SLPJ July 06
       -- In due course I'd like Opt_MonoLocalBinds to be on by default
       -- But NB it's implied by GADTs etc
       -- SLPJ September 2010
+    : Opt_NondecreasingIndentation -- This has been on by default for some time
     : languageExtensions (Just Haskell2010)
     : languageExtensions (Just Haskell2010)
+
 languageExtensions (Just Haskell98)
     = [Opt_ImplicitPrelude,
        Opt_MonomorphismRestriction,
        Opt_NPlusKPatterns,
 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,
        Opt_MonomorphismRestriction,
 languageExtensions (Just Haskell2010)
     = [Opt_ImplicitPrelude,
        Opt_MonomorphismRestriction,
@@ -852,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
 
 -- | 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,
 
 setObjectDir, setHiDir, setStubDir, setOutputDir, setDylibInstallName,
          setObjectSuf, setHiSuf, setHcSuf, parseDynLibLoaderMode,
@@ -869,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
 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}
 
 setOutputDir  f = setObjectDir f . setHiDir f . setStubDir f
 setDylibInstallName  f d = d{ dylibInstallName = Just f}
 
@@ -1030,16 +1057,7 @@ parseDynamicFlags_ dflags0 args pkg_flags = do
           = runCmdLine (processArgs flag_spec args') dflags0
   when (not (null errs)) $ ghcError $ errorsToGhcException errs
 
           = 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)
   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 -"
 #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 -"
@@ -1088,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 "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,[])}))
   , 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,[])}))
@@ -1159,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-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
   , Flag "keep-llvm-file"   (NoArg (setDynFlag Opt_KeepLlvmFiles))
   , Flag "keep-llvm-files"  (NoArg (setDynFlag Opt_KeepLlvmFiles))
      -- This only makes sense as plural
@@ -1198,8 +1216,10 @@ dynamic_flags = [
   , Flag "dstg-stats"     (NoArg (setDynFlag Opt_StgStats))
 
   , Flag "ddump-cmm"               (setDumpFlag Opt_D_dump_cmm)
   , 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-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)
   , 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)
@@ -1220,6 +1240,7 @@ dynamic_flags = [
   , Flag "ddump-foreign"           (setDumpFlag Opt_D_dump_foreign)
   , Flag "ddump-inlinings"         (setDumpFlag Opt_D_dump_inlinings)
   , Flag "ddump-rule-firings"      (setDumpFlag Opt_D_dump_rule_firings)
   , Flag "ddump-foreign"           (setDumpFlag Opt_D_dump_foreign)
   , Flag "ddump-inlinings"         (setDumpFlag Opt_D_dump_inlinings)
   , Flag "ddump-rule-firings"      (setDumpFlag Opt_D_dump_rule_firings)
+  , Flag "ddump-rule-rewrites"     (setDumpFlag Opt_D_dump_rule_rewrites)
   , Flag "ddump-occur-anal"        (setDumpFlag Opt_D_dump_occur_anal)
   , Flag "ddump-parsed"            (setDumpFlag Opt_D_dump_parsed)
   , Flag "ddump-rn"                (setDumpFlag Opt_D_dump_rn)
   , Flag "ddump-occur-anal"        (setDumpFlag Opt_D_dump_occur_anal)
   , Flag "ddump-parsed"            (setDumpFlag Opt_D_dump_parsed)
   , Flag "ddump-rn"                (setDumpFlag Opt_D_dump_rn)
@@ -1237,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-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-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)
   , 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)
@@ -1264,11 +1287,16 @@ dynamic_flags = [
                                               setVerbosity (Just 2)))
   , Flag "dfaststring-stats"       (NoArg (setDynFlag Opt_D_faststring_stats))
 
                                               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 ---------------------------
 
         ------ 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 -------------------------------------------------
   , Flag "msse2"        (NoArg (setDynFlag Opt_SSE2))
 
      ------ Warning opts -------------------------------------------------
@@ -1298,6 +1326,8 @@ dynamic_flags = [
   , Flag "frule-check"                 (SepArg (\s -> upd (\d -> d{ ruleCheck = Just s })))
   , Flag "fcontext-stack"              (intSuffix (\n d -> d{ ctxtStkDepth = n }))
   , Flag "fstrictness-before"          (intSuffix (\n d -> d{ strictnessBefore = n : strictnessBefore d }))
   , Flag "frule-check"                 (SepArg (\s -> upd (\d -> d{ ruleCheck = Just s })))
   , Flag "fcontext-stack"              (intSuffix (\n d -> d{ ctxtStkDepth = n }))
   , Flag "fstrictness-before"          (intSuffix (\n d -> d{ strictnessBefore = n : strictnessBefore d }))
+  , Flag "ffloat-lam-args"             (intSuffix (\n d -> d{ floatLamArgs = Just n }))
+  , Flag "ffloat-all-lams"             (intSuffix (\n d -> d{ floatLamArgs = Nothing }))
 
         ------ Profiling ----------------------------------------------------
 
 
         ------ Profiling ----------------------------------------------------
 
@@ -1318,14 +1348,15 @@ dynamic_flags = [
   , Flag "fdph-seq"         (NoArg (setDPHBackend DPHSeq))
   , Flag "fdph-par"         (NoArg (setDPHBackend DPHPar))
   , Flag "fdph-this"        (NoArg (setDPHBackend DPHThis))
   , Flag "fdph-seq"         (NoArg (setDPHBackend DPHSeq))
   , Flag "fdph-par"         (NoArg (setDPHBackend DPHPar))
   , Flag "fdph-this"        (NoArg (setDPHBackend DPHThis))
+  , Flag "fdph-none"        (NoArg (setDPHBackend DPHNone))
 
         ------ Compiler flags -----------------------------------------------
 
   , Flag "fasm"             (NoArg (setObjTarget HscAsm))
 
         ------ 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 }
   , Flag "fllvm"            (NoArg (setObjTarget HscLlvm))
 
   , Flag "fno-code"         (NoArg (do upd $ \d -> d{ ghcLink=NoLink }
@@ -1335,13 +1366,13 @@ dynamic_flags = [
   , Flag "fglasgow-exts"    (NoArg (enableGlasgowExts >> deprecate "Use individual extensions instead"))
   , Flag "fno-glasgow-exts" (NoArg (disableGlasgowExts >> deprecate "Use individual extensions instead"))
  ]
   , Flag "fglasgow-exts"    (NoArg (enableGlasgowExts >> deprecate "Use individual extensions instead"))
   , Flag "fno-glasgow-exts" (NoArg (disableGlasgowExts >> deprecate "Use individual extensions instead"))
  ]
- ++ map (mkFlag True  "f"    setDynFlag  ) fFlags
- ++ map (mkFlag False "fno-" unSetDynFlag) fFlags
- ++ map (mkFlag True  "f"    setExtensionFlag  ) fLangFlags
- ++ map (mkFlag False "fno-" unSetExtensionFlag) fLangFlags
- ++ map (mkFlag True  "X"    setExtensionFlag  ) xFlags
- ++ map (mkFlag False "XNo"  unSetExtensionFlag) xFlags
- ++ map (mkFlag True  "X"    setLanguage) languageFlags
+ ++ map (mkFlag turnOn  "f"    setDynFlag  ) fFlags
+ ++ map (mkFlag turnOff "fno-" unSetDynFlag) fFlags
+ ++ map (mkFlag turnOn  "f"    setExtensionFlag  ) fLangFlags
+ ++ map (mkFlag turnOff "fno-" unSetExtensionFlag) fLangFlags
+ ++ map (mkFlag turnOn  "X"    setExtensionFlag  ) xFlags
+ ++ map (mkFlag turnOff "XNo"  unSetExtensionFlag) xFlags
+ ++ map (mkFlag turnOn  "X"    setLanguage) languageFlags
 
 package_flags :: [Flag (CmdLineP DynFlags)]
 package_flags = [
 
 package_flags :: [Flag (CmdLineP DynFlags)]
 package_flags = [
@@ -1358,37 +1389,39 @@ package_flags = [
                                                   ; deprecate "Use -package instead" }))
   ]
 
                                                   ; deprecate "Use -package instead" }))
   ]
 
-type FlagSpec flag 
-   = ( String  -- Flag in string form
-     , flag     -- Flag in internal form
-     , Bool -> DynP ())         -- Extra action to run when the flag is found
-                                -- Typically, emit a warning or error
-                                -- True  <=> we are turning the flag on
+type TurnOnFlag = Bool   -- True  <=> we are turning the flag on
                                 -- False <=> we are turning the flag off
                                 -- False <=> we are turning the flag off
+turnOn  :: TurnOnFlag; turnOn = True
+turnOff :: TurnOnFlag; turnOff = False
 
 
+type FlagSpec flag
+   = ( String  -- Flag in string form
+     , flag     -- Flag in internal form
+     , TurnOnFlag -> DynP ())    -- Extra action to run when the flag is found
+                                 -- Typically, emit a warning or error
 
 
-mkFlag :: Bool                  -- ^ True <=> it should be turned on
+mkFlag :: TurnOnFlag            -- ^ True <=> it should be turned on
        -> String                -- ^ The flag prefix
        -> (flag -> DynP ())    -- ^ What to do when the flag is found
        -> FlagSpec flag                -- ^ Specification of this particular flag
        -> Flag (CmdLineP DynFlags)
        -> String                -- ^ The flag prefix
        -> (flag -> DynP ())    -- ^ What to do when the flag is found
        -> FlagSpec flag                -- ^ Specification of this particular flag
        -> Flag (CmdLineP DynFlags)
-mkFlag turnOn flagPrefix f (name, flag, extra_action)
-    = Flag (flagPrefix ++ name) (NoArg (f flag >> extra_action turnOn))
+mkFlag turn_on flagPrefix f (name, flag, extra_action)
+    = Flag (flagPrefix ++ name) (NoArg (f flag >> extra_action turn_on))
 
 
-deprecatedForExtension :: String -> Bool -> DynP ()
+deprecatedForExtension :: String -> TurnOnFlag -> DynP ()
 deprecatedForExtension lang turn_on
     = deprecate ("use -X"  ++ flag ++ " or pragma {-# LANGUAGE " ++ flag ++ " #-} instead")
     where 
       flag | turn_on    = lang
            | otherwise = "No"++lang
 
 deprecatedForExtension lang turn_on
     = deprecate ("use -X"  ++ flag ++ " or pragma {-# LANGUAGE " ++ flag ++ " #-} instead")
     where 
       flag | turn_on    = lang
            | otherwise = "No"++lang
 
-useInstead :: String -> Bool -> DynP ()
+useInstead :: String -> TurnOnFlag -> DynP ()
 useInstead flag turn_on
   = deprecate ("Use -f" ++ no ++ flag ++ " instead")
   where
     no = if turn_on then "" else "no-"
 
 useInstead flag turn_on
   = deprecate ("Use -f" ++ no ++ flag ++ " instead")
   where
     no = if turn_on then "" else "no-"
 
-nop :: Bool -> DynP ()
+nop :: TurnOnFlag -> DynP ()
 nop _ = return ()
 
 -- | These @-f\<blah\>@ flags can all be reversed with @-fno-\<blah\>@
 nop _ = return ()
 
 -- | These @-f\<blah\>@ flags can all be reversed with @-fno-\<blah\>@
@@ -1401,6 +1434,7 @@ fFlags = [
   ( "warn-hi-shadowing",                Opt_WarnHiShadows, nop ),
   ( "warn-implicit-prelude",            Opt_WarnImplicitPrelude, nop ),
   ( "warn-incomplete-patterns",         Opt_WarnIncompletePatterns, nop ),
   ( "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 ),
   ( "warn-incomplete-record-updates",   Opt_WarnIncompletePatternsRecUpd, nop ),
   ( "warn-missing-fields",              Opt_WarnMissingFields, nop ),
   ( "warn-missing-import-lists",        Opt_WarnMissingImportList, nop ),
@@ -1418,6 +1452,7 @@ fFlags = [
   ( "warn-deprecations",                Opt_WarnWarningsDeprecations, nop ),
   ( "warn-deprecated-flags",            Opt_WarnDeprecatedFlags, nop ),
   ( "warn-orphans",                     Opt_WarnOrphans, nop ),
   ( "warn-deprecations",                Opt_WarnWarningsDeprecations, nop ),
   ( "warn-deprecated-flags",            Opt_WarnDeprecatedFlags, nop ),
   ( "warn-orphans",                     Opt_WarnOrphans, nop ),
+  ( "warn-identities",                  Opt_WarnIdentities, nop ),
   ( "warn-auto-orphans",                Opt_WarnAutoOrphans, nop ),
   ( "warn-tabs",                        Opt_WarnTabs, nop ),
   ( "warn-unrecognised-pragmas",        Opt_WarnUnrecognisedPragmas, nop ),
   ( "warn-auto-orphans",                Opt_WarnAutoOrphans, nop ),
   ( "warn-tabs",                        Opt_WarnTabs, nop ),
   ( "warn-unrecognised-pragmas",        Opt_WarnUnrecognisedPragmas, nop ),
@@ -1442,11 +1477,12 @@ fFlags = [
   ( "do-eta-reduction",                 Opt_DoEtaReduction, nop ),
   ( "case-merge",                       Opt_CaseMerge, nop ),
   ( "unbox-strict-fields",              Opt_UnboxStrictFields, nop ),
   ( "do-eta-reduction",                 Opt_DoEtaReduction, nop ),
   ( "case-merge",                       Opt_CaseMerge, nop ),
   ( "unbox-strict-fields",              Opt_UnboxStrictFields, nop ),
-  ( "method-sharing",                   Opt_MethodSharing, nop ),
+  ( "method-sharing",                   Opt_MethodSharing, 
+     \_ -> deprecate "doesn't do anything any more"),
+     -- Remove altogether in GHC 7.2
   ( "dicts-cheap",                      Opt_DictsCheap, nop ),
   ( "excess-precision",                 Opt_ExcessPrecision, nop ),
   ( "eager-blackholing",                Opt_EagerBlackHoling, nop ),
   ( "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 ),
   ( "print-bind-result",                Opt_PrintBindResult, nop ),
   ( "force-recomp",                     Opt_ForceRecomp, nop ),
   ( "hpc-no-auto",                      Opt_Hpc_No_Auto, nop ),
@@ -1468,6 +1504,7 @@ fFlags = [
   ( "ext-core",                         Opt_EmitExternalCore, nop ),
   ( "shared-implib",                    Opt_SharedImplib, nop ),
   ( "ghci-sandbox",                     Opt_GhciSandbox, nop ),
   ( "ext-core",                         Opt_EmitExternalCore, nop ),
   ( "shared-implib",                    Opt_SharedImplib, nop ),
   ( "ghci-sandbox",                     Opt_GhciSandbox, nop ),
+  ( "helpful-errors",                   Opt_HelpfulErrors, nop ),
   ( "building-cabal-package",           Opt_BuildingCabalPackage, nop ),
   ( "implicit-import-qualified",        Opt_ImplicitImportQualified, nop )
   ]
   ( "building-cabal-package",           Opt_BuildingCabalPackage, nop ),
   ( "implicit-import-qualified",        Opt_ImplicitImportQualified, nop )
   ]
@@ -1499,8 +1536,10 @@ fLangFlags = [
     deprecatedForExtension "ImplicitParams" ),
   ( "scoped-type-variables",            Opt_ScopedTypeVariables,
     deprecatedForExtension "ScopedTypeVariables" ),
     deprecatedForExtension "ImplicitParams" ),
   ( "scoped-type-variables",            Opt_ScopedTypeVariables,
     deprecatedForExtension "ScopedTypeVariables" ),
-  ( "parr",                             Opt_PArr,
-    deprecatedForExtension "PArr" ),
+  ( "parr",                             Opt_ParallelArrays,
+    deprecatedForExtension "ParallelArrays" ),
+  ( "PArr",                             Opt_ParallelArrays,
+    deprecatedForExtension "ParallelArrays" ),
   ( "allow-overlapping-instances",      Opt_OverlappingInstances,
     deprecatedForExtension "OverlappingInstances" ),
   ( "allow-undecidable-instances",      Opt_UndecidableInstances,
   ( "allow-overlapping-instances",      Opt_OverlappingInstances,
     deprecatedForExtension "OverlappingInstances" ),
   ( "allow-undecidable-instances",      Opt_UndecidableInstances,
@@ -1552,7 +1591,8 @@ xFlags = [
     deprecatedForExtension "DoRec"),
   ( "DoRec",                            Opt_DoRec, nop ),
   ( "Arrows",                           Opt_Arrows, nop ),
     deprecatedForExtension "DoRec"),
   ( "DoRec",                            Opt_DoRec, nop ),
   ( "Arrows",                           Opt_Arrows, nop ),
-  ( "PArr",                             Opt_PArr, nop ),
+  ( "ModalTypes",                      Opt_ModalTypes, nop ),
+  ( "ParallelArrays",                   Opt_ParallelArrays, nop ),
   ( "TemplateHaskell",                  Opt_TemplateHaskell, checkTemplateHaskellOk ),
   ( "QuasiQuotes",                      Opt_QuasiQuotes, nop ),
   ( "Generics",                         Opt_Generics, nop ),
   ( "TemplateHaskell",                  Opt_TemplateHaskell, checkTemplateHaskellOk ),
   ( "QuasiQuotes",                      Opt_QuasiQuotes, nop ),
   ( "Generics",                         Opt_Generics, nop ),
@@ -1564,6 +1604,7 @@ xFlags = [
   ( "DisambiguateRecordFields",         Opt_DisambiguateRecordFields, nop ),
   ( "OverloadedStrings",                Opt_OverloadedStrings, nop ),
   ( "GADTs",                            Opt_GADTs, nop ),
   ( "DisambiguateRecordFields",         Opt_DisambiguateRecordFields, nop ),
   ( "OverloadedStrings",                Opt_OverloadedStrings, nop ),
   ( "GADTs",                            Opt_GADTs, nop ),
+  ( "GADTSyntax",                       Opt_GADTSyntax, nop ),
   ( "ViewPatterns",                     Opt_ViewPatterns, nop ),
   ( "TypeFamilies",                     Opt_TypeFamilies, nop ),
   ( "BangPatterns",                     Opt_BangPatterns, nop ),
   ( "ViewPatterns",                     Opt_ViewPatterns, nop ),
   ( "TypeFamilies",                     Opt_TypeFamilies, nop ),
   ( "BangPatterns",                     Opt_BangPatterns, nop ),
@@ -1576,6 +1617,8 @@ xFlags = [
   ( "AlternativeLayoutRule",            Opt_AlternativeLayoutRule, nop ),
   ( "AlternativeLayoutRuleTransitional",Opt_AlternativeLayoutRuleTransitional, nop ),
   ( "DatatypeContexts",                 Opt_DatatypeContexts, nop ),
   ( "AlternativeLayoutRule",            Opt_AlternativeLayoutRule, nop ),
   ( "AlternativeLayoutRuleTransitional",Opt_AlternativeLayoutRuleTransitional, nop ),
   ( "DatatypeContexts",                 Opt_DatatypeContexts, nop ),
+  ( "NondecreasingIndentation",         Opt_NondecreasingIndentation, nop ),
+  ( "RelaxedLayout",                    Opt_RelaxedLayout, nop ),
   ( "MonoLocalBinds",                   Opt_MonoLocalBinds, nop ),
   ( "RelaxedPolyRec",                   Opt_RelaxedPolyRec, 
     \ turn_on -> if not turn_on 
   ( "MonoLocalBinds",                   Opt_MonoLocalBinds, nop ),
   ( "RelaxedPolyRec",                   Opt_RelaxedPolyRec, 
     \ turn_on -> if not turn_on 
@@ -1604,9 +1647,7 @@ xFlags = [
   ( "OverlappingInstances",             Opt_OverlappingInstances, nop ),
   ( "UndecidableInstances",             Opt_UndecidableInstances, nop ),
   ( "IncoherentInstances",              Opt_IncoherentInstances, nop ),
   ( "OverlappingInstances",             Opt_OverlappingInstances, nop ),
   ( "UndecidableInstances",             Opt_UndecidableInstances, nop ),
   ( "IncoherentInstances",              Opt_IncoherentInstances, nop ),
-  ( "PackageImports",                   Opt_PackageImports, nop ),
-  ( "NewQualifiedOperators",            Opt_NewQualifiedOperators,
-    \_ -> deprecate "The new qualified operator syntax was rejected by Haskell'" )
+  ( "PackageImports",                   Opt_PackageImports, nop )
   ]
 
 defaultFlags :: [DynFlag]
   ]
 
 defaultFlags :: [DynFlag]
@@ -1614,16 +1655,17 @@ defaultFlags
   = [ Opt_AutoLinkPackages,
       Opt_ReadUserPackageConf,
 
   = [ Opt_AutoLinkPackages,
       Opt_ReadUserPackageConf,
 
-      Opt_MethodSharing,
-
-      Opt_DoAsmMangling,
-
       Opt_SharedImplib,
 
       Opt_SharedImplib,
 
+#if GHC_DEFAULT_NEW_CODEGEN
+      Opt_TryNewCodeGen,
+#endif
+
       Opt_GenManifest,
       Opt_EmbedManifest,
       Opt_PrintBindContents,
       Opt_GenManifest,
       Opt_EmbedManifest,
       Opt_PrintBindContents,
-      Opt_GhciSandbox
+      Opt_GhciSandbox,
+      Opt_HelpfulErrors
     ]
 
     ++ [f | (ns,f) <- optLevelFlags, 0 `elem` ns]
     ]
 
     ++ [f | (ns,f) <- optLevelFlags, 0 `elem` ns]
@@ -1631,30 +1673,40 @@ defaultFlags
 
     ++ standardWarnings
 
 
     ++ standardWarnings
 
-impliedFlags :: [(ExtensionFlag, ExtensionFlag)]
+impliedFlags :: [(ExtensionFlag, TurnOnFlag, ExtensionFlag)]
 impliedFlags
 impliedFlags
-  = [ (Opt_RankNTypes,                Opt_ExplicitForAll)
-    , (Opt_Rank2Types,                Opt_ExplicitForAll)
-    , (Opt_ScopedTypeVariables,       Opt_ExplicitForAll)
-    , (Opt_LiberalTypeSynonyms,       Opt_ExplicitForAll)
-    , (Opt_ExistentialQuantification, Opt_ExplicitForAll)
-    , (Opt_PolymorphicComponents,     Opt_ExplicitForAll)
-
-    , (Opt_RebindableSyntax,          Opt_ImplicitPrelude)
-
-    , (Opt_GADTs,                  Opt_MonoLocalBinds)
-    , (Opt_TypeFamilies,           Opt_MonoLocalBinds)
-
-    , (Opt_TypeFamilies,        Opt_KindSignatures)  -- Type families use kind signatures
+  = [ (Opt_RankNTypes,                turnOn, Opt_ExplicitForAll)
+    , (Opt_Rank2Types,                turnOn, Opt_ExplicitForAll)
+    , (Opt_ScopedTypeVariables,       turnOn, Opt_ExplicitForAll)
+    , (Opt_LiberalTypeSynonyms,       turnOn, Opt_ExplicitForAll)
+    , (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!
+
+    , (Opt_GADTs,            turnOn, Opt_GADTSyntax)
+    , (Opt_GADTs,            turnOn, Opt_MonoLocalBinds)
+    , (Opt_TypeFamilies,     turnOn, Opt_MonoLocalBinds)
+
+    , (Opt_TypeFamilies,     turnOn, Opt_KindSignatures)  -- Type families use kind signatures
                                                     -- all over the place
 
                                                     -- all over the place
 
-    , (Opt_ImpredicativeTypes,  Opt_RankNTypes)
+    , (Opt_ImpredicativeTypes,  turnOn, Opt_RankNTypes)
 
        -- Record wild-cards implies field disambiguation
        -- Otherwise if you write (C {..}) you may well get
        -- stuff like " 'a' not in scope ", which is a bit silly
        -- if the compiler has just filled in field 'a' of constructor 'C'
 
        -- Record wild-cards implies field disambiguation
        -- Otherwise if you write (C {..}) you may well get
        -- stuff like " 'a' not in scope ", which is a bit silly
        -- if the compiler has just filled in field 'a' of constructor 'C'
-    , (Opt_RecordWildCards,     Opt_DisambiguateRecordFields)
+    , (Opt_RecordWildCards,     turnOn, Opt_DisambiguateRecordFields)
+    
+    , (Opt_ParallelArrays, turnOn, Opt_ParallelListComp)
   ]
 
 optLevelFlags :: [([Int], DynFlag)]
   ]
 
 optLevelFlags :: [([Int], DynFlag)]
@@ -1713,6 +1765,7 @@ standardWarnings
       ]
 
 minusWOpts :: [DynFlag]
       ]
 
 minusWOpts :: [DynFlag]
+-- Things you get with -W
 minusWOpts
     = standardWarnings ++
       [ Opt_WarnUnusedBinds,
 minusWOpts
     = standardWarnings ++
       [ Opt_WarnUnusedBinds,
@@ -1724,6 +1777,7 @@ minusWOpts
       ]
 
 minusWallOpts :: [DynFlag]
       ]
 
 minusWallOpts :: [DynFlag]
+-- Things you get with -Wall
 minusWallOpts
     = minusWOpts ++
       [ Opt_WarnTypeDefaults,
 minusWallOpts
     = minusWOpts ++
       [ Opt_WarnTypeDefaults,
@@ -1734,17 +1788,18 @@ minusWallOpts
         Opt_WarnUnusedDoBind
       ]
 
         Opt_WarnUnusedDoBind
       ]
 
--- minuswRemovesOpts should be every warning option
 minuswRemovesOpts :: [DynFlag]
 minuswRemovesOpts :: [DynFlag]
+-- minuswRemovesOpts should be every warning option 
 minuswRemovesOpts
     = minusWallOpts ++
 minuswRemovesOpts
     = minusWallOpts ++
-      [Opt_WarnImplicitPrelude,
+      [Opt_WarnTabs,
        Opt_WarnIncompletePatternsRecUpd,
        Opt_WarnIncompletePatternsRecUpd,
+       Opt_WarnIncompleteUniPatterns,
        Opt_WarnMonomorphism,
        Opt_WarnUnrecognisedPragmas,
        Opt_WarnAutoOrphans,
        Opt_WarnMonomorphism,
        Opt_WarnUnrecognisedPragmas,
        Opt_WarnAutoOrphans,
-       Opt_WarnTabs
-      ]
+       Opt_WarnImplicitPrelude
+     ]       
 
 enableGlasgowExts :: DynP ()
 enableGlasgowExts = do setDynFlag Opt_PrintExplicitForalls
 
 enableGlasgowExts :: DynP ()
 enableGlasgowExts = do setDynFlag Opt_PrintExplicitForalls
@@ -1848,16 +1903,18 @@ unSetDynFlag f = upd (\dfs -> dopt_unset dfs f)
 --------------------------
 setExtensionFlag, unSetExtensionFlag :: ExtensionFlag -> DynP ()
 setExtensionFlag f = do { upd (\dfs -> xopt_set dfs f)
 --------------------------
 setExtensionFlag, unSetExtensionFlag :: ExtensionFlag -> DynP ()
 setExtensionFlag f = do { upd (\dfs -> xopt_set dfs f)
-                        ; mapM_ setExtensionFlag deps }
+                        ; sequence_ deps }
   where
   where
-    deps = [ d | (f', d) <- impliedFlags, f' == f ]
+    deps = [ if turn_on then setExtensionFlag   d
+                        else unSetExtensionFlag d
+           | (f', turn_on, d) <- impliedFlags, f' == f ]
         -- When you set f, set the ones it implies
         -- NB: use setExtensionFlag recursively, in case the implied flags
         --     implies further flags
         -- When you set f, set the ones it implies
         -- NB: use setExtensionFlag recursively, in case the implied flags
         --     implies further flags
-        -- When you un-set f, however, we don't un-set the things it implies
-        --      (except for -fno-glasgow-exts, which is treated specially)
 
 unSetExtensionFlag f = upd (\dfs -> xopt_unset dfs f)
 
 unSetExtensionFlag f = upd (\dfs -> xopt_unset dfs f)
+   -- When you un-set f, however, we don't un-set the things it implies
+   --      (except for -fno-glasgow-exts, which is treated specially)
 
 --------------------------
 setDumpFlag' :: DynFlag -> DynP ()
 
 --------------------------
 setDumpFlag' :: DynFlag -> DynP ()
@@ -1925,8 +1982,8 @@ setTarget l = upd set
      | otherwise = dfs
 
 -- Changes the target only if we're compiling object code.  This is
      | 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
 -- can be safely used in an OPTIONS_GHC pragma.
 setObjTarget :: HscTarget -> DynP ()
 setObjTarget l = upd set
@@ -1948,45 +2005,36 @@ setOptLevel n dflags
 -- -Odph is equivalent to
 --
 --    -O2                               optimise as much as possible
 -- -Odph is equivalent to
 --
 --    -O2                               optimise as much as possible
---    -fno-method-sharing               sharing specialisation defeats fusion
---                                      sometimes
---    -fdicts-cheap                     always inline dictionaries
 --    -fmax-simplifier-iterations20     this is necessary sometimes
 --    -fmax-simplifier-iterations20     this is necessary sometimes
---    -fsimplifier-phases=3             we use an additional simplifier phase
---                                      for fusion
---    -fno-spec-constr-threshold        run SpecConstr even for big loops
---    -fno-spec-constr-count            SpecConstr as much as possible
---    -finline-enough-args              hack to prevent excessive inlining
+--    -fsimplifier-phases=3             we use an additional simplifier phase for fusion
 --
 setDPHOpt :: DynFlags -> DynFlags
 setDPHOpt dflags = setOptLevel 2 (dflags { maxSimplIterations  = 20
                                          , simplPhases         = 3
 --
 setDPHOpt :: DynFlags -> DynFlags
 setDPHOpt dflags = setOptLevel 2 (dflags { maxSimplIterations  = 20
                                          , simplPhases         = 3
-                                         , specConstrThreshold = Nothing
-                                         , specConstrCount     = Nothing
                                          })
                                          })
-                   `dopt_set`   Opt_DictsCheap
-                   `dopt_unset` Opt_MethodSharing
 
 
-data DPHBackend = DPHPar
-                | DPHSeq
-                | DPHThis
+-- Determines the package used by the vectoriser for the symbols of the vectorised code.
+-- 'DPHNone' indicates that no data-parallel backend library is available; hence, the
+-- vectoriser cannot be used.
+--
+data DPHBackend = DPHPar    -- "dph-par"
+                | DPHSeq    -- "dph-seq"
+                | DPHThis   -- the currently compiled package
+                | DPHNone   -- no DPH library available
         deriving(Eq, Ord, Enum, Show)
 
 setDPHBackend :: DPHBackend -> DynP ()
         deriving(Eq, Ord, Enum, Show)
 
 setDPHBackend :: DPHBackend -> DynP ()
-setDPHBackend backend 
-  = do
-      upd $ \dflags -> dflags { dphBackend = backend }
-      mapM_ exposePackage (dph_packages backend)
-  where
-    dph_packages DPHThis = []
-    dph_packages DPHPar  = ["dph-prim-par", "dph-par"]
-    dph_packages DPHSeq  = ["dph-prim-seq", "dph-seq"]
+setDPHBackend backend = upd $ \dflags -> dflags { dphBackend = backend }
 
 
-dphPackage :: DynFlags -> PackageId
-dphPackage dflags = case dphBackend dflags of
-                      DPHPar  -> dphParPackageId
-                      DPHSeq  -> dphSeqPackageId
-                      DPHThis -> thisPackage dflags
+-- Query the DPH backend package to be used by the vectoriser and desugaring of DPH syntax.
+--
+dphPackageMaybe :: DynFlags -> Maybe PackageId
+dphPackageMaybe dflags 
+  = case dphBackend dflags of
+      DPHPar  -> Just dphParPackageId
+      DPHSeq  -> Just dphSeqPackageId
+      DPHThis -> Just (thisPackage dflags)
+      DPHNone -> Nothing
 
 setMainIs :: String -> DynP ()
 setMainIs arg
 
 setMainIs :: String -> DynP ()
 setMainIs arg
@@ -2117,20 +2165,17 @@ setOptHpcDir arg  = upd $ \ d -> d{hpcDir = arg}
 -- The options below are not dependent on the version of gcc, only the
 -- platform.
 
 -- 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
 #if alpha_TARGET_ARCH
-        =       ( ["-w", "-mieee"
+        =       ["-w", "-mieee"
 #ifdef HAVE_THREADED_RTS_SUPPORT
                     , "-D_REENTRANT"
 #endif
 #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.
         -- 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.
@@ -2138,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.)
 #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.
 
 #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
 #else
-        = ( [], [] )
+        = []
 #endif
 
 picCCOpts :: DynFlags -> [String]
 #endif
 
 picCCOpts :: DynFlags -> [String]
@@ -2242,7 +2233,7 @@ picCCOpts _dflags
 -- Splitting
 
 can_split :: Bool
 -- Splitting
 
 can_split :: Bool
-can_split = cSplitObjs == "YES"
+can_split = cSupportsSplitObjs == "YES"
 
 -- -----------------------------------------------------------------------------
 -- Compiler Info
 
 -- -----------------------------------------------------------------------------
 -- Compiler Info
@@ -2255,14 +2246,12 @@ compilerInfo = [("Project name",                String cProjectName),
                 ("Project version",             String cProjectVersion),
                 ("Booter version",              String cBooterVersion),
                 ("Stage",                       String cStage),
                 ("Project version",             String cProjectVersion),
                 ("Booter version",              String cBooterVersion),
                 ("Stage",                       String cStage),
-                ("Build platform",              String cBuildPlatform),
-                ("Host platform",               String cHostPlatform),
-                ("Target platform",             String cTargetPlatform),
+                ("Build platform",              String cBuildPlatformString),
+                ("Host platform",               String cHostPlatformString),
+                ("Target platform",             String cTargetPlatformString),
                 ("Have interpreter",            String cGhcWithInterpreter),
                 ("Have interpreter",            String cGhcWithInterpreter),
-                ("Object splitting",            String cSplitObjs),
+                ("Object splitting supported",  String cSupportsSplitObjs),
                 ("Have native code generator",  String cGhcWithNativeCodeGen),
                 ("Have native code generator",  String cGhcWithNativeCodeGen),
-                ("Have llvm code generator",    String cGhcWithLlvmCodeGen),
-                ("Use archives for ghci",       String (show cUseArchivesForGhci)),
                 ("Support SMP",                 String cGhcWithSMP),
                 ("Unregisterised",              String cGhcUnregisterised),
                 ("Tables next to code",         String cGhcEnableTablesNextToCode),
                 ("Support SMP",                 String cGhcWithSMP),
                 ("Unregisterised",              String cGhcUnregisterised),
                 ("Tables next to code",         String cGhcEnableTablesNextToCode),
@@ -2270,6 +2259,9 @@ compilerInfo = [("Project name",                String cProjectName),
                 ("Leading underscore",          String cLeadingUnderscore),
                 ("Debug on",                    String (show debugIsOn)),
                 ("LibDir",                      FromDynFlags topDir),
                 ("Leading underscore",          String cLeadingUnderscore),
                 ("Debug on",                    String (show debugIsOn)),
                 ("LibDir",                      FromDynFlags topDir),
-                ("Global Package DB",           FromDynFlags systemPackageConfig)
+                ("Global Package DB",           FromDynFlags systemPackageConfig),
+                ("C compiler flags",            String (show cCcOpts)),
+                ("Gcc Linker flags",            String (show cGccLinkerOpts)),
+                ("Ld Linker flags",             String (show cLdLinkerOpts))
                ]
 
                ]