Add tuple sections as a new feature
[ghc-hetmet.git] / compiler / main / DynFlags.hs
index 114a523..500d257 100644 (file)
@@ -1,4 +1,3 @@
-
 -- |
 -- Dynamic flags
 --
@@ -18,7 +17,7 @@ module DynFlags (
         GhcMode(..), isOneShot,
         GhcLink(..), isNoLink,
         PackageFlag(..),
-        Option(..),
+        Option(..), showOpt,
         DynLibLoader(..),
         fFlags, xFlags,
         dphPackage,
@@ -31,13 +30,14 @@ module DynFlags (
         dopt_set, dopt_unset,           -- DynFlags -> DynFlag -> DynFlags
         getOpts,                        -- DynFlags -> (DynFlags -> [a]) -> [a]
         getVerbFlag,
-        getMainFun,
         updOptLevel,
         setTmpDir,
         setPackageName,
+        doingTickyProfiling,
 
         -- ** Parsing DynFlags
         parseDynamicFlags,
+        parseDynamicNoPackageFlags,
         allFlags,
 
         supportedLanguages, languageOptions,
@@ -57,17 +57,19 @@ module DynFlags (
         getStgToDo,
 
         -- * Compiler configuration suitable for display to the user
+        Printable(..),
         compilerInfo
   ) where
 
 #include "HsVersions.h"
 
+#ifndef OMIT_NATIVE_CODEGEN
+import Platform
+#endif
 import Module
 import PackageConfig
-import PrelNames        ( mAIN, main_RDR_Unqual )
-import RdrName          ( RdrName, mkRdrUnqual )
-import OccName          ( mkVarOccFS )
-#ifdef i386_TARGET_ARCH
+import PrelNames        ( mAIN )
+#if defined(i386_TARGET_ARCH) || (!defined(mingw32_TARGET_OS) && !defined(darwin_TARGET_OS))
 import StaticFlags      ( opt_Static )
 #endif
 import StaticFlags      ( opt_PIC, WayName(..), v_Ways, v_Build_tag,
@@ -83,13 +85,15 @@ import Util
 import Maybes           ( orElse )
 import SrcLoc
 import FastString
+import FiniteMap
 import Outputable
 import {-# SOURCE #-} ErrUtils ( Severity(..), Message, mkLocMessage )
 
-import Data.IORef       ( readIORef )
+import Data.IORef
 import Control.Monad    ( when )
 
 import Data.Char
+import Data.List
 import System.FilePath
 import System.IO        ( stderr, hPutChar )
 
@@ -113,6 +117,7 @@ data DynFlag
    | Opt_D_dump_asm_regalloc_stages
    | Opt_D_dump_asm_conflicts
    | Opt_D_dump_asm_stats
+   | Opt_D_dump_asm_expanded
    | Opt_D_dump_cpranal
    | Opt_D_dump_deriv
    | Opt_D_dump_ds
@@ -145,6 +150,7 @@ data DynFlag
    | Opt_D_dump_BCOs
    | Opt_D_dump_vect
    | Opt_D_dump_hpc
+   | Opt_D_dump_rtti
    | Opt_D_source_stats
    | Opt_D_verbose_core2core
    | Opt_D_verbose_stg2stg
@@ -180,11 +186,16 @@ data DynFlag
    | Opt_WarnUnusedMatches
    | Opt_WarnWarningsDeprecations
    | Opt_WarnDeprecatedFlags
+   | Opt_WarnDodgyExports
    | Opt_WarnDodgyImports
    | Opt_WarnOrphans
    | Opt_WarnTabs
    | Opt_WarnUnrecognisedPragmas
    | Opt_WarnDodgyForeignImports
+   | Opt_WarnLazyUnliftedBindings
+   | Opt_WarnUnusedDoBind
+   | Opt_WarnWrongDoBind
+
 
    -- language opts
    | Opt_OverlappingInstances
@@ -192,9 +203,11 @@ data DynFlag
    | 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
@@ -213,8 +226,13 @@ data DynFlag
    | Opt_ViewPatterns
    | Opt_GADTs
    | Opt_RelaxedPolyRec
+
    | Opt_StandaloneDeriving
    | Opt_DeriveDataTypeable
+   | Opt_DeriveFunctor
+   | Opt_DeriveTraversable
+   | Opt_DeriveFoldable
+
    | Opt_TypeSynonymInstances
    | Opt_FlexibleContexts
    | Opt_FlexibleInstances
@@ -232,6 +250,7 @@ data DynFlag
    | Opt_GeneralizedNewtypeDeriving
    | Opt_RecursiveDo
    | Opt_PostfixOperators
+   | Opt_TupleSections
    | Opt_PatternGuards
    | Opt_LiberalTypeSynonyms
    | Opt_Rank2Types
@@ -239,6 +258,7 @@ data DynFlag
    | Opt_ImpredicativeTypes
    | Opt_TypeOperators
    | Opt_PackageImports
+   | Opt_NewQualifiedOperators
 
    | Opt_PrintExplicitForalls
 
@@ -258,11 +278,17 @@ data DynFlag
    | Opt_UnboxStrictFields
    | Opt_MethodSharing
    | Opt_DictsCheap
+   | Opt_InlineIfEnoughArgs
    | 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
 
+   -- profiling opts
+   | Opt_AutoSccsOnAllToplevs
+   | Opt_AutoSccsOnExportedToplevs
+   | Opt_AutoSccsOnIndividualCafs
+
    -- misc opts
    | Opt_Cpp
    | Opt_Pp
@@ -270,6 +296,7 @@ data DynFlag
    | Opt_DryRun
    | Opt_DoAsmMangling
    | Opt_ExcessPrecision
+   | Opt_EagerBlackHoling
    | Opt_ReadUserPackageConf
    | Opt_NoHsMain
    | Opt_SplitObjs
@@ -285,10 +312,16 @@ data DynFlag
    | Opt_PrintBindContents
    | Opt_GenManifest
    | Opt_EmbedManifest
+   | Opt_EmitExternalCore
+   | Opt_SharedImplib
+
+       -- temporary flags
+   | Opt_RunCPS
    | Opt_RunCPSZ
    | Opt_ConvertToZipCfgAndBack
    | Opt_AutoLinkPackages
    | Opt_ImplicitImportQualified
+   | Opt_TryNewCodeGen
 
    -- keeping stuff
    | Opt_KeepHiDiffs
@@ -296,6 +329,7 @@ data DynFlag
    | Opt_KeepSFiles
    | Opt_KeepRawSFiles
    | Opt_KeepTmpFiles
+   | Opt_KeepRawTokenStream
 
    deriving (Eq, Show)
 
@@ -320,6 +354,9 @@ data DynFlags = DynFlags {
   specConstrCount       :: Maybe Int,   -- ^ Max number of specialisations for any one function
   liberateCaseThreshold :: Maybe Int,   -- ^ Threshold for LiberateCase
 
+#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],
@@ -336,6 +373,9 @@ data DynFlags = DynFlags {
   buildTag              :: String,      -- ^ The global \"way\" (e.g. \"p\" for prof)
   rtsBuildTag           :: String,      -- ^ The RTS \"way\"
 
+  -- For object splitting
+  splitInfo             :: Maybe (String,Int),
+
   -- paths etc.
   objectDir             :: Maybe String,
   hiDir                 :: Maybe String,
@@ -397,7 +437,6 @@ data DynFlags = DynFlags {
   depIncludePkgDeps     :: Bool,
   depExcludeMods        :: [ModuleName],
   depSuffixes           :: [String],
-  depWarnings           :: Bool,
 
   --  Package flags
   extraPkgConfs         :: [FilePath],
@@ -415,6 +454,12 @@ data DynFlags = DynFlags {
   pkgDatabase           :: Maybe (UniqFM PackageConfig),
   pkgState              :: PackageState,
 
+  -- Temporary files
+  -- These have to be IORefs, because the defaultCleanupHandler needs to
+  -- know what to clean when an exception happens
+  filesToClean          :: IORef [FilePath],
+  dirsToClean           :: IORef (FiniteMap FilePath FilePath),
+
   -- hsc dynamic flags
   flags                 :: [DynFlag],
 
@@ -424,12 +469,32 @@ data DynFlags = DynFlags {
   haddockOptions :: Maybe String
  }
 
+-- | The target code type of the compilation (if any).
+--
+-- Whenever you change the target, also make sure to set 'ghcLink' to
+-- something sensible.
+--
+-- 'HscNothing' can be used to avoid generating any output, however, note
+-- that:
+--
+--  * This will not run the desugaring step, thus no warnings generated in
+--    this step will be output.  In particular, this includes warnings related
+--    to pattern matching.  You can run the desugarer manually using
+--    'GHC.desugarModule'.
+--
+--  * If a program uses Template Haskell the typechecker may try to run code
+--    from an imported module.  This will fail if no code has been generated
+--    for this module.  You can use 'GHC.needsTemplateHaskell' to detect
+--    whether this might be the case and choose to either switch to a
+--    different target or avoid typechecking such modules.  (The latter may
+--    preferable for security reasons.)
+--
 data HscTarget
-  = HscC
-  | HscAsm
-  | HscJava
-  | HscInterpreted
-  | HscNothing
+  = HscC           -- ^ Generate C code.
+  | HscAsm         -- ^ Generate assembly using the native code generator.
+  | HscJava        -- ^ Generate Java bytecode.
+  | HscInterpreted -- ^ Generate bytecode.  (Requires 'LinkInMemory')
+  | HscNothing     -- ^ Don't generate any code.  See notes above.
   deriving (Eq, Show)
 
 -- | Will this target result in an object file on the disk?
@@ -463,7 +528,8 @@ isOneShot _other  = False
 data GhcLink
   = NoLink              -- ^ Don't link at all
   | LinkBinary          -- ^ Link object code into a binary
-  | LinkInMemory        -- ^ Use the in-memory dynamic linker
+  | LinkInMemory        -- ^ Use the in-memory dynamic linker (works for both
+                        --   bytecode and object code).
   | LinkDynLib          -- ^ Link objects into a dynamic lib (DLL on Windows, DSO on ELF platforms)
   deriving (Eq, Show)
 
@@ -471,6 +537,11 @@ isNoLink :: GhcLink -> Bool
 isNoLink NoLink = True
 isNoLink _      = False
 
+-- Is it worth evaluating this Bool and caching it in the DynFlags value
+-- during initDynFlags?
+doingTickyProfiling :: DynFlags -> Bool
+doingTickyProfiling dflags = WayTicky `elem` wayNames dflags
+
 data PackageFlag
   = ExposePackage  String
   | HidePackage    String
@@ -500,10 +571,14 @@ initDynFlags dflags = do
  ways <- readIORef v_Ways
  build_tag <- readIORef v_Build_tag
  rts_build_tag <- readIORef v_RTS_Build_tag
+ refFilesToClean <- newIORef []
+ refDirsToClean <- newIORef emptyFM
  return dflags{
         wayNames        = ways,
         buildTag        = build_tag,
-        rtsBuildTag     = rts_build_tag
+        rtsBuildTag     = rts_build_tag,
+        filesToClean    = refFilesToClean,
+        dirsToClean     = refDirsToClean
         }
 
 -- | The normal 'DynFlags'. Note that they is not suitable for use in this form
@@ -527,6 +602,9 @@ defaultDynFlags =
         specConstrThreshold     = Just 200,
         specConstrCount         = Just 3,
         liberateCaseThreshold   = Just 200,
+#ifndef OMIT_NATIVE_CODEGEN
+        targetPlatform          = defaultTargetPlatform,
+#endif
         stolen_x86_regs         = 4,
         cmdlineHcIncludes       = [],
         importPaths             = ["."],
@@ -548,7 +626,7 @@ defaultDynFlags =
 
         outputFile              = Nothing,
         outputHi                = Nothing,
-        dynLibLoader            = Deployable,
+        dynLibLoader            = SystemDependent,
         dumpPrefix              = Nothing,
         dumpPrefixForce         = Nothing,
         includePaths            = [],
@@ -561,7 +639,7 @@ defaultDynFlags =
 
         opt_L                   = [],
         opt_P                   = (if opt_PIC
-                                   then ["-D__PIC__"]
+                                   then ["-D__PIC__", "-U __PIC__"] -- this list is reversed
                                    else []),
         opt_F                   = [],
         opt_c                   = [],
@@ -577,6 +655,7 @@ defaultDynFlags =
         wayNames                = panic "defaultDynFlags: No wayNames",
         buildTag                = panic "defaultDynFlags: No buildTag",
         rtsBuildTag             = panic "defaultDynFlags: No rtsBuildTag",
+        splitInfo               = Nothing,
         -- initSysTools fills all these in
         ghcUsagePath            = panic "defaultDynFlags: No ghciUsagePath",
         ghciUsagePath           = panic "defaultDynFlags: No ghciUsagePath",
@@ -600,8 +679,9 @@ defaultDynFlags =
         depIncludePkgDeps = False,
         depExcludeMods    = [],
         depSuffixes       = [],
-        depWarnings       = True,
         -- end of ghc -M values
+        filesToClean   = panic "defaultDynFlags: No filesToClean",
+        dirsToClean    = panic "defaultDynFlags: No dirsToClean",
         haddockOptions = Nothing,
         flags = [
             Opt_AutoLinkPackages,
@@ -618,6 +698,8 @@ defaultDynFlags =
 
             Opt_DoAsmMangling,
 
+            Opt_SharedImplib,
+
             Opt_GenManifest,
             Opt_EmbedManifest,
             Opt_PrintBindContents
@@ -676,7 +758,8 @@ getVerbFlag dflags
   | verbosity dflags >= 3  = "-v"
   | otherwise =  ""
 
-setObjectDir, setHiDir, setStubDir, setObjectSuf, setHiSuf, setHcSuf, parseDynLibLoaderMode,
+setObjectDir, setHiDir, setStubDir, setOutputDir,
+         setObjectSuf, setHiSuf, setHcSuf, parseDynLibLoaderMode,
          setPgmP, setPgmL, setPgmF, setPgmc, setPgmm, setPgms, setPgma, setPgml, setPgmdll, setPgmwindres,
          addOptL, addOptP, addOptF, addOptc, addOptm, addOpta, addOptl, addOptwindres,
          addCmdlineFramework, addHaddockOpts
@@ -689,6 +772,7 @@ 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.
+setOutputDir  f = setObjectDir f . setHiDir f . setStubDir f
 
 setObjectSuf  f d = d{ objectSuf  = f}
 setHiSuf      f d = d{ hiSuf      = f}
@@ -704,7 +788,7 @@ parseDynLibLoaderMode f d =
    ("wrapped", "")      -> d{ dynLibLoader = Wrapped Nothing }
    ("wrapped:", "hard") -> d{ dynLibLoader = Wrapped Nothing }
    ("wrapped:", flex)   -> d{ dynLibLoader = Wrapped (Just flex) }
-   (_,_)                -> error "Unknown dynlib loader"
+   _                    -> ghcError (CmdLineError ("Unknown dynlib loader: " ++ f))
 
 setDumpPrefixForce f d = d { dumpPrefixForce = f}
 
@@ -744,14 +828,11 @@ addDepExcludeMod m 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
+deOptDep x = case stripPrefix "-optdep" x of
              Just rest -> rest
              Nothing -> x
 
@@ -775,6 +856,10 @@ data Option
               String  -- the filepath/filename portion
  | Option     String
 
+showOpt :: Option -> String
+showOpt (FileOption pre f) = pre ++ f
+showOpt (Option s)  = s
+
 -----------------------------------------------------------------------------
 -- Setting the optimisation level
 
@@ -836,7 +921,9 @@ standardWarnings
         Opt_WarnMissingFields,
         Opt_WarnMissingMethods,
         Opt_WarnDuplicateExports,
-        Opt_WarnDodgyForeignImports
+        Opt_WarnLazyUnliftedBindings,
+        Opt_WarnDodgyForeignImports,
+        Opt_WarnWrongDoBind
       ]
 
 minusWOpts :: [DynFlag]
@@ -846,6 +933,7 @@ minusWOpts
         Opt_WarnUnusedMatches,
         Opt_WarnUnusedImports,
         Opt_WarnIncompletePatterns,
+        Opt_WarnDodgyExports,
         Opt_WarnDodgyImports
       ]
 
@@ -856,7 +944,8 @@ minusWallOpts
         Opt_WarnNameShadowing,
         Opt_WarnMissingSigs,
         Opt_WarnHiShadows,
-        Opt_WarnOrphans
+        Opt_WarnOrphans,
+        Opt_WarnUnusedDoBind
       ]
 
 -- minuswRemovesOpts should be every warning option
@@ -901,18 +990,44 @@ data CoreToDo           -- These are diff core-to-core passes,
   | CoreDoNothing                -- Useful when building up
   | CoreDoPasses [CoreToDo]      -- lists of these things
 
+
 data SimplifierMode             -- See comments in SimplMonad
   = SimplGently
   | SimplPhase Int [String]
 
+instance Outputable SimplifierMode where
+    ppr SimplGently       = ptext (sLit "gentle")
+    ppr (SimplPhase n ss) = int n <+> brackets (text (concat $ intersperse "," ss))
+
+
 data SimplifierSwitch
   = MaxSimplifierIterations Int
   | NoCaseOfCase
 
-data FloatOutSwitches
-  = FloatOutSw  Bool    -- True <=> float lambdas to top level
-                Bool    -- True <=> float constants to top level,
-                        --          even if they do not escape a lambda
+
+data FloatOutSwitches = FloatOutSwitches {
+        floatOutLambdas :: Bool,     -- ^ True <=> float lambdas to top level
+        floatOutConstants :: Bool    -- ^ True <=> float constants to top level,
+                                     --            even if they do not escape a lambda
+    }
+
+instance Outputable FloatOutSwitches where
+    ppr = pprFloatOutSwitches
+
+pprFloatOutSwitches :: FloatOutSwitches -> SDoc
+pprFloatOutSwitches sw = pp_not (floatOutLambdas sw) <+> text "lambdas" <> comma
+                     <+> pp_not (floatOutConstants sw) <+> text "constants"
+  where
+    pp_not True  = empty
+    pp_not False = text "not"
+
+-- | Switches that specify the minimum amount of floating out
+-- gentleFloatOutSwitches :: FloatOutSwitches
+-- gentleFloatOutSwitches = FloatOutSwitches False False
+
+-- | Switches that do not specify floating out of lambdas, just of constants
+constantsOnlyFloatOutSwitches :: FloatOutSwitches
+constantsOnlyFloatOutSwitches = FloatOutSwitches False True
 
 
 -- The core-to-core pass ordering is derived from the DynFlags:
@@ -1010,7 +1125,14 @@ getCoreToDo dflags
         -- so that overloaded functions have all their dictionary lambdas manifest
         CoreDoSpecialising,
 
-        runWhen full_laziness (CoreDoFloatOutwards (FloatOutSw False False)),
+        runWhen full_laziness (CoreDoFloatOutwards constantsOnlyFloatOutSwitches),
+               -- Was: gentleFloatOutSwitches  
+               -- I have no idea why, but not floating constants to top level is
+               -- very bad in some cases. 
+               -- Notably: p_ident in spectral/rewrite
+               --          Changing from "gentle" to "constantsOnly" improved
+               --          rewrite's allocation by 19%, and made  0.0% difference
+               --          to any other nofib benchmark
 
         CoreDoFloatInwards,
 
@@ -1040,8 +1162,7 @@ getCoreToDo dflags
                 ]),
 
         runWhen full_laziness
-          (CoreDoFloatOutwards (FloatOutSw False    -- Not lambdas
-                                           True)),  -- Float constants
+          (CoreDoFloatOutwards constantsOnlyFloatOutSwitches),
                 -- nofib/spectral/hartel/wang doubles in speed if you
                 -- do full laziness late in the day.  It only happens
                 -- after fusion and other stuff, so the early pass doesn't
@@ -1152,7 +1273,7 @@ dynamic_flags = [
   , 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)))
+  , Flag "optdep-w"                 (NoArg  (return ()))
          (Deprecated "-optdep-w doesn't do anything")
   , Flag "include-pkg-deps" (NoArg  (upd (setDepIncludePkgDeps True))) Supported
   , Flag "optdep--include-prelude"  (NoArg  (upd (setDepIncludePkgDeps True)))
@@ -1194,6 +1315,7 @@ dynamic_flags = [
   , Flag "hidir"          (HasArg (upd . setHiDir)) Supported
   , Flag "tmpdir"         (HasArg (upd . setTmpDir)) Supported
   , Flag "stubdir"        (HasArg (upd . setStubDir)) Supported
+  , Flag "outputdir"      (HasArg (upd . setOutputDir)) Supported
   , Flag "ddump-file-prefix" (HasArg (upd . setDumpPrefixForce . Just))
          Supported
 
@@ -1222,20 +1344,6 @@ dynamic_flags = [
   , Flag "no-recomp"      (NoArg (setDynFlag   Opt_ForceRecomp))
          (Deprecated "Use -fforce-recomp instead")
 
-        ------- Packages ----------------------------------------------------
-  , Flag "package-conf"   (HasArg extraPkgConf_) Supported
-  , Flag "no-user-package-conf" (NoArg (unSetDynFlag Opt_ReadUserPackageConf))
-         Supported
-  , Flag "package-name"   (HasArg (upd . setPackageName)) Supported
-  , Flag "package"        (HasArg exposePackage) Supported
-  , Flag "hide-package"   (HasArg hidePackage) Supported
-  , Flag "hide-all-packages" (NoArg (setDynFlag Opt_HideAllPackages))
-         Supported
-  , Flag "ignore-package" (HasArg ignorePackage)
-         Supported
-  , Flag "syslib"         (HasArg exposePackage)
-         (Deprecated "Use -package instead")
-
         ------ HsCpp opts ---------------------------------------------------
   , Flag "D"              (AnySuffix (upd . addOptP)) Supported
   , Flag "U"              (AnySuffix (upd . addOptP)) Supported
@@ -1274,6 +1382,8 @@ dynamic_flags = [
          Supported
   , Flag "ddump-asm-stats"         (setDumpFlag Opt_D_dump_asm_stats)
          Supported
+  , Flag "ddump-asm-expanded"      (setDumpFlag Opt_D_dump_asm_expanded)
+         Supported
   , Flag "ddump-cpranal"           (setDumpFlag Opt_D_dump_cpranal)
          Supported
   , Flag "ddump-deriv"             (setDumpFlag Opt_D_dump_deriv)
@@ -1356,6 +1466,8 @@ dynamic_flags = [
          Supported
   , Flag "ddump-hi-diffs"          (setDumpFlag Opt_D_dump_hi_diffs)
          Supported
+  , Flag "ddump-rtti"             (setDumpFlag Opt_D_dump_rtti)
+         Supported
 
   , Flag "dcore-lint"              (NoArg (setDynFlag Opt_DoCoreLinting))
          Supported
@@ -1437,6 +1549,38 @@ dynamic_flags = [
          (IntSuffix $ \n -> upd $ \dfs -> dfs{ ctxtStkDepth = n })
          Supported
 
+        ------ Profiling ----------------------------------------------------
+
+  -- XXX Should the -f* flags be deprecated?
+  -- They don't seem to be documented
+  , Flag "fauto-sccs-on-all-toplevs"
+         (NoArg (setDynFlag Opt_AutoSccsOnAllToplevs))
+         Supported
+  , Flag "auto-all"
+         (NoArg (setDynFlag Opt_AutoSccsOnAllToplevs))
+         Supported
+  , Flag "no-auto-all"
+         (NoArg (unSetDynFlag Opt_AutoSccsOnAllToplevs))
+         Supported
+  , Flag "fauto-sccs-on-exported-toplevs"
+         (NoArg (setDynFlag Opt_AutoSccsOnExportedToplevs))
+         Supported
+  , Flag "auto"
+         (NoArg (setDynFlag Opt_AutoSccsOnExportedToplevs))
+         Supported
+  , Flag "no-auto"
+         (NoArg (unSetDynFlag Opt_AutoSccsOnExportedToplevs))
+         Supported
+  , Flag "fauto-sccs-on-individual-cafs"
+         (NoArg (setDynFlag Opt_AutoSccsOnIndividualCafs))
+         Supported
+  , Flag "caf-all"
+         (NoArg (setDynFlag Opt_AutoSccsOnIndividualCafs))
+         Supported
+  , Flag "no-caf-all"
+         (NoArg (unSetDynFlag Opt_AutoSccsOnIndividualCafs))
+         Supported
+
         ------ DPH flags ----------------------------------------------------
 
   , Flag "fdph-seq"
@@ -1469,6 +1613,23 @@ dynamic_flags = [
  ++ map (mkFlag True  "X"    setDynFlag  ) xFlags
  ++ map (mkFlag False "XNo"  unSetDynFlag) xFlags
 
+package_flags :: [Flag DynP]
+package_flags = [
+        ------- Packages ----------------------------------------------------
+    Flag "package-conf"   (HasArg extraPkgConf_) Supported
+  , Flag "no-user-package-conf" (NoArg (unSetDynFlag Opt_ReadUserPackageConf))
+         Supported
+  , Flag "package-name"   (HasArg (upd . setPackageName)) Supported
+  , Flag "package"        (HasArg exposePackage) Supported
+  , Flag "hide-package"   (HasArg hidePackage) Supported
+  , Flag "hide-all-packages" (NoArg (setDynFlag Opt_HideAllPackages))
+         Supported
+  , Flag "ignore-package" (HasArg ignorePackage)
+         Supported
+  , Flag "syslib"         (HasArg exposePackage)
+         (Deprecated "Use -package instead")
+  ]
+
 mkFlag :: Bool                  -- ^ True <=> it should be turned on
        -> String                -- ^ The flag prefix
        -> (DynFlag -> DynP ())
@@ -1494,6 +1655,7 @@ useInstead flag turn_on
 fFlags :: [(String, DynFlag, Bool -> Deprecated)]
 fFlags = [
   ( "warn-dodgy-foreign-imports",       Opt_WarnDodgyForeignImports, const Supported ),
+  ( "warn-dodgy-exports",               Opt_WarnDodgyExports, const Supported ),
   ( "warn-dodgy-imports",               Opt_WarnDodgyImports, const Supported ),
   ( "warn-duplicate-exports",           Opt_WarnDuplicateExports, const Supported ),
   ( "warn-hi-shadowing",                Opt_WarnHiShadows, const Supported ),
@@ -1517,6 +1679,10 @@ fFlags = [
   ( "warn-orphans",                     Opt_WarnOrphans, const Supported ),
   ( "warn-tabs",                        Opt_WarnTabs, const Supported ),
   ( "warn-unrecognised-pragmas",        Opt_WarnUnrecognisedPragmas, const Supported ),
+  ( "warn-lazy-unlifted-bindings",      Opt_WarnLazyUnliftedBindings,
+    const $ Deprecated "lazy unlifted bindings will be an error in GHC 6.14, and this flag will no longer exist"),
+  ( "warn-unused-do-bind",              Opt_WarnUnusedDoBind, const Supported ),
+  ( "warn-wrong-do-bind",               Opt_WarnWrongDoBind, const Supported ),
   ( "print-explicit-foralls",           Opt_PrintExplicitForalls, const Supported ),
   ( "strictness",                       Opt_Strictness, const Supported ),
   ( "static-argument-transformation",   Opt_StaticArgumentTransformation, const Supported ),
@@ -1533,7 +1699,9 @@ fFlags = [
   ( "unbox-strict-fields",              Opt_UnboxStrictFields, const Supported ),
   ( "method-sharing",                   Opt_MethodSharing, const Supported ),
   ( "dicts-cheap",                      Opt_DictsCheap, const Supported ),
+  ( "inline-if-enough-args",            Opt_InlineIfEnoughArgs, const Supported ),
   ( "excess-precision",                 Opt_ExcessPrecision, const Supported ),
+  ( "eager-blackholing",                Opt_EagerBlackHoling, const Supported ),
   ( "asm-mangling",                     Opt_DoAsmMangling, const Supported ),
   ( "print-bind-result",                Opt_PrintBindResult, const Supported ),
   ( "force-recomp",                     Opt_ForceRecomp, const Supported ),
@@ -1544,7 +1712,9 @@ fFlags = [
   ( "break-on-error",                   Opt_BreakOnError, const Supported ),
   ( "print-evld-with-show",             Opt_PrintEvldWithShow, const Supported ),
   ( "print-bind-contents",              Opt_PrintBindContents, const Supported ),
-  ( "run-cps",                          Opt_RunCPSZ, const Supported ),
+  ( "run-cps",                          Opt_RunCPS, const Supported ),
+  ( "run-cpsz",                         Opt_RunCPSZ, const Supported ),
+  ( "new-codegen",                      Opt_TryNewCodeGen, const Supported ),
   ( "convert-to-zipper-and-back",       Opt_ConvertToZipCfgAndBack, const Supported ),
   ( "vectorise",                        Opt_Vectorise, const Supported ),
   ( "regs-graph",                       Opt_RegsGraph, const Supported ),
@@ -1583,6 +1753,8 @@ fFlags = [
     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 ),
   ( "implicit-import-qualified",        Opt_ImplicitImportQualified, const Supported )
   ]
 
@@ -1598,6 +1770,7 @@ xFlags :: [(String, DynFlag, Bool -> Deprecated)]
 xFlags = [
   ( "CPP",                              Opt_Cpp, const Supported ),
   ( "PostfixOperators",                 Opt_PostfixOperators, const Supported ),
+  ( "TupleSections",                    Opt_TupleSections, const Supported ),
   ( "PatternGuards",                    Opt_PatternGuards, const Supported ),
   ( "UnicodeSyntax",                    Opt_UnicodeSyntax, const Supported ),
   ( "MagicHash",                        Opt_MagicHash, const Supported ),
@@ -1609,6 +1782,7 @@ xFlags = [
   ( "TransformListComp",                Opt_TransformListComp, const Supported ),
   ( "ForeignFunctionInterface",         Opt_ForeignFunctionInterface, const Supported ),
   ( "UnliftedFFITypes",                 Opt_UnliftedFFITypes, const Supported ),
+  ( "GHCForeignImportPrim",             Opt_GHCForeignImportPrim, const Supported ),
   ( "LiberalTypeSynonyms",              Opt_LiberalTypeSynonyms, const Supported ),
   ( "Rank2Types",                       Opt_Rank2Types, const Supported ),
   ( "RankNTypes",                       Opt_RankNTypes, const Supported ),
@@ -1636,6 +1810,7 @@ xFlags = [
   ( "MonomorphismRestriction",          Opt_MonomorphismRestriction, const Supported ),
   -- On by default (which is not strictly H98):
   ( "MonoPatBinds",                     Opt_MonoPatBinds, const Supported ),
+  ( "MonoLocalBinds",                   Opt_MonoLocalBinds, const Supported ),
   ( "RelaxedPolyRec",                   Opt_RelaxedPolyRec, const Supported ),
   ( "ExtendedDefaultRules",             Opt_ExtendedDefaultRules, const Supported ),
   ( "ImplicitParams",                   Opt_ImplicitParams, const Supported ),
@@ -1647,6 +1822,9 @@ xFlags = [
   ( "UnboxedTuples",                    Opt_UnboxedTuples, const Supported ),
   ( "StandaloneDeriving",               Opt_StandaloneDeriving, const Supported ),
   ( "DeriveDataTypeable",               Opt_DeriveDataTypeable, const Supported ),
+  ( "DeriveFunctor",                    Opt_DeriveFunctor, const Supported ),
+  ( "DeriveTraversable",                Opt_DeriveTraversable, const Supported ),
+  ( "DeriveFoldable",                   Opt_DeriveFoldable, const Supported ),
   ( "TypeSynonymInstances",             Opt_TypeSynonymInstances, const Supported ),
   ( "FlexibleContexts",                 Opt_FlexibleContexts, const Supported ),
   ( "FlexibleInstances",                Opt_FlexibleInstances, const Supported ),
@@ -1657,7 +1835,8 @@ xFlags = [
   ( "OverlappingInstances",             Opt_OverlappingInstances, const Supported ),
   ( "UndecidableInstances",             Opt_UndecidableInstances, const Supported ),
   ( "IncoherentInstances",              Opt_IncoherentInstances, const Supported ),
-  ( "PackageImports",                   Opt_PackageImports, const Supported )
+  ( "PackageImports",                   Opt_PackageImports, const Supported ),
+  ( "NewQualifiedOperators",            Opt_NewQualifiedOperators, const Supported )
   ]
 
 impliedFlags :: [(DynFlag, DynFlag)]
@@ -1665,8 +1844,13 @@ impliedFlags
   = [ (Opt_GADTs,               Opt_RelaxedPolyRec)  -- We want type-sig variables to
                                                      --      be completely rigid for GADTs
 
+    , (Opt_TypeFamilies,        Opt_RelaxedPolyRec)  -- Trac #2944 gives a nice example
+    , (Opt_TypeFamilies,        Opt_KindSignatures)  -- Type families use kind signatures
+                                                    -- all over the place
+
     , (Opt_ScopedTypeVariables, Opt_RelaxedPolyRec)  -- Ditto for scoped type variables; see
                                                      --      Note [Scoped tyvars] in TcBinds
+    , (Opt_ImpredicativeTypes,  Opt_RankNTypes)
   ]
 
 glasgowExtsFlags :: [DynFlag]
@@ -1681,6 +1865,9 @@ glasgowExtsFlags = [
            , Opt_TypeSynonymInstances
            , Opt_StandaloneDeriving
            , Opt_DeriveDataTypeable
+           , Opt_DeriveFunctor
+           , Opt_DeriveFoldable
+           , Opt_DeriveTraversable
            , Opt_FlexibleContexts
            , Opt_FlexibleInstances
            , Opt_ConstrainedClassMethods
@@ -1694,7 +1881,6 @@ glasgowExtsFlags = [
            , Opt_PatternGuards
            , Opt_LiberalTypeSynonyms
            , Opt_RankNTypes
-           , Opt_ImpredicativeTypes
            , Opt_TypeOperators
            , Opt_RecursiveDo
            , Opt_ParallelListComp
@@ -1706,7 +1892,7 @@ glasgowExtsFlags = [
 -- -----------------------------------------------------------------------------
 -- Parsing the dynamic flags.
 
--- | Parse dynamic flags from a list of command line argument.  Returns the
+-- | Parse dynamic flags from a list of command line arguments.  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).
@@ -1715,7 +1901,21 @@ parseDynamicFlags :: Monad m =>
                   -> m (DynFlags, [Located String], [Located String])
                      -- ^ Updated 'DynFlags', left-over arguments, and
                      -- list of warnings.
-parseDynamicFlags dflags args = do
+parseDynamicFlags dflags args = parseDynamicFlags_ dflags args True
+
+-- | Like 'parseDynamicFlags' but does not allow the package flags (-package,
+-- -hide-package, -ignore-package, -hide-all-packages, -package-conf).
+parseDynamicNoPackageFlags :: Monad m =>
+                     DynFlags -> [Located String]
+                  -> m (DynFlags, [Located String], [Located String])
+                     -- ^ Updated 'DynFlags', left-over arguments, and
+                     -- list of warnings.
+parseDynamicNoPackageFlags dflags args = parseDynamicFlags_ dflags args False
+
+parseDynamicFlags_ :: Monad m =>
+                      DynFlags -> [Located String] -> Bool
+                  -> m (DynFlags, [Located String], [Located String])
+parseDynamicFlags_ dflags args pkg_flags = do
   -- XXX Legacy support code
   -- We used to accept things like
   --     optdep-f  -optdepdepend
@@ -1727,8 +1927,13 @@ parseDynamicFlags dflags args = do
       f (x : xs) = x : f xs
       f xs = xs
       args' = f args
+
+      -- Note: -ignore-package (package_flags) must precede -i* (dynamic_flags)
+      flag_spec | pkg_flags = package_flags ++ dynamic_flags
+                | otherwise = dynamic_flags
+
   let ((leftover, errs, warns), dflags')
-          = runCmdLine (processArgs dynamic_flags args') dflags
+          = runCmdLine (processArgs flag_spec args') dflags
   when (not (null errs)) $ ghcError $ errorsToGhcException errs
   return (dflags', leftover, warns)
 
@@ -1874,16 +2079,21 @@ setOptLevel n dflags
 --                                      sometimes
 --    -fdicts-cheap                     always inline dictionaries
 --    -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
 --
 setDPHOpt :: DynFlags -> DynFlags
 setDPHOpt dflags = setOptLevel 2 (dflags { maxSimplIterations  = 20
+                                         , simplPhases         = 3
                                          , specConstrThreshold = Nothing
                                          , specConstrCount     = Nothing
                                          })
                    `dopt_set`   Opt_DictsCheap
                    `dopt_unset` Opt_MethodSharing
+                   `dopt_set`   Opt_InlineIfEnoughArgs
 
 data DPHBackend = DPHPar
                 | DPHSeq
@@ -1921,13 +2131,6 @@ setMainIs 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
 
@@ -2086,7 +2289,13 @@ machdepCCOpts _dflags
         = ( [], ["-fomit-frame-pointer", "-G0"] )
 
 #elif x86_64_TARGET_ARCH
-        = ( [], ["-fomit-frame-pointer",
+        = (
+#if darwin_TARGET_OS
+            ["-m64"],
+#else
+            [],
+#endif
+                ["-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
@@ -2126,18 +2335,18 @@ picCCOpts _dflags
       --     in dynamic libraries.
 
     | opt_PIC
-        = ["-fno-common", "-D__PIC__"]
+        = ["-fno-common", "-U __PIC__","-D__PIC__"]
     | otherwise
         = ["-mdynamic-no-pic"]
 #elif mingw32_TARGET_OS
       -- no -fPIC for Windows
     | opt_PIC
-        = ["-D__PIC__"]
+        = ["-U __PIC__","-D__PIC__"]
     | otherwise
         = []
 #else
-    | opt_PIC
-        = ["-fPIC", "-D__PIC__"]
+    | opt_PIC || not opt_Static
+        = ["-fPIC", "-U __PIC__", "-D__PIC__"]
     | otherwise
         = []
 #endif
@@ -2151,21 +2360,24 @@ can_split = cSplitObjs == "YES"
 -- -----------------------------------------------------------------------------
 -- Compiler Info
 
-compilerInfo :: [(String, String)]
-compilerInfo = [("Project name",                cProjectName),
-                ("Project version",             cProjectVersion),
-                ("Booter version",              cBooterVersion),
-                ("Stage",                       cStage),
-                ("Interface file version",      cHscIfaceFileVersion),
-                ("Have interpreter",            cGhcWithInterpreter),
-                ("Object splitting",            cSplitObjs),
-                ("Have native code generator",  cGhcWithNativeCodeGen),
-                ("Support SMP",                 cGhcWithSMP),
-                ("Unregisterised",              cGhcUnregisterised),
-                ("Tables next to code",         cGhcEnableTablesNextToCode),
-                ("Win32 DLLs",                  cEnableWin32DLLs),
-                ("RTS ways",                    cGhcRTSWays),
-                ("Leading underscore",          cLeadingUnderscore),
-                ("Debug on",                    show debugIsOn)
+data Printable = String String
+               | FromDynFlags (DynFlags -> String)
+
+compilerInfo :: [(String, Printable)]
+compilerInfo = [("Project name",                String cProjectName),
+                ("Project version",             String cProjectVersion),
+                ("Booter version",              String cBooterVersion),
+                ("Stage",                       String cStage),
+                ("Have interpreter",            String cGhcWithInterpreter),
+                ("Object splitting",            String cSplitObjs),
+                ("Have native code generator",  String cGhcWithNativeCodeGen),
+                ("Support SMP",                 String cGhcWithSMP),
+                ("Unregisterised",              String cGhcUnregisterised),
+                ("Tables next to code",         String cGhcEnableTablesNextToCode),
+                ("Win32 DLLs",                  String cEnableWin32DLLs),
+                ("RTS ways",                    String cGhcRTSWays),
+                ("Leading underscore",          String cLeadingUnderscore),
+                ("Debug on",                    String (show debugIsOn)),
+                ("LibDir",                      FromDynFlags topDir)
                ]