Expose the dph packages automatically if -dph-* is set
[ghc-hetmet.git] / compiler / main / DynFlags.hs
index 3e030f2..3d17361 100644 (file)
@@ -1,19 +1,17 @@
 
 
------------------------------------------------------------------------------
---
+-- |
 -- Dynamic flags
 --
 -- Dynamic flags
 --
--- Most flags are dynamic flags, which means they can change from
--- compilation to compilation using OPTIONS_GHC pragmas, and in a
--- multi-session GHC each session can be using different dynamic
--- flags.  Dynamic flags can also be set at the prompt in GHCi.
 --
 -- (c) The University of Glasgow 2005
 --
 --
 -- (c) The University of Glasgow 2005
 --
------------------------------------------------------------------------------
 
 
+-- Most flags are dynamic flags, which means they can change from
+-- compilation to compilation using @OPTIONS_GHC@ pragmas, and in a
+-- multi-session GHC each session can be using different dynamic
+-- flags.  Dynamic flags can also be set at the prompt in GHCi.
 module DynFlags (
 module DynFlags (
-        -- Dynamic flags
+        -- * Dynamic flags and associated configuration types
         DynFlag(..),
         DynFlags(..),
         HscTarget(..), isObjectTarget, defaultObjectTarget,
         DynFlag(..),
         DynFlags(..),
         HscTarget(..), isObjectTarget, defaultObjectTarget,
@@ -25,40 +23,50 @@ module DynFlags (
         fFlags, xFlags,
         DPHBackend(..),
 
         fFlags, xFlags,
         DPHBackend(..),
 
-        -- Configuration of the core-to-core and stg-to-stg phases
-        CoreToDo(..),
-        StgToDo(..),
-        SimplifierSwitch(..),
-        SimplifierMode(..), FloatOutSwitches(..),
-        getCoreToDo, getStgToDo,
-
-        -- Manipulating DynFlags
+        -- ** Manipulating DynFlags
         defaultDynFlags,                -- DynFlags
         initDynFlags,                   -- DynFlags -> IO DynFlags
 
         dopt,                           -- DynFlag -> DynFlags -> Bool
         dopt_set, dopt_unset,           -- DynFlags -> DynFlag -> DynFlags
         defaultDynFlags,                -- DynFlags
         initDynFlags,                   -- DynFlags -> IO DynFlags
 
         dopt,                           -- DynFlag -> DynFlags -> Bool
         dopt_set, dopt_unset,           -- DynFlags -> DynFlag -> DynFlags
-        getOpts,                        -- (DynFlags -> [a]) -> IO [a]
+        getOpts,                        -- DynFlags -> (DynFlags -> [a]) -> [a]
         getVerbFlag,
         getVerbFlag,
+        getMainFun,
         updOptLevel,
         setTmpDir,
         setPackageName,
 
         updOptLevel,
         setTmpDir,
         setPackageName,
 
-        -- parsing DynFlags
+        -- ** Parsing DynFlags
         parseDynamicFlags,
         allFlags,
 
         parseDynamicFlags,
         allFlags,
 
-        -- misc stuff
+        supportedLanguages, languageOptions,
+
+        -- ** DynFlag C compiler options
         machdepCCOpts, picCCOpts,
         machdepCCOpts, picCCOpts,
-    supportedLanguages, languageOptions,
-    compilerInfo,
+
+        -- * Configuration of the core-to-core passes
+        CoreToDo(..),
+        SimplifierMode(..),
+        SimplifierSwitch(..),
+        FloatOutSwitches(..),
+        getCoreToDo,
+
+        -- * Configuration of the stg-to-stg passes
+        StgToDo(..),
+        getStgToDo,
+
+        -- * Compiler configuration suitable for display to the user
+        compilerInfo
   ) where
 
 #include "HsVersions.h"
 
 import Module
 import PackageConfig
   ) where
 
 #include "HsVersions.h"
 
 import Module
 import PackageConfig
-import PrelNames        ( mAIN )
+import PrelNames        ( mAIN, main_RDR_Unqual )
+import RdrName          ( RdrName, mkRdrUnqual )
+import OccName          ( mkVarOccFS )
 #ifdef i386_TARGET_ARCH
 import StaticFlags      ( opt_Static )
 #endif
 #ifdef i386_TARGET_ARCH
 import StaticFlags      ( opt_Static )
 #endif
@@ -69,25 +77,26 @@ import DriverPhases     ( Phase(..), phaseInputExt )
 import Config
 import CmdLineParser
 import Constants        ( mAX_CONTEXT_REDUCTION_DEPTH )
 import Config
 import CmdLineParser
 import Constants        ( mAX_CONTEXT_REDUCTION_DEPTH )
-import Panic            ( panic, GhcException(..) )
+import Panic
 import UniqFM           ( UniqFM )
 import Util
 import Maybes           ( orElse )
 import UniqFM           ( UniqFM )
 import Util
 import Maybes           ( orElse )
-import SrcLoc           ( SrcSpan )
+import SrcLoc
+import FastString
 import Outputable
 import {-# SOURCE #-} ErrUtils ( Severity(..), Message, mkLocMessage )
 
 import Data.IORef       ( readIORef )
 import Outputable
 import {-# SOURCE #-} ErrUtils ( Severity(..), Message, mkLocMessage )
 
 import Data.IORef       ( readIORef )
-import Control.Exception ( throwDyn )
 import Control.Monad    ( when )
 
 import Data.Char
 import System.FilePath
 import Control.Monad    ( when )
 
 import Data.Char
 import System.FilePath
-import System.IO        ( hPutStrLn, stderr )
+import System.IO        ( stderr, hPutChar )
 
 -- -----------------------------------------------------------------------------
 -- DynFlags
 
 
 -- -----------------------------------------------------------------------------
 -- DynFlags
 
+-- | Enumerates the simple on-or-off dynamic flags
 data DynFlag
 
    -- debugging flags
 data DynFlag
 
    -- debugging flags
@@ -169,11 +178,12 @@ data DynFlag
    | Opt_WarnUnusedBinds
    | Opt_WarnUnusedImports
    | Opt_WarnUnusedMatches
    | Opt_WarnUnusedBinds
    | Opt_WarnUnusedImports
    | Opt_WarnUnusedMatches
-   | Opt_WarnDeprecations
+   | Opt_WarnWarningsDeprecations
    | Opt_WarnDeprecatedFlags
    | Opt_WarnDodgyImports
    | Opt_WarnOrphans
    | Opt_WarnTabs
    | Opt_WarnDeprecatedFlags
    | Opt_WarnDodgyImports
    | Opt_WarnOrphans
    | Opt_WarnTabs
+   | Opt_WarnUnrecognisedPragmas
    | Opt_WarnDodgyForeignImports
 
    -- language opts
    | Opt_WarnDodgyForeignImports
 
    -- language opts
@@ -190,7 +200,7 @@ data DynFlag
    | Opt_TemplateHaskell
    | Opt_QuasiQuotes
    | Opt_ImplicitParams
    | Opt_TemplateHaskell
    | Opt_QuasiQuotes
    | Opt_ImplicitParams
-   | Opt_Generics
+   | Opt_Generics                      -- "Derivable type classes"
    | Opt_ImplicitPrelude
    | Opt_ScopedTypeVariables
    | Opt_UnboxedTuples
    | Opt_ImplicitPrelude
    | Opt_ScopedTypeVariables
    | Opt_UnboxedTuples
@@ -217,7 +227,6 @@ data DynFlag
    | Opt_MagicHash
    | Opt_EmptyDataDecls
    | Opt_KindSignatures
    | Opt_MagicHash
    | Opt_EmptyDataDecls
    | Opt_KindSignatures
-   | Opt_PatternSignatures
    | Opt_ParallelListComp
    | Opt_TransformListComp
    | Opt_GeneralizedNewtypeDeriving
    | Opt_ParallelListComp
    | Opt_TransformListComp
    | Opt_GeneralizedNewtypeDeriving
@@ -229,6 +238,7 @@ data DynFlag
    | Opt_RankNTypes
    | Opt_ImpredicativeTypes
    | Opt_TypeOperators
    | Opt_RankNTypes
    | Opt_ImpredicativeTypes
    | Opt_TypeOperators
+   | Opt_PackageImports
 
    | Opt_PrintExplicitForalls
 
 
    | Opt_PrintExplicitForalls
 
@@ -248,7 +258,7 @@ data DynFlag
    | Opt_UnboxStrictFields
    | Opt_MethodSharing
    | Opt_DictsCheap
    | Opt_UnboxStrictFields
    | Opt_MethodSharing
    | Opt_DictsCheap
-   | Opt_RewriteRules
+   | Opt_EnableRewriteRules            -- Apply rewrite rules during simplification
    | Opt_Vectorise
    | Opt_RegsGraph                      -- do graph coloring register allocation
    | Opt_RegsIterative                  -- do iterative coalescing graph coloring register allocation
    | Opt_Vectorise
    | Opt_RegsGraph                      -- do graph coloring register allocation
    | Opt_RegsIterative                  -- do iterative coalescing graph coloring register allocation
@@ -278,6 +288,7 @@ data DynFlag
    | Opt_RunCPSZ
    | Opt_ConvertToZipCfgAndBack
    | Opt_AutoLinkPackages
    | Opt_RunCPSZ
    | Opt_ConvertToZipCfgAndBack
    | Opt_AutoLinkPackages
+   | Opt_ImplicitImportQualified
 
    -- keeping stuff
    | Opt_KeepHiDiffs
 
    -- keeping stuff
    | Opt_KeepHiDiffs
@@ -288,40 +299,42 @@ data DynFlag
 
    deriving (Eq, Show)
 
 
    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 {
   ghcMode               :: GhcMode,
   ghcLink               :: GhcLink,
   coreToDo              :: Maybe [CoreToDo], -- reserved for -Ofile
   stgToDo               :: Maybe [StgToDo],  -- similarly
   hscTarget             :: HscTarget,
 data DynFlags = DynFlags {
   ghcMode               :: GhcMode,
   ghcLink               :: GhcLink,
   coreToDo              :: Maybe [CoreToDo], -- reserved for -Ofile
   stgToDo               :: Maybe [StgToDo],  -- similarly
   hscTarget             :: HscTarget,
-  hscOutName            :: String,      -- name of the output file
-  extCoreName           :: String,      -- name of the .core output file
-  verbosity             :: Int,         -- verbosity level
-  optLevel              :: Int,         -- optimisation level
-  simplPhases           :: Int,         -- number of simplifier phases
-  maxSimplIterations    :: Int,         -- max simplifier iterations
+  hscOutName            :: String,      -- ^ Name of the output file
+  extCoreName           :: String,      -- ^ Name of the .hcr output file
+  verbosity             :: Int,         -- ^ Verbosity level: see "DynFlags#verbosity_levels"
+  optLevel              :: Int,         -- ^ Optimisation level
+  simplPhases           :: Int,         -- ^ Number of simplifier phases
+  maxSimplIterations    :: Int,         -- ^ Max simplifier iterations
   shouldDumpSimplPhase  :: SimplifierMode -> Bool,
   ruleCheck             :: Maybe String,
 
   shouldDumpSimplPhase  :: SimplifierMode -> Bool,
   ruleCheck             :: Maybe String,
 
-  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
 
   stolen_x86_regs       :: Int,
 
   stolen_x86_regs       :: Int,
-  cmdlineHcIncludes     :: [String],    -- -#includes
+  cmdlineHcIncludes     :: [String],    -- ^ @\-\#includes@
   importPaths           :: [FilePath],
   mainModIs             :: Module,
   mainFunIs             :: Maybe String,
   importPaths           :: [FilePath],
   mainModIs             :: Module,
   mainFunIs             :: Maybe String,
-  ctxtStkDepth          :: Int,         -- Typechecker context stack depth
+  ctxtStkDepth          :: Int,         -- ^ Typechecker context stack depth
 
   dphBackend            :: DPHBackend,
 
 
   dphBackend            :: DPHBackend,
 
-  thisPackage           :: PackageId,
+  thisPackage           :: PackageId,   -- ^ name of package currently being compiled
 
   -- ways
 
   -- ways
-  wayNames              :: [WayName],   -- way flags from the cmd line
-  buildTag              :: String,      -- the global "way" (eg. "p" for prof)
-  rtsBuildTag           :: String,      -- the RTS "way"
+  wayNames              :: [WayName],   -- ^ Way flags from the command line
+  buildTag              :: String,      -- ^ The global \"way\" (e.g. \"p\" for prof)
+  rtsBuildTag           :: String,      -- ^ The RTS \"way\"
 
   -- paths etc.
   objectDir             :: Maybe String,
 
   -- paths etc.
   objectDir             :: Maybe String,
@@ -336,12 +349,12 @@ data DynFlags = DynFlags {
   outputHi              :: Maybe String,
   dynLibLoader          :: DynLibLoader,
 
   outputHi              :: Maybe String,
   dynLibLoader          :: DynLibLoader,
 
-  -- | This is set by DriverPipeline.runPipeline based on where
+  -- | This is set by 'DriverPipeline.runPipeline' based on where
   --    its output is going.
   dumpPrefix            :: Maybe FilePath,
 
   --    its output is going.
   dumpPrefix            :: Maybe FilePath,
 
-  -- | Override the dumpPrefix set by runPipeline.
-  --    Set by -ddump-file-prefix
+  -- | Override the 'dumpPrefix' set by 'DriverPipeline.runPipeline'.
+  --    Set by @-ddump-file-prefix@
   dumpPrefixForce       :: Maybe FilePath,
 
   includePaths          :: [String],
   dumpPrefixForce       :: Maybe FilePath,
 
   includePaths          :: [String],
@@ -353,7 +366,7 @@ data DynFlags = DynFlags {
   ghcUsagePath          :: FilePath,    -- Filled in by SysTools
   ghciUsagePath         :: FilePath,    -- ditto
 
   ghcUsagePath          :: FilePath,    -- Filled in by SysTools
   ghciUsagePath         :: FilePath,    -- ditto
 
-  hpcDir                :: String,      -- ^ path to store the .mix files
+  hpcDir                :: String,      -- ^ Path to store the .mix files
 
   -- options for particular phases
   opt_L                 :: [String],
 
   -- options for particular phases
   opt_L                 :: [String],
@@ -363,7 +376,6 @@ data DynFlags = DynFlags {
   opt_m                 :: [String],
   opt_a                 :: [String],
   opt_l                 :: [String],
   opt_m                 :: [String],
   opt_a                 :: [String],
   opt_l                 :: [String],
-  opt_dep               :: [String],
   opt_windres           :: [String],
 
   -- commands for particular phases
   opt_windres           :: [String],
 
   -- commands for particular phases
@@ -380,15 +392,22 @@ data DynFlags = DynFlags {
   pgm_sysman            :: String,
   pgm_windres           :: String,
 
   pgm_sysman            :: String,
   pgm_windres           :: String,
 
+  --  For ghc -M
+  depMakefile           :: FilePath,
+  depIncludePkgDeps     :: Bool,
+  depExcludeMods        :: [ModuleName],
+  depSuffixes           :: [String],
+  depWarnings           :: Bool,
+
   --  Package flags
   extraPkgConfs         :: [FilePath],
   topDir                :: FilePath,    -- filled in by SysTools
   systemPackageConfig   :: FilePath,    -- ditto
   --  Package flags
   extraPkgConfs         :: [FilePath],
   topDir                :: FilePath,    -- filled in by SysTools
   systemPackageConfig   :: FilePath,    -- ditto
-        -- The -package-conf flags given on the command line, in the order
+        -- ^ The @-package-conf@ flags given on the command line, in the order
         -- they appeared.
 
   packageFlags          :: [PackageFlag],
         -- they appeared.
 
   packageFlags          :: [PackageFlag],
-        -- The -package and -hide-package flags from the command-line
+        -- ^ The @-package@ and @-hide-package@ flags from the command-line
 
   -- Package state
   -- NB. do not modify this field, it is calculated by
 
   -- Package state
   -- NB. do not modify this field, it is calculated by
@@ -399,7 +418,7 @@ data DynFlags = DynFlags {
   -- hsc dynamic flags
   flags                 :: [DynFlag],
 
   -- hsc dynamic flags
   flags                 :: [DynFlag],
 
-  -- message output
+  -- | Message output action: use "ErrUtils" instead of this if you can
   log_action            :: Severity -> SrcSpan -> PprStyle -> Message -> IO (),
 
   haddockOptions :: Maybe String
   log_action            :: Severity -> SrcSpan -> PprStyle -> Message -> IO (),
 
   haddockOptions :: Maybe String
@@ -413,7 +432,7 @@ data HscTarget
   | HscNothing
   deriving (Eq, Show)
 
   | HscNothing
   deriving (Eq, Show)
 
--- | will this target result in an object file on the disk?
+-- | Will this target result in an object file on the disk?
 isObjectTarget :: HscTarget -> Bool
 isObjectTarget HscC     = True
 isObjectTarget HscAsm   = True
 isObjectTarget :: HscTarget -> Bool
 isObjectTarget HscC     = True
 isObjectTarget HscAsm   = True
@@ -426,21 +445,21 @@ isObjectTarget _        = False
 -- imported modules, but in multi-module mode we look for source files
 -- in order to check whether they need to be recompiled.
 data GhcMode
 -- imported modules, but in multi-module mode we look for source files
 -- in order to check whether they need to be recompiled.
 data GhcMode
-  = CompManager         -- ^ --make, GHCi, etc.
-  | OneShot             -- ^ ghc -c Foo.hs
-  | MkDepend            -- ^ ghc -M, see Finder for why we need this
+  = CompManager         -- ^ @\-\-make@, GHCi, etc.
+  | OneShot             -- ^ @ghc -c Foo.hs@
+  | MkDepend            -- ^ @ghc -M@, see "Finder" for why we need this
   deriving Eq
 
 isOneShot :: GhcMode -> Bool
 isOneShot OneShot = True
 isOneShot _other  = False
 
   deriving Eq
 
 isOneShot :: GhcMode -> Bool
 isOneShot OneShot = True
 isOneShot _other  = False
 
--- | What kind of linking to do.
-data GhcLink    -- What to do in the link step, if there is one
-  = NoLink              -- Don't link at all
-  | LinkBinary          -- Link object code into a binary
-  | LinkInMemory        -- Use the in-memory dynamic linker
-  | LinkDynLib          -- Link objects into a dynamic lib (DLL on Windows, DSO on ELF platforms)
+-- | What to do in the link step, if there is one.
+data GhcLink
+  = NoLink              -- ^ Don't link at all
+  | LinkBinary          -- ^ Link object code into a binary
+  | LinkInMemory        -- ^ Use the in-memory dynamic linker
+  | LinkDynLib          -- ^ Link objects into a dynamic lib (DLL on Windows, DSO on ELF platforms)
   deriving (Eq, Show)
 
 isNoLink :: GhcLink -> Bool
   deriving (Eq, Show)
 
 isNoLink :: GhcLink -> Bool
@@ -456,7 +475,7 @@ data PackageFlag
 defaultHscTarget :: HscTarget
 defaultHscTarget = defaultObjectTarget
 
 defaultHscTarget :: HscTarget
 defaultHscTarget = defaultObjectTarget
 
--- | the 'HscTarget' value corresponding to the default way to create
+-- | The 'HscTarget' value corresponding to the default way to create
 -- object files on the current platform.
 defaultObjectTarget :: HscTarget
 defaultObjectTarget
 -- object files on the current platform.
 defaultObjectTarget :: HscTarget
 defaultObjectTarget
@@ -469,6 +488,7 @@ data DynLibLoader
   | SystemDependent
   deriving Eq
 
   | SystemDependent
   deriving Eq
 
+-- | Used by 'GHC.newSession' to partially initialize a new 'DynFlags' value
 initDynFlags :: DynFlags -> IO DynFlags
 initDynFlags dflags = do
  -- someday these will be dynamic flags
 initDynFlags :: DynFlags -> IO DynFlags
 initDynFlags dflags = do
  -- someday these will be dynamic flags
@@ -481,6 +501,8 @@ initDynFlags dflags = do
         rtsBuildTag     = rts_build_tag
         }
 
         rtsBuildTag     = rts_build_tag
         }
 
+-- | The normal 'DynFlags'. Note that they is not suitable for use in this form
+-- and must be fully initialized by 'GHC.newSession' first.
 defaultDynFlags :: DynFlags
 defaultDynFlags =
      DynFlags {
 defaultDynFlags :: DynFlags
 defaultDynFlags =
      DynFlags {
@@ -541,7 +563,6 @@ defaultDynFlags =
         opt_a                   = [],
         opt_m                   = [],
         opt_l                   = [],
         opt_a                   = [],
         opt_m                   = [],
         opt_l                   = [],
-        opt_dep                 = [],
         opt_windres             = [],
 
         extraPkgConfs           = [],
         opt_windres             = [],
 
         extraPkgConfs           = [],
@@ -555,7 +576,7 @@ defaultDynFlags =
         ghcUsagePath            = panic "defaultDynFlags: No ghciUsagePath",
         ghciUsagePath           = panic "defaultDynFlags: No ghciUsagePath",
         topDir                  = panic "defaultDynFlags: No topDir",
         ghcUsagePath            = panic "defaultDynFlags: No ghciUsagePath",
         ghciUsagePath           = panic "defaultDynFlags: No ghciUsagePath",
         topDir                  = panic "defaultDynFlags: No topDir",
-        systemPackageConfig     = panic "defaultDynFlags: No systemPackageConfig",
+        systemPackageConfig     = panic  "no systemPackageConfig: call GHC.setSessionDynFlags",
         pgm_L                   = panic "defaultDynFlags: No pgm_L",
         pgm_P                   = panic "defaultDynFlags: No pgm_P",
         pgm_F                   = panic "defaultDynFlags: No pgm_F",
         pgm_L                   = panic "defaultDynFlags: No pgm_L",
         pgm_P                   = panic "defaultDynFlags: No pgm_P",
         pgm_F                   = panic "defaultDynFlags: No pgm_F",
@@ -569,6 +590,13 @@ defaultDynFlags =
         pgm_sysman              = panic "defaultDynFlags: No pgm_sysman",
         pgm_windres             = panic "defaultDynFlags: No pgm_windres",
         -- end of initSysTools values
         pgm_sysman              = panic "defaultDynFlags: No pgm_sysman",
         pgm_windres             = panic "defaultDynFlags: No pgm_windres",
         -- end of initSysTools values
+        -- ghc -M values
+        depMakefile       = "Makefile",
+        depIncludePkgDeps = False,
+        depExcludeMods    = [],
+        depSuffixes       = [],
+        depWarnings       = True,
+        -- end of ghc -M values
         haddockOptions = Nothing,
         flags = [
             Opt_AutoLinkPackages,
         haddockOptions = Nothing,
         flags = [
             Opt_AutoLinkPackages,
@@ -595,12 +623,18 @@ defaultDynFlags =
 
         log_action = \severity srcSpan style msg ->
                         case severity of
 
         log_action = \severity srcSpan style msg ->
                         case severity of
-                          SevInfo  -> hPutStrLn stderr (show (msg style))
-                          SevFatal -> hPutStrLn stderr (show (msg style))
-                          _        -> hPutStrLn stderr ('\n':show ((mkLocMessage srcSpan msg) style))
+                          SevInfo  -> printErrs (msg style)
+                          SevFatal -> printErrs (msg style)
+                          _        -> do 
+                                hPutChar stderr '\n'
+                                printErrs ((mkLocMessage srcSpan msg) style)
+                     -- careful (#2302): printErrs prints in UTF-8, whereas
+                     -- converting to string first and using hPutStr would
+                     -- just emit the low 8 bits of each unicode char.
       }
 
 {-
       }
 
 {-
+    #verbosity_levels#
     Verbosity levels:
 
     0   |   print errors & warnings only
     Verbosity levels:
 
     0   |   print errors & warnings only
@@ -611,19 +645,27 @@ defaultDynFlags =
     5   |   "ghc -v -ddump-all"
 -}
 
     5   |   "ghc -v -ddump-all"
 -}
 
+-- | 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'
 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'
 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) }
 
-getOpts :: DynFlags -> (DynFlags -> [a]) -> [a]
+-- | Retrieve the options corresponding to a particular @opt_*@ field in the correct order
+getOpts :: DynFlags             -- ^ 'DynFlags' to retrieve the options from
+        -> (DynFlags -> [a])    -- ^ Relevant record accessor: one of the @opt_*@ accessors
+        -> [a]                  -- ^ Correctly ordered extracted options
 getOpts dflags opts = reverse (opts dflags)
         -- We add to the options from the front, so we need to reverse the list
 
 getOpts dflags opts = reverse (opts dflags)
         -- We add to the options from the front, so we need to reverse the list
 
+-- | 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"
 getVerbFlag :: DynFlags -> String
 getVerbFlag dflags
   | verbosity dflags >= 3  = "-v"
@@ -631,7 +673,7 @@ getVerbFlag dflags
 
 setObjectDir, setHiDir, setStubDir, setObjectSuf, setHiSuf, setHcSuf, parseDynLibLoaderMode,
          setPgmP, setPgmL, setPgmF, setPgmc, setPgmm, setPgms, setPgma, setPgml, setPgmdll, setPgmwindres,
 
 setObjectDir, setHiDir, setStubDir, setObjectSuf, setHiSuf, setHcSuf, parseDynLibLoaderMode,
          setPgmP, setPgmL, setPgmF, setPgmc, setPgmm, setPgms, setPgma, setPgml, setPgmdll, setPgmwindres,
-         addOptL, addOptP, addOptF, addOptc, addOptm, addOpta, addOptl, addOptdep, addOptwindres,
+         addOptL, addOptP, addOptF, addOptc, addOptm, addOpta, addOptl, addOptwindres,
          addCmdlineFramework, addHaddockOpts
    :: String -> DynFlags -> DynFlags
 setOutputFile, setOutputHi, setDumpPrefixForce
          addCmdlineFramework, addHaddockOpts
    :: String -> DynFlags -> DynFlags
 setOutputFile, setOutputHi, setDumpPrefixForce
@@ -641,7 +683,7 @@ 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 with -fvia-C.
 
 setObjectSuf  f d = d{ objectSuf  = f}
 setHiSuf      f d = d{ hiSuf      = f}
 
 setObjectSuf  f d = d{ objectSuf  = f}
 setHiSuf      f d = d{ hiSuf      = f}
@@ -682,9 +724,32 @@ addOptc   f d = d{ opt_c   = f : opt_c d}
 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}
 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}
-addOptdep f d = d{ opt_dep = f : opt_dep d}
 addOptwindres f d = d{ opt_windres = f : opt_windres d}
 
 addOptwindres f d = d{ opt_windres = f : opt_windres d}
 
+setDepMakefile :: FilePath -> DynFlags -> DynFlags
+setDepMakefile f d = d { depMakefile = deOptDep f }
+
+setDepIncludePkgDeps :: Bool -> DynFlags -> DynFlags
+setDepIncludePkgDeps b d = d { depIncludePkgDeps = b }
+
+addDepExcludeMod :: String -> DynFlags -> DynFlags
+addDepExcludeMod m d
+    = d { depExcludeMods = mkModuleName (deOptDep m) : depExcludeMods d }
+
+addDepSuffix :: FilePath -> DynFlags -> DynFlags
+addDepSuffix s d = d { depSuffixes = deOptDep s : depSuffixes d }
+
+setDepWarnings :: Bool -> DynFlags -> DynFlags
+setDepWarnings b d = d { depWarnings = b }
+
+-- XXX Legacy code:
+-- We used to use "-optdep-flag -optdeparg", so for legacy applications
+-- we need to strip the "-optdep" off of the arg
+deOptDep :: String -> String
+deOptDep x = case maybePrefixMatch "-optdep" x of
+             Just rest -> rest
+             Nothing -> x
+
 addCmdlineFramework f d = d{ cmdlineFrameworks = f : cmdlineFrameworks d}
 
 addHaddockOpts f d = d{ haddockOptions = Just f}
 addCmdlineFramework f d = d{ cmdlineFrameworks = f : cmdlineFrameworks d}
 
 addHaddockOpts f d = d{ haddockOptions = Just f}
@@ -692,13 +757,12 @@ addHaddockOpts f d = d{ haddockOptions = Just f}
 -- -----------------------------------------------------------------------------
 -- Command-line options
 
 -- -----------------------------------------------------------------------------
 -- Command-line options
 
--- When invoking external tools as part of the compilation pipeline, we
+-- | When invoking external tools as part of the compilation pipeline, we
 -- pass these a sequence of options on the command-line. Rather than
 -- just using a list of Strings, we use a type that allows us to distinguish
 -- pass these a sequence of options on the command-line. Rather than
 -- just using a list of Strings, we use a type that allows us to distinguish
--- between filepaths and 'other stuff'. [The reason being, of course, that
+-- between filepaths and 'other stuff'. The reason for this is that
 -- this type gives us a handle on transforming filenames, and filenames only,
 -- this type gives us a handle on transforming filenames, and filenames only,
--- to whatever format they're expected to be on a particular platform.]
-
+-- to whatever format they're expected to be on a particular platform.
 data Option
  = FileOption -- an entry that _contains_ filename(s) / filepaths.
               String  -- a non-filepath prefix that shouldn't be
 data Option
  = FileOption -- an entry that _contains_ filename(s) / filepaths.
               String  -- a non-filepath prefix that shouldn't be
@@ -710,7 +774,7 @@ data Option
 -- Setting the optimisation level
 
 updOptLevel :: Int -> DynFlags -> DynFlags
 -- Setting the optimisation level
 
 updOptLevel :: Int -> DynFlags -> DynFlags
--- Set dynflags appropriate to the optimisation level
+-- ^ Sets the 'DynFlags' to be appropriate to the optimisation level
 updOptLevel n dfs
   = dfs2{ optLevel = final_n }
   where
 updOptLevel n dfs
   = dfs2{ optLevel = final_n }
   where
@@ -727,8 +791,8 @@ optLevelFlags
     , ([0],     Opt_OmitInterfacePragmas)
 
     , ([1,2],   Opt_IgnoreAsserts)
     , ([0],     Opt_OmitInterfacePragmas)
 
     , ([1,2],   Opt_IgnoreAsserts)
-    , ([1,2],   Opt_RewriteRules)       -- Off for -O0; see Note [Scoping for Builtin rules]
-                                        --              in PrelRules
+    , ([1,2],   Opt_EnableRewriteRules)  -- Off for -O0; see Note [Scoping for Builtin rules]
+                                         --              in PrelRules
     , ([1,2],   Opt_DoEtaReduction)
     , ([1,2],   Opt_CaseMerge)
     , ([1,2],   Opt_Strictness)
     , ([1,2],   Opt_DoEtaReduction)
     , ([1,2],   Opt_CaseMerge)
     , ([1,2],   Opt_Strictness)
@@ -737,7 +801,16 @@ optLevelFlags
 
     , ([2],     Opt_LiberateCase)
     , ([2],     Opt_SpecConstr)
 
     , ([2],     Opt_LiberateCase)
     , ([2],     Opt_SpecConstr)
-    , ([2],     Opt_StaticArgumentTransformation)
+
+--     , ([2],     Opt_StaticArgumentTransformation)
+-- Max writes: I think it's probably best not to enable SAT with -O2 for the
+-- 6.10 release. The version of SAT in HEAD at the moment doesn't incorporate
+-- several improvements to the heuristics, and I'm concerned that without
+-- those changes SAT will interfere with some attempts to write "high
+-- performance Haskell", as we saw in some posts on Haskell-Cafe earlier
+-- this year. In particular, the version in HEAD lacks the tail call
+-- criterion, so many things that look like reasonable loops will be
+-- turned into functions with extra (unneccesary) thunk creation.
 
     , ([0,1,2], Opt_DoLambdaEtaExpansion)
                 -- This one is important for a tiresome reason:
 
     , ([0,1,2], Opt_DoLambdaEtaExpansion)
                 -- This one is important for a tiresome reason:
@@ -751,8 +824,9 @@ optLevelFlags
 
 standardWarnings :: [DynFlag]
 standardWarnings
 
 standardWarnings :: [DynFlag]
 standardWarnings
-    = [ Opt_WarnDeprecations,
+    = [ Opt_WarnWarningsDeprecations,
         Opt_WarnDeprecatedFlags,
         Opt_WarnDeprecatedFlags,
+        Opt_WarnUnrecognisedPragmas,
         Opt_WarnOverlappingPatterns,
         Opt_WarnMissingFields,
         Opt_WarnMissingMethods,
         Opt_WarnOverlappingPatterns,
         Opt_WarnMissingFields,
         Opt_WarnMissingMethods,
@@ -788,6 +862,7 @@ minuswRemovesOpts
        Opt_WarnIncompletePatternsRecUpd,
        Opt_WarnSimplePatterns,
        Opt_WarnMonomorphism,
        Opt_WarnIncompletePatternsRecUpd,
        Opt_WarnSimplePatterns,
        Opt_WarnMonomorphism,
+       Opt_WarnUnrecognisedPragmas,
        Opt_WarnTabs
       ]
 
        Opt_WarnTabs
       ]
 
@@ -1059,13 +1134,32 @@ dynamic_flags = [
   , Flag "optm"           (HasArg (upd . addOptm)) Supported
   , Flag "opta"           (HasArg (upd . addOpta)) Supported
   , Flag "optl"           (HasArg (upd . addOptl)) Supported
   , Flag "optm"           (HasArg (upd . addOptm)) Supported
   , Flag "opta"           (HasArg (upd . addOpta)) Supported
   , Flag "optl"           (HasArg (upd . addOptl)) Supported
-  , Flag "optdep"         (HasArg (upd . addOptdep)) Supported
   , Flag "optwindres"     (HasArg (upd . addOptwindres)) Supported
 
   , Flag "split-objs"
          (NoArg (if can_split then setDynFlag Opt_SplitObjs else return ()))
          Supported
 
   , Flag "optwindres"     (HasArg (upd . addOptwindres)) Supported
 
   , Flag "split-objs"
          (NoArg (if can_split then setDynFlag Opt_SplitObjs else return ()))
          Supported
 
+        -------- ghc -M -----------------------------------------------------
+  , Flag "dep-suffix"               (HasArg (upd . addDepSuffix)) Supported
+  , Flag "optdep-s"                 (HasArg (upd . addDepSuffix))
+         (Deprecated "Use -dep-suffix instead")
+  , Flag "dep-makefile"             (HasArg (upd . setDepMakefile)) Supported
+  , Flag "optdep-f"                 (HasArg (upd . setDepMakefile))
+         (Deprecated "Use -dep-makefile instead")
+  , Flag "optdep-w"                 (NoArg  (upd (setDepWarnings False)))
+         (Deprecated "-optdep-w doesn't do anything")
+  , Flag "include-pkg-deps" (NoArg  (upd (setDepIncludePkgDeps True))) Supported
+  , Flag "optdep--include-prelude"  (NoArg  (upd (setDepIncludePkgDeps True)))
+         (Deprecated "Use -include-pkg-deps instead")
+  , Flag "optdep--include-pkg-deps" (NoArg  (upd (setDepIncludePkgDeps True)))
+         (Deprecated "Use -include-pkg-deps instead")
+  , Flag "exclude-module"           (HasArg (upd . addDepExcludeMod)) Supported
+  , Flag "optdep--exclude-module"   (HasArg (upd . addDepExcludeMod))
+         (Deprecated "Use -exclude-module instead")
+  , Flag "optdep-x"                 (HasArg (upd . addDepExcludeMod))
+         (Deprecated "Use -exclude-module instead")
+
         -------- Linking ----------------------------------------------------
   , Flag "c"              (NoArg (upd $ \d -> d{ ghcLink=NoLink } ))
          Supported
         -------- Linking ----------------------------------------------------
   , Flag "c"              (NoArg (upd $ \d -> d{ ghcLink=NoLink } ))
          Supported
@@ -1341,10 +1435,10 @@ dynamic_flags = [
         ------ DPH flags ----------------------------------------------------
 
   , Flag "fdph-seq"
         ------ DPH flags ----------------------------------------------------
 
   , Flag "fdph-seq"
-         (NoArg (upd (setDPHBackend DPHSeq)))
+         (NoArg (setDPHBackend DPHSeq))
          Supported
   , Flag "fdph-par"
          Supported
   , Flag "fdph-par"
-         (NoArg (upd (setDPHBackend DPHPar)))
+         (NoArg (setDPHBackend DPHPar))
          Supported
 
         ------ Compiler flags -----------------------------------------------
          Supported
 
         ------ Compiler flags -----------------------------------------------
@@ -1367,8 +1461,8 @@ dynamic_flags = [
  ++ map (mkFlag True  "X"    setDynFlag  ) xFlags
  ++ map (mkFlag False "XNo"  unSetDynFlag) xFlags
 
  ++ map (mkFlag True  "X"    setDynFlag  ) xFlags
  ++ map (mkFlag False "XNo"  unSetDynFlag) xFlags
 
-mkFlag :: Bool -- True => turn it on, False => turn it off
-       -> String
+mkFlag :: Bool                  -- ^ True <=> it should be turned on
+       -> String                -- ^ The flag prefix
        -> (DynFlag -> DynP ())
        -> (String, DynFlag, Bool -> Deprecated)
        -> Flag DynP
        -> (DynFlag -> DynP ())
        -> (String, DynFlag, Bool -> Deprecated)
        -> Flag DynP
@@ -1376,12 +1470,19 @@ mkFlag turnOn flagPrefix f (name, dynflag, deprecated)
     = Flag (flagPrefix ++ name) (NoArg (f dynflag)) (deprecated turnOn)
 
 deprecatedForLanguage :: String -> Bool -> Deprecated
     = Flag (flagPrefix ++ name) (NoArg (f dynflag)) (deprecated turnOn)
 
 deprecatedForLanguage :: String -> Bool -> Deprecated
-deprecatedForLanguage lang turnOn =
-    Deprecated ("Use the " ++ prefix ++ lang ++ " language instead")
-    where prefix = if turnOn then "" else "No"
-
--- these -f<blah> flags can all be reversed with -fno-<blah>
+deprecatedForLanguage lang turn_on
+    = Deprecated ("use -X"  ++ flag ++ " or pragma {-# LANGUAGE " ++ flag ++ "#-} instead")
+    where 
+      flag | turn_on    = lang
+           | otherwise = "No"++lang
+
+useInstead :: String -> Bool -> Deprecated
+useInstead flag turn_on
+  = Deprecated ("Use -f" ++ no ++ flag ++ " instead")
+  where
+    no = if turn_on then "" else "no-"
 
 
+-- | These @-f\<blah\>@ flags can all be reversed with @-fno-\<blah\>@
 fFlags :: [(String, DynFlag, Bool -> Deprecated)]
 fFlags = [
   ( "warn-dodgy-foreign-imports",       Opt_WarnDodgyForeignImports, const Supported ),
 fFlags :: [(String, DynFlag, Bool -> Deprecated)]
 fFlags = [
   ( "warn-dodgy-foreign-imports",       Opt_WarnDodgyForeignImports, const Supported ),
@@ -1402,10 +1503,12 @@ fFlags = [
   ( "warn-unused-binds",                Opt_WarnUnusedBinds, const Supported ),
   ( "warn-unused-imports",              Opt_WarnUnusedImports, const Supported ),
   ( "warn-unused-matches",              Opt_WarnUnusedMatches, const Supported ),
   ( "warn-unused-binds",                Opt_WarnUnusedBinds, const Supported ),
   ( "warn-unused-imports",              Opt_WarnUnusedImports, const Supported ),
   ( "warn-unused-matches",              Opt_WarnUnusedMatches, const Supported ),
-  ( "warn-deprecations",                Opt_WarnDeprecations, const Supported ),
+  ( "warn-warnings-deprecations",       Opt_WarnWarningsDeprecations, const Supported ),
+  ( "warn-deprecations",                Opt_WarnWarningsDeprecations, const Supported ),
   ( "warn-deprecated-flags",            Opt_WarnDeprecatedFlags, const Supported ),
   ( "warn-orphans",                     Opt_WarnOrphans, const Supported ),
   ( "warn-tabs",                        Opt_WarnTabs, const Supported ),
   ( "warn-deprecated-flags",            Opt_WarnDeprecatedFlags, const Supported ),
   ( "warn-orphans",                     Opt_WarnOrphans, const Supported ),
   ( "warn-tabs",                        Opt_WarnTabs, const Supported ),
+  ( "warn-unrecognised-pragmas",        Opt_WarnUnrecognisedPragmas, const Supported ),
   ( "print-explicit-foralls",           Opt_PrintExplicitForalls, const Supported ),
   ( "strictness",                       Opt_Strictness, const Supported ),
   ( "static-argument-transformation",   Opt_StaticArgumentTransformation, const Supported ),
   ( "print-explicit-foralls",           Opt_PrintExplicitForalls, const Supported ),
   ( "strictness",                       Opt_Strictness, const Supported ),
   ( "static-argument-transformation",   Opt_StaticArgumentTransformation, const Supported ),
@@ -1427,7 +1530,8 @@ fFlags = [
   ( "print-bind-result",                Opt_PrintBindResult, const Supported ),
   ( "force-recomp",                     Opt_ForceRecomp, const Supported ),
   ( "hpc-no-auto",                      Opt_Hpc_No_Auto, const Supported ),
   ( "print-bind-result",                Opt_PrintBindResult, const Supported ),
   ( "force-recomp",                     Opt_ForceRecomp, const Supported ),
   ( "hpc-no-auto",                      Opt_Hpc_No_Auto, const Supported ),
-  ( "rewrite-rules",                    Opt_RewriteRules, const Supported ),
+  ( "rewrite-rules",                    Opt_EnableRewriteRules, useInstead "enable-rewrite-rules" ),
+  ( "enable-rewrite-rules",             Opt_EnableRewriteRules, const Supported ),
   ( "break-on-exception",               Opt_BreakOnException, const Supported ),
   ( "break-on-error",                   Opt_BreakOnError, const Supported ),
   ( "print-evld-with-show",             Opt_PrintEvldWithShow, const Supported ),
   ( "break-on-exception",               Opt_BreakOnException, const Supported ),
   ( "break-on-error",                   Opt_BreakOnError, const Supported ),
   ( "print-evld-with-show",             Opt_PrintEvldWithShow, const Supported ),
@@ -1470,7 +1574,8 @@ fFlags = [
   ( "allow-incoherent-instances",       Opt_IncoherentInstances,
     deprecatedForLanguage "IncoherentInstances" ),
   ( "gen-manifest",                     Opt_GenManifest, const Supported ),
   ( "allow-incoherent-instances",       Opt_IncoherentInstances,
     deprecatedForLanguage "IncoherentInstances" ),
   ( "gen-manifest",                     Opt_GenManifest, const Supported ),
-  ( "embed-manifest",                   Opt_EmbedManifest, const Supported )
+  ( "embed-manifest",                   Opt_EmbedManifest, const Supported ),
+  ( "implicit-import-qualified",        Opt_ImplicitImportQualified, const Supported )
   ]
 
 supportedLanguages :: [String]
   ]
 
 supportedLanguages :: [String]
@@ -1480,7 +1585,7 @@ supportedLanguages = [ name | (name, _, _) <- xFlags ]
 languageOptions :: [DynFlag]
 languageOptions = [ dynFlag | (_, dynFlag, _) <- xFlags ]
 
 languageOptions :: [DynFlag]
 languageOptions = [ dynFlag | (_, dynFlag, _) <- 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 = [
   ( "CPP",                              Opt_Cpp, const Supported ),
 xFlags :: [(String, DynFlag, Bool -> Deprecated)]
 xFlags = [
   ( "CPP",                              Opt_Cpp, const Supported ),
@@ -1491,7 +1596,6 @@ xFlags = [
   ( "PolymorphicComponents",            Opt_PolymorphicComponents, const Supported ),
   ( "ExistentialQuantification",        Opt_ExistentialQuantification, const Supported ),
   ( "KindSignatures",                   Opt_KindSignatures, const Supported ),
   ( "PolymorphicComponents",            Opt_PolymorphicComponents, const Supported ),
   ( "ExistentialQuantification",        Opt_ExistentialQuantification, const Supported ),
   ( "KindSignatures",                   Opt_KindSignatures, const Supported ),
-  ( "PatternSignatures",                Opt_PatternSignatures, const Supported ),
   ( "EmptyDataDecls",                   Opt_EmptyDataDecls, const Supported ),
   ( "ParallelListComp",                 Opt_ParallelListComp, const Supported ),
   ( "TransformListComp",                Opt_TransformListComp, const Supported ),
   ( "EmptyDataDecls",                   Opt_EmptyDataDecls, const Supported ),
   ( "ParallelListComp",                 Opt_ParallelListComp, const Supported ),
   ( "TransformListComp",                Opt_TransformListComp, const Supported ),
@@ -1528,6 +1632,10 @@ xFlags = [
   ( "ExtendedDefaultRules",             Opt_ExtendedDefaultRules, const Supported ),
   ( "ImplicitParams",                   Opt_ImplicitParams, const Supported ),
   ( "ScopedTypeVariables",              Opt_ScopedTypeVariables, const Supported ),
   ( "ExtendedDefaultRules",             Opt_ExtendedDefaultRules, const Supported ),
   ( "ImplicitParams",                   Opt_ImplicitParams, const Supported ),
   ( "ScopedTypeVariables",              Opt_ScopedTypeVariables, const Supported ),
+
+  ( "PatternSignatures",                Opt_ScopedTypeVariables, 
+    deprecatedForLanguage "ScopedTypeVariables" ),
+
   ( "UnboxedTuples",                    Opt_UnboxedTuples, const Supported ),
   ( "StandaloneDeriving",               Opt_StandaloneDeriving, const Supported ),
   ( "DeriveDataTypeable",               Opt_DeriveDataTypeable, const Supported ),
   ( "UnboxedTuples",                    Opt_UnboxedTuples, const Supported ),
   ( "StandaloneDeriving",               Opt_StandaloneDeriving, const Supported ),
   ( "DeriveDataTypeable",               Opt_DeriveDataTypeable, const Supported ),
@@ -1540,15 +1648,17 @@ xFlags = [
   ( "GeneralizedNewtypeDeriving",       Opt_GeneralizedNewtypeDeriving, const Supported ),
   ( "OverlappingInstances",             Opt_OverlappingInstances, const Supported ),
   ( "UndecidableInstances",             Opt_UndecidableInstances, const Supported ),
   ( "GeneralizedNewtypeDeriving",       Opt_GeneralizedNewtypeDeriving, const Supported ),
   ( "OverlappingInstances",             Opt_OverlappingInstances, const Supported ),
   ( "UndecidableInstances",             Opt_UndecidableInstances, const Supported ),
-  ( "IncoherentInstances",              Opt_IncoherentInstances, const Supported )
+  ( "IncoherentInstances",              Opt_IncoherentInstances, const Supported ),
+  ( "PackageImports",                   Opt_PackageImports, const Supported )
   ]
 
   ]
 
-impliedFlags :: [(DynFlag, [DynFlag])]
-impliedFlags = [
-   ( Opt_GADTs,               [Opt_RelaxedPolyRec] )    -- We want type-sig variables to
-                                                        --      be completely rigid for GADTs
- , ( Opt_ScopedTypeVariables, [Opt_RelaxedPolyRec] )    -- Ditto for scoped type variables; see
-                                                        --      Note [Scoped tyvars] in TcBinds
+impliedFlags :: [(DynFlag, DynFlag)]
+impliedFlags
+  = [ (Opt_GADTs,               Opt_RelaxedPolyRec)  -- We want type-sig variables to
+                                                     --      be completely rigid for GADTs
+
+    , (Opt_ScopedTypeVariables, Opt_RelaxedPolyRec)  -- Ditto for scoped type variables; see
+                                                     --      Note [Scoped tyvars] in TcBinds
   ]
 
 glasgowExtsFlags :: [DynFlag]
   ]
 
 glasgowExtsFlags :: [DynFlag]
@@ -1582,19 +1692,36 @@ glasgowExtsFlags = [
            , Opt_ParallelListComp
            , Opt_EmptyDataDecls
            , Opt_KindSignatures
            , Opt_ParallelListComp
            , Opt_EmptyDataDecls
            , Opt_KindSignatures
-           , Opt_PatternSignatures
            , Opt_GeneralizedNewtypeDeriving
            , Opt_TypeFamilies ]
 
 -- -----------------------------------------------------------------------------
 -- Parsing the dynamic flags.
 
            , Opt_GeneralizedNewtypeDeriving
            , Opt_TypeFamilies ]
 
 -- -----------------------------------------------------------------------------
 -- Parsing the dynamic flags.
 
-parseDynamicFlags :: DynFlags -> [String] -> IO (DynFlags, [String], [String])
+-- | Parse dynamic flags from a list of command line argument.  Returns the
+-- the parsed 'DynFlags', the left-over arguments, and a list of warnings.
+-- Throws a 'UsageError' if errors occurred during parsing (such as unknown
+-- flags or missing arguments).
+parseDynamicFlags :: Monad m =>
+                     DynFlags -> [Located String]
+                  -> m (DynFlags, [Located String], [Located String])
+                     -- ^ Updated 'DynFlags', left-over arguments, and
+                     -- list of warnings.
 parseDynamicFlags dflags args = do
 parseDynamicFlags dflags args = do
+  -- XXX Legacy support code
+  -- We used to accept things like
+  --     optdep-f  -optdepdepend
+  --     optdep-f  -optdep depend
+  --     optdep -f -optdepdepend
+  --     optdep -f -optdep depend
+  -- but the spaces trip up proper argument handling. So get rid of them.
+  let f (L p "-optdep" : L _ x : xs) = (L p ("-optdep" ++ x)) : f xs
+      f (x : xs) = x : f xs
+      f xs = xs
+      args' = f args
   let ((leftover, errs, warns), dflags')
   let ((leftover, errs, warns), dflags')
-          = runCmdLine (processArgs dynamic_flags args) dflags
-  when (not (null errs)) $ do
-    throwDyn (UsageError (unlines errs))
+          = runCmdLine (processArgs dynamic_flags args') dflags
+  when (not (null errs)) $ ghcError $ errorsToGhcException errs
   return (dflags', leftover, warns)
 
 type DynP = CmdLineP DynFlags
   return (dflags', leftover, warns)
 
 type DynP = CmdLineP DynFlags
@@ -1606,10 +1733,13 @@ upd f = do
 
 --------------------------
 setDynFlag, unSetDynFlag :: DynFlag -> DynP ()
 
 --------------------------
 setDynFlag, unSetDynFlag :: DynFlag -> DynP ()
-setDynFlag f = upd (\dfs -> foldl dopt_set (dopt_set dfs f) deps)
+setDynFlag f = do { upd (\dfs -> dopt_set dfs f)
+                 ; mapM_ setDynFlag deps }
   where
   where
-    deps = [ d | (f', ds) <- impliedFlags, f' == f, d <- ds ]
+    deps = [ d | (f', d) <- impliedFlags, f' == f ]
         -- When you set f, set the ones it implies
         -- When you set f, set the ones it implies
+       -- NB: use setDynFlag 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)
 
@@ -1686,7 +1816,7 @@ ignorePackage p =
 setPackageName :: String -> DynFlags -> DynFlags
 setPackageName p
   | Nothing <- unpackPackageId pid
 setPackageName :: String -> DynFlags -> DynFlags
 setPackageName p
   | Nothing <- unpackPackageId pid
-  = throwDyn (CmdLineError ("cannot parse \'" ++ p ++ "\' as a package identifier"))
+  = ghcError (CmdLineError ("cannot parse \'" ++ p ++ "\' as a package identifier"))
   | otherwise
   = \s -> s{ thisPackage = pid }
   where
   | otherwise
   = \s -> s{ thisPackage = pid }
   where
@@ -1730,10 +1860,12 @@ setOptLevel n dflags
 --    -fdicts-cheap                     always inline dictionaries
 --    -fmax-simplifier-iterations20     this is necessary sometimes
 --    -fno-spec-constr-threshold        run SpecConstr even for big loops
 --    -fdicts-cheap                     always inline dictionaries
 --    -fmax-simplifier-iterations20     this is necessary sometimes
 --    -fno-spec-constr-threshold        run SpecConstr even for big loops
+--    -fno-spec-constr-count            SpecConstr as much as possible
 --
 setDPHOpt :: DynFlags -> DynFlags
 setDPHOpt dflags = setOptLevel 2 (dflags { maxSimplIterations  = 20
                                          , specConstrThreshold = Nothing
 --
 setDPHOpt :: DynFlags -> DynFlags
 setDPHOpt dflags = setOptLevel 2 (dflags { maxSimplIterations  = 20
                                          , specConstrThreshold = Nothing
+                                         , specConstrCount     = Nothing
                                          })
                    `dopt_set`   Opt_DictsCheap
                    `dopt_unset` Opt_MethodSharing
                                          })
                    `dopt_set`   Opt_DictsCheap
                    `dopt_unset` Opt_MethodSharing
@@ -1741,9 +1873,15 @@ setDPHOpt dflags = setOptLevel 2 (dflags { maxSimplIterations  = 20
 data DPHBackend = DPHPar
                 | DPHSeq
 
 data DPHBackend = DPHPar
                 | DPHSeq
 
-setDPHBackend :: DPHBackend -> DynFlags -> DynFlags
-setDPHBackend backend dflags = dflags { dphBackend = backend }
-
+setDPHBackend :: DPHBackend -> DynP ()
+setDPHBackend backend 
+  = do
+      upd $ \dflags -> dflags { dphBackend = backend }
+      exposePackage $ "dph-prim-" ++ suffix backend
+      exposePackage $ "dph-"      ++ suffix backend
+  where
+    suffix DPHPar = "par"
+    suffix DPHSeq = "seq"
 
 setMainIs :: String -> DynP ()
 setMainIs arg
 
 setMainIs :: String -> DynP ()
 setMainIs arg
@@ -1760,6 +1898,13 @@ setMainIs arg
   where
     (main_mod, main_fn) = splitLongestPrefix arg (== '.')
 
   where
     (main_mod, main_fn) = splitLongestPrefix arg (== '.')
 
+-- | Get the unqualified name of the function to use as the \"main\" for the main module.
+-- Either returns the default name or the one configured on the command line with -main-is
+getMainFun :: DynFlags -> RdrName
+getMainFun dflags = case (mainFunIs dflags) of
+    Just fn -> mkRdrUnqual (mkVarOccFS (mkFastString fn))
+    Nothing -> main_RDR_Unqual
+
 -----------------------------------------------------------------------------
 -- Paths & Libraries
 
 -----------------------------------------------------------------------------
 -- Paths & Libraries