Separate the language flags from the other DynFlag's
[ghc-hetmet.git] / compiler / main / DynFlags.hs
index 70b1355..3f5c4f1 100644 (file)
@@ -11,7 +11,9 @@
 -- flags.  Dynamic flags can also be set at the prompt in GHCi.
 module DynFlags (
         -- * Dynamic flags and associated configuration types
 -- flags.  Dynamic flags can also be set at the prompt in GHCi.
 module DynFlags (
         -- * Dynamic flags and associated configuration types
+        DOpt(..),
         DynFlag(..),
         DynFlag(..),
+        LanguageFlag(..),
         DynFlags(..),
         HscTarget(..), isObjectTarget, defaultObjectTarget,
         GhcMode(..), isOneShot,
         DynFlags(..),
         HscTarget(..), isObjectTarget, defaultObjectTarget,
         GhcMode(..), isOneShot,
@@ -19,7 +21,7 @@ module DynFlags (
         PackageFlag(..),
         Option(..), showOpt,
         DynLibLoader(..),
         PackageFlag(..),
         Option(..), showOpt,
         DynLibLoader(..),
-        fFlags, xFlags,
+        fFlags, fLangFlags, xFlags,
         dphPackage,
         wayNames,
 
         dphPackage,
         wayNames,
 
@@ -27,8 +29,6 @@ module DynFlags (
         defaultDynFlags,                -- DynFlags
         initDynFlags,                   -- DynFlags -> IO DynFlags
 
         defaultDynFlags,                -- DynFlags
         initDynFlags,                   -- DynFlags -> IO DynFlags
 
-        dopt,                           -- DynFlag -> DynFlags -> Bool
-        dopt_set, dopt_unset,           -- DynFlags -> DynFlag -> DynFlags
         getOpts,                        -- DynFlags -> (DynFlags -> [a]) -> [a]
         getVerbFlag,
         updOptLevel,
         getOpts,                        -- DynFlags -> (DynFlags -> [a]) -> [a]
         getVerbFlag,
         updOptLevel,
@@ -108,7 +108,6 @@ 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_llvm_opt
    | Opt_D_dump_cpranal
    | Opt_D_dump_deriv
    | Opt_D_dump_ds
    | Opt_D_dump_cpranal
    | Opt_D_dump_deriv
    | Opt_D_dump_ds
@@ -165,6 +164,7 @@ data DynFlag
    | Opt_WarnIncompletePatterns
    | Opt_WarnIncompletePatternsRecUpd
    | Opt_WarnMissingFields
    | Opt_WarnIncompletePatterns
    | Opt_WarnIncompletePatternsRecUpd
    | Opt_WarnMissingFields
+   | Opt_WarnMissingImportList
    | Opt_WarnMissingMethods
    | Opt_WarnMissingSigs
    | Opt_WarnNameShadowing
    | Opt_WarnMissingMethods
    | Opt_WarnMissingSigs
    | Opt_WarnNameShadowing
@@ -188,75 +188,6 @@ data DynFlag
    | Opt_WarnWrongDoBind
    | Opt_WarnAlternativeLayoutRuleTransitional
 
    | Opt_WarnWrongDoBind
    | Opt_WarnAlternativeLayoutRuleTransitional
 
-
-   -- language opts
-   | Opt_OverlappingInstances
-   | Opt_UndecidableInstances
-   | Opt_IncoherentInstances
-   | Opt_MonomorphismRestriction
-   | Opt_MonoPatBinds
-   | Opt_MonoLocalBinds
-   | Opt_ExtendedDefaultRules           -- Use GHC's extended rules for defaulting
-   | Opt_ForeignFunctionInterface
-   | Opt_UnliftedFFITypes
-   | Opt_GHCForeignImportPrim
-   | Opt_PArr                           -- Syntactic support for parallel arrays
-   | Opt_Arrows                         -- Arrow-notation syntax
-   | Opt_TemplateHaskell
-   | Opt_QuasiQuotes
-   | Opt_ImplicitParams
-   | Opt_Generics                      -- "Derivable type classes"
-   | Opt_ImplicitPrelude
-   | Opt_ScopedTypeVariables
-   | Opt_UnboxedTuples
-   | Opt_BangPatterns
-   | Opt_TypeFamilies
-   | Opt_OverloadedStrings
-   | Opt_DisambiguateRecordFields
-   | Opt_RecordWildCards
-   | Opt_RecordPuns
-   | Opt_ViewPatterns
-   | Opt_GADTs
-   | Opt_RelaxedPolyRec
-   | Opt_NPlusKPatterns
-
-   | Opt_StandaloneDeriving
-   | Opt_DeriveDataTypeable
-   | Opt_DeriveFunctor
-   | Opt_DeriveTraversable
-   | Opt_DeriveFoldable
-
-   | Opt_TypeSynonymInstances
-   | Opt_FlexibleContexts
-   | Opt_FlexibleInstances
-   | Opt_ConstrainedClassMethods
-   | Opt_MultiParamTypeClasses
-   | Opt_FunctionalDependencies
-   | Opt_UnicodeSyntax
-   | Opt_PolymorphicComponents
-   | Opt_ExistentialQuantification
-   | Opt_MagicHash
-   | Opt_EmptyDataDecls
-   | Opt_KindSignatures
-   | Opt_ParallelListComp
-   | Opt_TransformListComp
-   | Opt_GeneralizedNewtypeDeriving
-   | Opt_RecursiveDo
-   | Opt_DoRec
-   | Opt_PostfixOperators
-   | Opt_TupleSections
-   | Opt_PatternGuards
-   | Opt_LiberalTypeSynonyms
-   | Opt_Rank2Types
-   | Opt_RankNTypes
-   | Opt_ImpredicativeTypes
-   | Opt_TypeOperators
-   | Opt_PackageImports
-   | Opt_NewQualifiedOperators
-   | Opt_ExplicitForAll
-   | Opt_AlternativeLayoutRule
-   | Opt_AlternativeLayoutRuleTransitional
-
    | Opt_PrintExplicitForalls
 
    -- optimisation opts
    | Opt_PrintExplicitForalls
 
    -- optimisation opts
@@ -291,7 +222,6 @@ data DynFlag
    | Opt_AutoSccsOnIndividualCafs
 
    -- misc opts
    | Opt_AutoSccsOnIndividualCafs
 
    -- misc opts
-   | Opt_Cpp
    | Opt_Pp
    | Opt_ForceRecomp
    | Opt_DryRun
    | Opt_Pp
    | Opt_ForceRecomp
    | Opt_DryRun
@@ -338,6 +268,77 @@ data DynFlag
 
    deriving (Eq, Show)
 
 
    deriving (Eq, Show)
 
+data LanguageFlag
+   = Opt_Cpp
+   | Opt_OverlappingInstances
+   | Opt_UndecidableInstances
+   | Opt_IncoherentInstances
+   | Opt_MonomorphismRestriction
+   | Opt_MonoPatBinds
+   | Opt_MonoLocalBinds
+   | Opt_ExtendedDefaultRules           -- Use GHC's extended rules for defaulting
+   | Opt_ForeignFunctionInterface
+   | Opt_UnliftedFFITypes
+   | Opt_GHCForeignImportPrim
+   | Opt_PArr                           -- Syntactic support for parallel arrays
+   | Opt_Arrows                         -- Arrow-notation syntax
+   | Opt_TemplateHaskell
+   | Opt_QuasiQuotes
+   | Opt_ImplicitParams
+   | Opt_Generics                      -- "Derivable type classes"
+   | Opt_ImplicitPrelude
+   | Opt_ScopedTypeVariables
+   | Opt_UnboxedTuples
+   | Opt_BangPatterns
+   | Opt_TypeFamilies
+   | Opt_OverloadedStrings
+   | Opt_DisambiguateRecordFields
+   | Opt_RecordWildCards
+   | Opt_RecordPuns
+   | Opt_ViewPatterns
+   | Opt_GADTs
+   | Opt_RelaxedPolyRec
+   | Opt_NPlusKPatterns
+
+   | Opt_StandaloneDeriving
+   | Opt_DeriveDataTypeable
+   | Opt_DeriveFunctor
+   | Opt_DeriveTraversable
+   | Opt_DeriveFoldable
+
+   | Opt_TypeSynonymInstances
+   | Opt_FlexibleContexts
+   | Opt_FlexibleInstances
+   | Opt_ConstrainedClassMethods
+   | Opt_MultiParamTypeClasses
+   | Opt_FunctionalDependencies
+   | Opt_UnicodeSyntax
+   | Opt_PolymorphicComponents
+   | Opt_ExistentialQuantification
+   | Opt_MagicHash
+   | Opt_EmptyDataDecls
+   | Opt_KindSignatures
+   | Opt_ParallelListComp
+   | Opt_TransformListComp
+   | Opt_GeneralizedNewtypeDeriving
+   | Opt_RecursiveDo
+   | Opt_DoRec
+   | Opt_PostfixOperators
+   | Opt_TupleSections
+   | Opt_PatternGuards
+   | Opt_LiberalTypeSynonyms
+   | Opt_Rank2Types
+   | Opt_RankNTypes
+   | Opt_ImpredicativeTypes
+   | Opt_TypeOperators
+   | Opt_PackageImports
+   | Opt_NewQualifiedOperators
+   | Opt_ExplicitForAll
+   | Opt_AlternativeLayoutRule
+   | Opt_AlternativeLayoutRuleTransitional
+   | Opt_DatatypeContexts
+   deriving (Eq, Show)
+
 -- | Contains not only a collection of 'DynFlag's but also a plethora of
 -- information relating to the compilation of a single file or GHC session
 data DynFlags = DynFlags {
 -- | Contains not only a collection of 'DynFlag's but also a plethora of
 -- information relating to the compilation of a single file or GHC session
 data DynFlags = DynFlags {
@@ -423,7 +424,6 @@ data DynFlags = DynFlags {
   opt_a                 :: [String],
   opt_l                 :: [String],
   opt_windres           :: [String],
   opt_a                 :: [String],
   opt_l                 :: [String],
   opt_windres           :: [String],
-  opt_la                :: [String], -- LLVM: llvm-as assembler
   opt_lo                :: [String], -- LLVM: llvm optimiser
   opt_lc                :: [String], -- LLVM: llc static compiler
 
   opt_lo                :: [String], -- LLVM: llvm optimiser
   opt_lc                :: [String], -- LLVM: llc static compiler
 
@@ -440,7 +440,6 @@ data DynFlags = DynFlags {
   pgm_T                 :: String,
   pgm_sysman            :: String,
   pgm_windres           :: String,
   pgm_T                 :: String,
   pgm_sysman            :: String,
   pgm_windres           :: String,
-  pgm_la                :: (String,[Option]), -- LLVM: llvm-as assembler
   pgm_lo                :: (String,[Option]), -- LLVM: opt llvm optimiser
   pgm_lc                :: (String,[Option]), -- LLVM: llc static compiler
 
   pgm_lo                :: (String,[Option]), -- LLVM: opt llvm optimiser
   pgm_lc                :: (String,[Option]), -- LLVM: llc static compiler
 
@@ -474,6 +473,7 @@ data DynFlags = DynFlags {
 
   -- hsc dynamic flags
   flags                 :: [DynFlag],
 
   -- hsc dynamic flags
   flags                 :: [DynFlag],
+  languageFlags         :: [LanguageFlag],
 
   -- | Message output action: use "ErrUtils" instead of this if you can
   log_action            :: Severity -> SrcSpan -> PprStyle -> Message -> IO (),
 
   -- | Message output action: use "ErrUtils" instead of this if you can
   log_action            :: Severity -> SrcSpan -> PprStyle -> Message -> IO (),
@@ -667,7 +667,6 @@ defaultDynFlags =
         opt_m                   = [],
         opt_l                   = [],
         opt_windres             = [],
         opt_m                   = [],
         opt_l                   = [],
         opt_windres             = [],
-        opt_la                  = [],
         opt_lo                  = [],
         opt_lc                  = [],
 
         opt_lo                  = [],
         opt_lc                  = [],
 
@@ -696,7 +695,6 @@ defaultDynFlags =
         pgm_T                   = panic "defaultDynFlags: No pgm_T",
         pgm_sysman              = panic "defaultDynFlags: No pgm_sysman",
         pgm_windres             = panic "defaultDynFlags: No pgm_windres",
         pgm_T                   = panic "defaultDynFlags: No pgm_T",
         pgm_sysman              = panic "defaultDynFlags: No pgm_sysman",
         pgm_windres             = panic "defaultDynFlags: No pgm_windres",
-        pgm_la                  = panic "defaultDynFlags: No pgm_la",
         pgm_lo                  = panic "defaultDynFlags: No pgm_lo",
         pgm_lc                  = panic "defaultDynFlags: No pgm_lc",
         -- end of initSysTools values
         pgm_lo                  = panic "defaultDynFlags: No pgm_lo",
         pgm_lc                  = panic "defaultDynFlags: No pgm_lc",
         -- end of initSysTools values
@@ -713,14 +711,6 @@ defaultDynFlags =
             Opt_AutoLinkPackages,
             Opt_ReadUserPackageConf,
 
             Opt_AutoLinkPackages,
             Opt_ReadUserPackageConf,
 
-            Opt_MonoPatBinds,   -- Experimentally, I'm making this non-standard
-                                -- behaviour the default, to see if anyone notices
-                                -- SLPJ July 06
-
-            Opt_ImplicitPrelude,
-            Opt_MonomorphismRestriction,
-            Opt_NPlusKPatterns,
-
             Opt_MethodSharing,
 
             Opt_DoAsmMangling,
             Opt_MethodSharing,
 
             Opt_DoAsmMangling,
@@ -735,6 +725,17 @@ defaultDynFlags =
                     -- The default -O0 options
             ++ standardWarnings,
 
                     -- The default -O0 options
             ++ standardWarnings,
 
+        languageFlags = [
+            Opt_MonoPatBinds,   -- Experimentally, I'm making this non-standard
+                                -- behaviour the default, to see if anyone notices
+                                -- SLPJ July 06
+
+            Opt_ImplicitPrelude,
+            Opt_MonomorphismRestriction,
+            Opt_NPlusKPatterns,
+            Opt_DatatypeContexts
+            ],
+
         log_action = \severity srcSpan style msg ->
                         case severity of
                           SevInfo  -> printErrs (msg style)
         log_action = \severity srcSpan style msg ->
                         case severity of
                           SevInfo  -> printErrs (msg style)
@@ -758,17 +759,46 @@ Note [Verbosity levels]
     5   |   "ghc -v -ddump-all"
 -}
 
     5   |   "ghc -v -ddump-all"
 -}
 
+-- The DOpt class is a temporary workaround, to avoid having to do
+-- a mass-renaming dopt->lopt at the moment
+class DOpt a where
+    dopt :: a -> DynFlags -> Bool
+    dopt_set :: DynFlags -> a -> DynFlags
+    dopt_unset :: DynFlags -> a -> DynFlags
+
+instance DOpt DynFlag where
+    dopt = dopt'
+    dopt_set = dopt_set'
+    dopt_unset = dopt_unset'
+
+instance DOpt LanguageFlag where
+    dopt = lopt
+    dopt_set = lopt_set
+    dopt_unset = lopt_unset
+
 -- | Test whether a 'DynFlag' is set
 -- | Test whether a 'DynFlag' is set
-dopt :: DynFlag -> DynFlags -> Bool
-dopt f dflags  = f `elem` (flags dflags)
+dopt' :: DynFlag -> DynFlags -> Bool
+dopt' f dflags  = f `elem` (flags dflags)
 
 -- | Set a 'DynFlag'
 
 -- | Set a 'DynFlag'
-dopt_set :: DynFlags -> DynFlag -> DynFlags
-dopt_set dfs f = dfs{ flags = f : flags dfs }
+dopt_set' :: DynFlags -> DynFlag -> DynFlags
+dopt_set' dfs f = dfs{ flags = f : flags dfs }
 
 -- | Unset a 'DynFlag'
 
 -- | Unset a 'DynFlag'
-dopt_unset :: DynFlags -> DynFlag -> DynFlags
-dopt_unset dfs f = dfs{ flags = filter (/= f) (flags dfs) }
+dopt_unset' :: DynFlags -> DynFlag -> DynFlags
+dopt_unset' dfs f = dfs{ flags = filter (/= f) (flags dfs) }
+
+-- | Test whether a 'LanguageFlag' is set
+lopt :: LanguageFlag -> DynFlags -> Bool
+lopt f dflags  = f `elem` languageFlags dflags
+
+-- | Set a 'LanguageFlag'
+lopt_set :: DynFlags -> LanguageFlag -> DynFlags
+lopt_set dfs f = dfs{ languageFlags = f : languageFlags dfs }
+
+-- | Unset a 'LanguageFlag'
+lopt_unset :: DynFlags -> LanguageFlag -> DynFlags
+lopt_unset dfs f = dfs{ languageFlags = filter (/= f) (languageFlags dfs) }
 
 -- | Retrieve the options corresponding to a particular @opt_*@ field in the correct order
 getOpts :: DynFlags             -- ^ 'DynFlags' to retrieve the options from
 
 -- | Retrieve the options corresponding to a particular @opt_*@ field in the correct order
 getOpts :: DynFlags             -- ^ 'DynFlags' to retrieve the options from
@@ -787,9 +817,9 @@ getVerbFlag dflags
 setObjectDir, setHiDir, setStubDir, setOutputDir, setDylibInstallName,
          setObjectSuf, setHiSuf, setHcSuf, parseDynLibLoaderMode,
          setPgmP, setPgmL, setPgmF, setPgmc, setPgmm, setPgms, setPgma, setPgml, setPgmdll, setPgmwindres,
 setObjectDir, setHiDir, setStubDir, setOutputDir, setDylibInstallName,
          setObjectSuf, setHiSuf, setHcSuf, parseDynLibLoaderMode,
          setPgmP, setPgmL, setPgmF, setPgmc, setPgmm, setPgms, setPgma, setPgml, setPgmdll, setPgmwindres,
-         setPgmla, setPgmlo, setPgmlc,
-         addOptL, addOptP, addOptF, addOptc, addOptm, addOpta, addOptl, addOptwindres, addOptla, addOptlo,
-         addOptlc, addCmdlineFramework, addHaddockOpts
+         setPgmlo, setPgmlc,
+         addOptL, addOptP, addOptF, addOptc, addOptm, addOpta, addOptl, addOptwindres, addOptlo, addOptlc,
+         addCmdlineFramework, addHaddockOpts
    :: String -> DynFlags -> DynFlags
 setOutputFile, setOutputHi, setDumpPrefixForce
    :: Maybe String -> DynFlags -> DynFlags
    :: String -> DynFlags -> DynFlags
 setOutputFile, setOutputHi, setDumpPrefixForce
    :: Maybe String -> DynFlags -> DynFlags
@@ -833,7 +863,6 @@ setPgma   f d = d{ pgm_a   = (f,[])}
 setPgml   f d = d{ pgm_l   = (f,[])}
 setPgmdll f d = d{ pgm_dll = (f,[])}
 setPgmwindres f d = d{ pgm_windres = f}
 setPgml   f d = d{ pgm_l   = (f,[])}
 setPgmdll f d = d{ pgm_dll = (f,[])}
 setPgmwindres f d = d{ pgm_windres = f}
-setPgmla  f d = d{ pgm_la  = (f,[])}
 setPgmlo  f d = d{ pgm_lo  = (f,[])}
 setPgmlc  f d = d{ pgm_lc  = (f,[])}
 
 setPgmlo  f d = d{ pgm_lo  = (f,[])}
 setPgmlc  f d = d{ pgm_lc  = (f,[])}
 
@@ -845,7 +874,6 @@ addOptm   f d = d{ opt_m   = f : opt_m d}
 addOpta   f d = d{ opt_a   = f : opt_a d}
 addOptl   f d = d{ opt_l   = f : opt_l d}
 addOptwindres f d = d{ opt_windres = f : opt_windres d}
 addOpta   f d = d{ opt_a   = f : opt_a d}
 addOptl   f d = d{ opt_l   = f : opt_l d}
 addOptwindres f d = d{ opt_windres = f : opt_windres d}
-addOptla  f d = d{ opt_la  = f : opt_la d}
 addOptlo  f d = d{ opt_lo  = f : opt_lo d}
 addOptlc  f d = d{ opt_lc  = f : opt_lc d}
 
 addOptlo  f d = d{ opt_lo  = f : opt_lo d}
 addOptlc  f d = d{ opt_lc  = f : opt_lc d}
 
@@ -1027,15 +1055,17 @@ allFlags = map ('-':) $
            [ flagName flag | flag <- dynamic_flags, ok (flagOptKind flag) ] ++
            map ("fno-"++) flags ++
            map ("f"++) flags ++
            [ flagName flag | flag <- dynamic_flags, ok (flagOptKind flag) ] ++
            map ("fno-"++) flags ++
            map ("f"++) flags ++
+           map ("f"++) flags' ++
            map ("X"++) supportedLanguages
     where ok (PrefixPred _ _) = False
           ok _ = True
           flags = [ name | (name, _, _) <- fFlags ]
            map ("X"++) supportedLanguages
     where ok (PrefixPred _ _) = False
           ok _ = True
           flags = [ name | (name, _, _) <- fFlags ]
+          flags' = [ name | (name, _, _) <- fLangFlags ]
 
 dynamic_flags :: [Flag DynP]
 dynamic_flags = [
     Flag "n"              (NoArg  (setDynFlag Opt_DryRun)) Supported
 
 dynamic_flags :: [Flag DynP]
 dynamic_flags = [
     Flag "n"              (NoArg  (setDynFlag Opt_DryRun)) Supported
-  , Flag "cpp"            (NoArg  (setDynFlag Opt_Cpp)) Supported
+  , Flag "cpp"            (NoArg  (setLanguageFlag Opt_Cpp)) Supported
   , Flag "F"              (NoArg  (setDynFlag Opt_Pp)) Supported
   , Flag "#include"       (HasArg (addCmdlineHCInclude))
                              (DeprecatedFullText "-#include and INCLUDE pragmas are deprecated: They no longer have any effect")
   , Flag "F"              (NoArg  (setDynFlag Opt_Pp)) Supported
   , Flag "#include"       (HasArg (addCmdlineHCInclude))
                              (DeprecatedFullText "-#include and INCLUDE pragmas are deprecated: They no longer have any effect")
@@ -1043,7 +1073,6 @@ dynamic_flags = [
 
         ------- Specific phases  --------------------------------------------
     -- need to appear before -pgmL to be parsed as LLVM flags.
 
         ------- Specific phases  --------------------------------------------
     -- need to appear before -pgmL to be parsed as LLVM flags.
-  , Flag "pgmla"         (HasArg (upd . setPgmla)) Supported
   , Flag "pgmlo"         (HasArg (upd . setPgmlo)) Supported
   , Flag "pgmlc"         (HasArg (upd . setPgmlc)) Supported
 
   , Flag "pgmlo"         (HasArg (upd . setPgmlo)) Supported
   , Flag "pgmlc"         (HasArg (upd . setPgmlc)) Supported
 
@@ -1059,7 +1088,6 @@ dynamic_flags = [
   , Flag "pgmwindres"     (HasArg (upd . setPgmwindres)) Supported
 
     -- need to appear before -optl/-opta to be parsed as LLVM flags.
   , Flag "pgmwindres"     (HasArg (upd . setPgmwindres)) Supported
 
     -- need to appear before -optl/-opta to be parsed as LLVM flags.
-  , Flag "optla"          (HasArg (upd . addOptla)) Supported
   , Flag "optlo"          (HasArg (upd . addOptlo)) Supported
   , Flag "optlc"          (HasArg (upd . addOptlc)) Supported
 
   , Flag "optlo"          (HasArg (upd . addOptlo)) Supported
   , Flag "optlc"          (HasArg (upd . addOptlc)) Supported
 
@@ -1201,8 +1229,6 @@ dynamic_flags = [
   , Flag "ddump-llvm"              (NoArg (do { setObjTarget HscLlvm
                                               ; setDumpFlag' Opt_D_dump_llvm}))
          Supported
   , Flag "ddump-llvm"              (NoArg (do { setObjTarget HscLlvm
                                               ; setDumpFlag' Opt_D_dump_llvm}))
          Supported
-  , Flag "ddump-opt-llvm"          (setDumpFlag Opt_D_dump_llvm_opt)
-         Supported
   , Flag "ddump-cpranal"           (setDumpFlag Opt_D_dump_cpranal)
          Supported
   , Flag "ddump-deriv"             (setDumpFlag Opt_D_dump_deriv)
   , Flag "ddump-cpranal"           (setDumpFlag Opt_D_dump_cpranal)
          Supported
   , Flag "ddump-deriv"             (setDumpFlag Opt_D_dump_deriv)
@@ -1423,8 +1449,10 @@ dynamic_flags = [
         ------ Compiler flags -----------------------------------------------
 
   , Flag "fasm"             (NoArg (setObjTarget HscAsm)) Supported
         ------ Compiler flags -----------------------------------------------
 
   , Flag "fasm"             (NoArg (setObjTarget HscAsm)) Supported
-  , Flag "fvia-c"           (NoArg (setObjTarget HscC)) Supported
-  , Flag "fvia-C"           (NoArg (setObjTarget HscC)) Supported
+  , Flag "fvia-c"           (NoArg (setObjTarget HscC))
+         (Deprecated "The -fvia-c flag will be removed in a future GHC release")
+  , Flag "fvia-C"           (NoArg (setObjTarget HscC))
+         (Deprecated "The -fvia-C flag will be removed in a future GHC release")
   , Flag "fllvm"            (NoArg (setObjTarget HscLlvm)) Supported
 
   , Flag "fno-code"         (NoArg (do upd $ \d -> d{ ghcLink=NoLink }
   , Flag "fllvm"            (NoArg (setObjTarget HscLlvm)) Supported
 
   , Flag "fno-code"         (NoArg (do upd $ \d -> d{ ghcLink=NoLink }
@@ -1433,15 +1461,17 @@ dynamic_flags = [
   , Flag "fbyte-code"       (NoArg (setTarget HscInterpreted)) Supported
   , Flag "fobject-code"     (NoArg (setTarget defaultHscTarget)) Supported
 
   , Flag "fbyte-code"       (NoArg (setTarget HscInterpreted)) Supported
   , Flag "fobject-code"     (NoArg (setTarget defaultHscTarget)) Supported
 
-  , Flag "fglasgow-exts"    (NoArg (mapM_ setDynFlag   glasgowExtsFlags))
+  , Flag "fglasgow-exts"    (NoArg enableGlasgowExts)
          Supported
          Supported
-  , Flag "fno-glasgow-exts" (NoArg (mapM_ unSetDynFlag glasgowExtsFlags))
+  , Flag "fno-glasgow-exts" (NoArg disableGlasgowExts)
          Supported
  ]
  ++ map (mkFlag True  "f"    setDynFlag  ) fFlags
  ++ map (mkFlag False "fno-" unSetDynFlag) fFlags
          Supported
  ]
  ++ map (mkFlag True  "f"    setDynFlag  ) fFlags
  ++ map (mkFlag False "fno-" unSetDynFlag) fFlags
- ++ map (mkFlag True  "X"    setDynFlag  ) xFlags
- ++ map (mkFlag False "XNo"  unSetDynFlag) xFlags
+ ++ map (mkFlag True  "f"    setLanguageFlag  ) fLangFlags
+ ++ map (mkFlag False "fno-" unSetLanguageFlag) fLangFlags
+ ++ map (mkFlag True  "X"    setLanguageFlag  ) xFlags
+ ++ map (mkFlag False "XNo"  unSetLanguageFlag) xFlags
 
 package_flags :: [Flag DynP]
 package_flags = [
 
 package_flags :: [Flag DynP]
 package_flags = [
@@ -1463,11 +1493,11 @@ package_flags = [
 
 mkFlag :: Bool                  -- ^ True <=> it should be turned on
        -> String                -- ^ The flag prefix
 
 mkFlag :: Bool                  -- ^ True <=> it should be turned on
        -> String                -- ^ The flag prefix
-       -> (DynFlag -> DynP ())
-       -> (String, DynFlag, Bool -> Deprecated)
+       -> (flag -> DynP ())
+       -> (String, flag, Bool -> Deprecated)
        -> Flag DynP
        -> Flag DynP
-mkFlag turnOn flagPrefix f (name, dynflag, deprecated)
-    = Flag (flagPrefix ++ name) (NoArg (f dynflag)) (deprecated turnOn)
+mkFlag turnOn flagPrefix f (name, flag, deprecated)
+    = Flag (flagPrefix ++ name) (NoArg (f flag)) (deprecated turnOn)
 
 deprecatedForLanguage :: String -> Bool -> Deprecated
 deprecatedForLanguage lang turn_on
 
 deprecatedForLanguage :: String -> Bool -> Deprecated
 deprecatedForLanguage lang turn_on
@@ -1494,6 +1524,7 @@ fFlags = [
   ( "warn-incomplete-patterns",         Opt_WarnIncompletePatterns, const Supported ),
   ( "warn-incomplete-record-updates",   Opt_WarnIncompletePatternsRecUpd, const Supported ),
   ( "warn-missing-fields",              Opt_WarnMissingFields, const Supported ),
   ( "warn-incomplete-patterns",         Opt_WarnIncompletePatterns, const Supported ),
   ( "warn-incomplete-record-updates",   Opt_WarnIncompletePatternsRecUpd, const Supported ),
   ( "warn-missing-fields",              Opt_WarnMissingFields, const Supported ),
+  ( "warn-missing-import-lists",        Opt_WarnMissingImportList, const Supported ),
   ( "warn-missing-methods",             Opt_WarnMissingMethods, const Supported ),
   ( "warn-missing-signatures",          Opt_WarnMissingSigs, const Supported ),
   ( "warn-name-shadowing",              Opt_WarnNameShadowing, const Supported ),
   ( "warn-missing-methods",             Opt_WarnMissingMethods, const Supported ),
   ( "warn-missing-signatures",          Opt_WarnMissingSigs, const Supported ),
   ( "warn-name-shadowing",              Opt_WarnNameShadowing, const Supported ),
@@ -1553,6 +1584,17 @@ fFlags = [
   ( "vectorise",                        Opt_Vectorise, const Supported ),
   ( "regs-graph",                       Opt_RegsGraph, const Supported ),
   ( "regs-iterative",                   Opt_RegsIterative, const Supported ),
   ( "vectorise",                        Opt_Vectorise, const Supported ),
   ( "regs-graph",                       Opt_RegsGraph, const Supported ),
   ( "regs-iterative",                   Opt_RegsIterative, const Supported ),
+  ( "gen-manifest",                     Opt_GenManifest, const Supported ),
+  ( "embed-manifest",                   Opt_EmbedManifest, const Supported ),
+  ( "ext-core",                         Opt_EmitExternalCore, const Supported ),
+  ( "shared-implib",                    Opt_SharedImplib, const Supported ),
+  ( "building-cabal-package",           Opt_BuildingCabalPackage, const Supported ),
+  ( "implicit-import-qualified",        Opt_ImplicitImportQualified, const Supported )
+  ]
+
+-- | These @-f\<blah\>@ flags can all be reversed with @-fno-\<blah\>@
+fLangFlags :: [(String, LanguageFlag, Bool -> Deprecated)]
+fLangFlags = [
   ( "th",                               Opt_TemplateHaskell,
     deprecatedForLanguage "TemplateHaskell" ),
   ( "fi",                               Opt_ForeignFunctionInterface,
   ( "th",                               Opt_TemplateHaskell,
     deprecatedForLanguage "TemplateHaskell" ),
   ( "fi",                               Opt_ForeignFunctionInterface,
@@ -1584,24 +1626,18 @@ fFlags = [
   ( "allow-undecidable-instances",      Opt_UndecidableInstances,
     deprecatedForLanguage "UndecidableInstances" ),
   ( "allow-incoherent-instances",       Opt_IncoherentInstances,
   ( "allow-undecidable-instances",      Opt_UndecidableInstances,
     deprecatedForLanguage "UndecidableInstances" ),
   ( "allow-incoherent-instances",       Opt_IncoherentInstances,
-    deprecatedForLanguage "IncoherentInstances" ),
-  ( "gen-manifest",                     Opt_GenManifest, const Supported ),
-  ( "embed-manifest",                   Opt_EmbedManifest, const Supported ),
-  ( "ext-core",                         Opt_EmitExternalCore, const Supported ),
-  ( "shared-implib",                    Opt_SharedImplib, const Supported ),
-  ( "building-cabal-package",           Opt_BuildingCabalPackage, const Supported ),
-  ( "implicit-import-qualified",        Opt_ImplicitImportQualified, const Supported )
+    deprecatedForLanguage "IncoherentInstances" )
   ]
 
 supportedLanguages :: [String]
 supportedLanguages = [ name' | (name, _, _) <- xFlags, name' <- [name, "No" ++ name] ]
 
 -- This may contain duplicates
   ]
 
 supportedLanguages :: [String]
 supportedLanguages = [ name' | (name, _, _) <- xFlags, name' <- [name, "No" ++ name] ]
 
 -- This may contain duplicates
-languageOptions :: [DynFlag]
-languageOptions = [ dynFlag | (_, dynFlag, _) <- xFlags ]
+languageOptions :: [LanguageFlag]
+languageOptions = [ langFlag | (_, langFlag, _) <- xFlags ]
 
 -- | These -X<blah> flags can all be reversed with -XNo<blah>
 
 -- | These -X<blah> flags can all be reversed with -XNo<blah>
-xFlags :: [(String, DynFlag, Bool -> Deprecated)]
+xFlags :: [(String, LanguageFlag, Bool -> Deprecated)]
 xFlags = [
   ( "CPP",                              Opt_Cpp, const Supported ),
   ( "PostfixOperators",                 Opt_PostfixOperators, const Supported ),
 xFlags = [
   ( "CPP",                              Opt_Cpp, const Supported ),
   ( "PostfixOperators",                 Opt_PostfixOperators, const Supported ),
@@ -1653,6 +1689,8 @@ xFlags = [
   ( "ExplicitForAll",                   Opt_ExplicitForAll, const Supported ),
   ( "AlternativeLayoutRule",            Opt_AlternativeLayoutRule, const Supported ),
   ( "AlternativeLayoutRuleTransitional",Opt_AlternativeLayoutRuleTransitional, const Supported ),
   ( "ExplicitForAll",                   Opt_ExplicitForAll, const Supported ),
   ( "AlternativeLayoutRule",            Opt_AlternativeLayoutRule, const Supported ),
   ( "AlternativeLayoutRuleTransitional",Opt_AlternativeLayoutRuleTransitional, const Supported ),
+  -- On by default:
+  ( "DatatypeContexts",                 Opt_DatatypeContexts, const Supported ),
   ( "MonoLocalBinds",                   Opt_MonoLocalBinds, const Supported ),
   ( "RelaxedPolyRec",                   Opt_RelaxedPolyRec, const Supported ),
   ( "ExtendedDefaultRules",             Opt_ExtendedDefaultRules, const Supported ),
   ( "MonoLocalBinds",                   Opt_MonoLocalBinds, const Supported ),
   ( "RelaxedPolyRec",                   Opt_RelaxedPolyRec, const Supported ),
   ( "ExtendedDefaultRules",             Opt_ExtendedDefaultRules, const Supported ),
@@ -1679,10 +1717,11 @@ xFlags = [
   ( "UndecidableInstances",             Opt_UndecidableInstances, const Supported ),
   ( "IncoherentInstances",              Opt_IncoherentInstances, const Supported ),
   ( "PackageImports",                   Opt_PackageImports, const Supported ),
   ( "UndecidableInstances",             Opt_UndecidableInstances, const Supported ),
   ( "IncoherentInstances",              Opt_IncoherentInstances, const Supported ),
   ( "PackageImports",                   Opt_PackageImports, const Supported ),
-  ( "NewQualifiedOperators",            Opt_NewQualifiedOperators, const Supported )
+  ( "NewQualifiedOperators",            Opt_NewQualifiedOperators,
+    const $ Deprecated "The new qualified operator syntax was rejected by Haskell'" )
   ]
 
   ]
 
-impliedFlags :: [(DynFlag, DynFlag)]
+impliedFlags :: [(LanguageFlag, LanguageFlag)]
 impliedFlags
   = [ (Opt_RankNTypes,                Opt_ExplicitForAll)
     , (Opt_Rank2Types,                Opt_ExplicitForAll)
 impliedFlags
   = [ (Opt_RankNTypes,                Opt_ExplicitForAll)
     , (Opt_Rank2Types,                Opt_ExplicitForAll)
@@ -1709,10 +1748,17 @@ impliedFlags
     , (Opt_RecordWildCards,     Opt_DisambiguateRecordFields)
   ]
 
     , (Opt_RecordWildCards,     Opt_DisambiguateRecordFields)
   ]
 
-glasgowExtsFlags :: [DynFlag]
+enableGlasgowExts :: DynP ()
+enableGlasgowExts = do setDynFlag Opt_PrintExplicitForalls
+                       mapM_ setLanguageFlag glasgowExtsFlags
+
+disableGlasgowExts :: DynP ()
+disableGlasgowExts = do unSetDynFlag Opt_PrintExplicitForalls
+                        mapM_ unSetLanguageFlag glasgowExtsFlags
+
+glasgowExtsFlags :: [LanguageFlag]
 glasgowExtsFlags = [
 glasgowExtsFlags = [
-             Opt_PrintExplicitForalls
-           , Opt_ForeignFunctionInterface
+             Opt_ForeignFunctionInterface
            , Opt_UnliftedFFITypes
            , Opt_GADTs
            , Opt_ImplicitParams
            , Opt_UnliftedFFITypes
            , Opt_GADTs
            , Opt_ImplicitParams
@@ -1815,17 +1861,22 @@ upd f = do
 
 --------------------------
 setDynFlag, unSetDynFlag :: DynFlag -> DynP ()
 
 --------------------------
 setDynFlag, unSetDynFlag :: DynFlag -> DynP ()
-setDynFlag f = do { upd (\dfs -> dopt_set dfs f)
-                 ; mapM_ setDynFlag deps }
+setDynFlag f = upd (\dfs -> dopt_set dfs f)
+unSetDynFlag f = upd (\dfs -> dopt_unset dfs f)
+
+--------------------------
+setLanguageFlag, unSetLanguageFlag :: LanguageFlag -> DynP ()
+setLanguageFlag f = do { upd (\dfs -> lopt_set dfs f)
+                       ; mapM_ setLanguageFlag deps }
   where
     deps = [ d | (f', d) <- impliedFlags, f' == f ]
         -- When you set f, set the ones it implies
   where
     deps = [ d | (f', d) <- impliedFlags, f' == f ]
         -- When you set f, set the ones it implies
-       -- NB: use setDynFlag recursively, in case the implied flags
-       --     implies further flags
+        -- NB: use setLanguageFlag 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)
 
         -- When you un-set f, however, we don't un-set the things it implies
         --      (except for -fno-glasgow-exts, which is treated specially)
 
-unSetDynFlag f = upd (\dfs -> dopt_unset dfs f)
+unSetLanguageFlag f = upd (\dfs -> lopt_unset dfs f)
 
 --------------------------
 setDumpFlag :: DynFlag -> OptKind DynP
 
 --------------------------
 setDumpFlag :: DynFlag -> OptKind DynP
@@ -2204,6 +2255,11 @@ picCCOpts _dflags
     | otherwise
         = []
 #else
     | otherwise
         = []
 #else
+      -- we need -fPIC for C files when we are compiling with -dynamic,
+      -- otherwise things like stub.c files don't get compiled
+      -- correctly.  They need to reference data in the Haskell
+      -- objects, but can't without -fPIC.  See
+      -- http://hackage.haskell.org/trac/ghc/wiki/Commentary/PositionIndependentCode
     | opt_PIC || not opt_Static
         = ["-fPIC", "-U __PIC__", "-D__PIC__"]
     | otherwise
     | opt_PIC || not opt_Static
         = ["-fPIC", "-U __PIC__", "-D__PIC__"]
     | otherwise
@@ -2227,6 +2283,9 @@ 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),
                 ("Have interpreter",            String cGhcWithInterpreter),
                 ("Object splitting",            String cSplitObjs),
                 ("Have native code generator",  String cGhcWithNativeCodeGen),
                 ("Have interpreter",            String cGhcWithInterpreter),
                 ("Object splitting",            String cSplitObjs),
                 ("Have native code generator",  String cGhcWithNativeCodeGen),