X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fmain%2FDynFlags.hs;h=3f5c4f1ec87f3d709cc9ed0a7b586ba7e5a52a88;hb=27286cf2ce6733cbbf008972c6bea30ea2e562ee;hp=3fcb628dbca0f66a21dea6eda1c5eaadc90de508;hpb=9c966bfa8c0328cb4d2e01806a8eca242b9e6f66;p=ghc-hetmet.git diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 3fcb628..3f5c4f1 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -1,4 +1,3 @@ - -- | -- Dynamic flags -- @@ -12,32 +11,34 @@ -- flags. Dynamic flags can also be set at the prompt in GHCi. module DynFlags ( -- * Dynamic flags and associated configuration types + DOpt(..), DynFlag(..), + LanguageFlag(..), DynFlags(..), HscTarget(..), isObjectTarget, defaultObjectTarget, GhcMode(..), isOneShot, GhcLink(..), isNoLink, PackageFlag(..), - Option(..), + Option(..), showOpt, DynLibLoader(..), - fFlags, xFlags, - DPHBackend(..), + fFlags, fLangFlags, xFlags, + dphPackage, + wayNames, -- ** Manipulating DynFlags defaultDynFlags, -- DynFlags initDynFlags, -- DynFlags -> IO DynFlags - dopt, -- DynFlag -> DynFlags -> Bool - 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, @@ -45,51 +46,43 @@ module DynFlags ( -- ** DynFlag C compiler options machdepCCOpts, picCCOpts, - -- * 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 + 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 StaticFlags ( opt_Static ) -#endif -import StaticFlags ( opt_PIC, WayName(..), v_Ways, v_Build_tag, - v_RTS_Build_tag ) +import PrelNames ( mAIN ) +import StaticFlags import {-# SOURCE #-} Packages (PackageState) import DriverPhases ( Phase(..), phaseInputExt ) import Config import CmdLineParser import Constants ( mAX_CONTEXT_REDUCTION_DEPTH ) import Panic -import UniqFM ( UniqFM ) 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 +106,8 @@ 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_llvm | Opt_D_dump_cpranal | Opt_D_dump_deriv | Opt_D_dump_ds @@ -145,6 +140,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 @@ -168,6 +164,7 @@ data DynFlag | Opt_WarnIncompletePatterns | Opt_WarnIncompletePatternsRecUpd | Opt_WarnMissingFields + | Opt_WarnMissingImportList | Opt_WarnMissingMethods | Opt_WarnMissingSigs | Opt_WarnNameShadowing @@ -180,77 +177,28 @@ data DynFlag | Opt_WarnUnusedMatches | Opt_WarnWarningsDeprecations | Opt_WarnDeprecatedFlags + | Opt_WarnDodgyExports | Opt_WarnDodgyImports | Opt_WarnOrphans | Opt_WarnTabs | Opt_WarnUnrecognisedPragmas | Opt_WarnDodgyForeignImports - - -- language opts - | Opt_OverlappingInstances - | Opt_UndecidableInstances - | Opt_IncoherentInstances - | Opt_MonomorphismRestriction - | Opt_MonoPatBinds - | Opt_ExtendedDefaultRules -- Use GHC's extended rules for defaulting - | Opt_ForeignFunctionInterface - | Opt_UnliftedFFITypes - | 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_StandaloneDeriving - | Opt_DeriveDataTypeable - | 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_PostfixOperators - | Opt_PatternGuards - | Opt_LiberalTypeSynonyms - | Opt_Rank2Types - | Opt_RankNTypes - | Opt_ImpredicativeTypes - | Opt_TypeOperators - | Opt_PackageImports + | Opt_WarnLazyUnliftedBindings + | Opt_WarnUnusedDoBind + | Opt_WarnWrongDoBind + | Opt_WarnAlternativeLayoutRuleTransitional | Opt_PrintExplicitForalls -- optimisation opts | Opt_Strictness | Opt_FullLaziness + | Opt_FloatIn + | Opt_Specialise | Opt_StaticArgumentTransformation | Opt_CSE | Opt_LiberateCase | Opt_SpecConstr - | Opt_IgnoreInterfacePragmas - | Opt_OmitInterfacePragmas | Opt_DoLambdaEtaExpansion | Opt_IgnoreAsserts | Opt_DoEtaReduction @@ -263,15 +211,26 @@ data DynFlag | Opt_RegsGraph -- do graph coloring register allocation | Opt_RegsIterative -- do iterative coalescing graph coloring register allocation + -- Interface files + | Opt_IgnoreInterfacePragmas + | Opt_OmitInterfacePragmas + | Opt_ExposeAllUnfoldings + + -- profiling opts + | Opt_AutoSccsOnAllToplevs + | Opt_AutoSccsOnExportedToplevs + | Opt_AutoSccsOnIndividualCafs + -- misc opts - | Opt_Cpp | Opt_Pp | Opt_ForceRecomp | Opt_DryRun | Opt_DoAsmMangling | Opt_ExcessPrecision + | Opt_EagerBlackHoling | Opt_ReadUserPackageConf | Opt_NoHsMain + | Opt_RtsOptsEnabled | Opt_SplitObjs | Opt_StgStats | Opt_HideAllPackages @@ -285,10 +244,18 @@ data DynFlag | Opt_PrintBindContents | Opt_GenManifest | Opt_EmbedManifest + | Opt_EmitExternalCore + | Opt_SharedImplib + | Opt_BuildingCabalPackage + | Opt_SSE2 + + -- temporary flags + | Opt_RunCPS | Opt_RunCPSZ | Opt_ConvertToZipCfgAndBack | Opt_AutoLinkPackages | Opt_ImplicitImportQualified + | Opt_TryNewCodeGen -- keeping stuff | Opt_KeepHiDiffs @@ -296,30 +263,105 @@ data DynFlag | Opt_KeepSFiles | Opt_KeepRawSFiles | Opt_KeepTmpFiles + | Opt_KeepRawTokenStream + | Opt_KeepLlvmFiles 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 { 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 .hcr output file - verbosity :: Int, -- ^ Verbosity level: see "DynFlags#verbosity_levels" + verbosity :: Int, -- ^ Verbosity level: see Note [Verbosity levels] optLevel :: Int, -- ^ Optimisation level simplPhases :: Int, -- ^ Number of simplifier phases maxSimplIterations :: Int, -- ^ Max simplifier iterations - shouldDumpSimplPhase :: SimplifierMode -> Bool, + shouldDumpSimplPhase :: Maybe String, ruleCheck :: Maybe String, + strictnessBefore :: [Int], -- ^ Additional demand analysis specConstrThreshold :: Maybe Int, -- ^ Threshold for SpecConstr 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], @@ -332,12 +374,16 @@ data DynFlags = DynFlags { thisPackage :: PackageId, -- ^ name of package currently being compiled -- ways - wayNames :: [WayName], -- ^ Way flags from the command line + ways :: [Way], -- ^ Way flags from the command line 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, + dylibInstallName :: Maybe String, hiDir :: Maybe String, stubDir :: Maybe String, @@ -365,6 +411,7 @@ data DynFlags = DynFlags { ghcUsagePath :: FilePath, -- Filled in by SysTools ghciUsagePath :: FilePath, -- ditto + rtsOpts :: Maybe String, hpcDir :: String, -- ^ Path to store the .mix files @@ -377,6 +424,8 @@ data DynFlags = DynFlags { opt_a :: [String], opt_l :: [String], opt_windres :: [String], + opt_lo :: [String], -- LLVM: llvm optimiser + opt_lc :: [String], -- LLVM: llc static compiler -- commands for particular phases pgm_L :: String, @@ -391,13 +440,14 @@ data DynFlags = DynFlags { pgm_T :: String, pgm_sysman :: String, pgm_windres :: String, + pgm_lo :: (String,[Option]), -- LLVM: opt llvm optimiser + pgm_lc :: (String,[Option]), -- LLVM: llc static compiler -- For ghc -M depMakefile :: FilePath, depIncludePkgDeps :: Bool, depExcludeMods :: [ModuleName], depSuffixes :: [String], - depWarnings :: Bool, -- Package flags extraPkgConfs :: [FilePath], @@ -412,11 +462,18 @@ data DynFlags = DynFlags { -- Package state -- NB. do not modify this field, it is calculated by -- Packages.initPackages and Packages.updatePackages. - pkgDatabase :: Maybe (UniqFM PackageConfig), + pkgDatabase :: Maybe [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], + languageFlags :: [LanguageFlag], -- | Message output action: use "ErrUtils" instead of this if you can log_action :: Severity -> SrcSpan -> PprStyle -> Message -> IO (), @@ -424,18 +481,43 @@ data DynFlags = DynFlags { haddockOptions :: Maybe String } +wayNames :: DynFlags -> [WayName] +wayNames = map wayName . ways + +-- | 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. + | HscLlvm -- ^ Generate assembly using the llvm 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? isObjectTarget :: HscTarget -> Bool isObjectTarget HscC = True isObjectTarget HscAsm = True +isObjectTarget HscLlvm = True isObjectTarget _ = False -- | The 'GhcMode' tells us whether we're doing multi-module @@ -450,6 +532,11 @@ data GhcMode | MkDepend -- ^ @ghc -M@, see "Finder" for why we need this deriving Eq +instance Outputable GhcMode where + ppr CompManager = ptext (sLit "CompManager") + ppr OneShot = ptext (sLit "OneShot") + ppr MkDepend = ptext (sLit "MkDepend") + isOneShot :: GhcMode -> Bool isOneShot OneShot = True isOneShot _other = False @@ -458,7 +545,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) @@ -466,8 +554,16 @@ 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 _ = opt_Ticky + -- XXX -ticky is a static flag, because it implies -debug which is also + -- static. If the way flags were made dynamic, we could fix this. + data PackageFlag = ExposePackage String + | ExposePackageId String | HidePackage String | IgnorePackage String deriving Eq @@ -493,12 +589,14 @@ initDynFlags :: DynFlags -> IO DynFlags initDynFlags dflags = do -- someday these will be dynamic flags 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 + ways = ways, + buildTag = mkBuildTag (filter (not . wayRTSOnly) ways), + rtsBuildTag = mkBuildTag ways, + filesToClean = refFilesToClean, + dirsToClean = refDirsToClean } -- | The normal 'DynFlags'. Note that they is not suitable for use in this form @@ -508,8 +606,6 @@ defaultDynFlags = DynFlags { ghcMode = CompManager, ghcLink = LinkBinary, - coreToDo = Nothing, - stgToDo = Nothing, hscTarget = defaultHscTarget, hscOutName = "", extCoreName = "", @@ -517,11 +613,16 @@ defaultDynFlags = optLevel = 0, simplPhases = 2, maxSimplIterations = 4, - shouldDumpSimplPhase = const False, + shouldDumpSimplPhase = Nothing, ruleCheck = Nothing, specConstrThreshold = Just 200, specConstrCount = Just 3, liberateCaseThreshold = Just 200, + strictnessBefore = [], + +#ifndef OMIT_NATIVE_CODEGEN + targetPlatform = defaultTargetPlatform, +#endif stolen_x86_regs = 4, cmdlineHcIncludes = [], importPaths = ["."], @@ -534,6 +635,7 @@ defaultDynFlags = thisPackage = mainPackageId, objectDir = Nothing, + dylibInstallName = Nothing, hiDir = Nothing, stubDir = Nothing, @@ -543,7 +645,7 @@ defaultDynFlags = outputFile = Nothing, outputHi = Nothing, - dynLibLoader = Deployable, + dynLibLoader = SystemDependent, dumpPrefix = Nothing, dumpPrefixForce = Nothing, includePaths = [], @@ -551,12 +653,13 @@ defaultDynFlags = frameworkPaths = [], cmdlineFrameworks = [], tmpDir = cDEFAULT_TMPDIR, + rtsOpts = Nothing, hpcDir = ".hpc", opt_L = [], opt_P = (if opt_PIC - then ["-D__PIC__"] + then ["-D__PIC__", "-U __PIC__"] -- this list is reversed else []), opt_F = [], opt_c = [], @@ -564,14 +667,17 @@ defaultDynFlags = opt_m = [], opt_l = [], opt_windres = [], + opt_lo = [], + opt_lc = [], extraPkgConfs = [], packageFlags = [], pkgDatabase = Nothing, pkgState = panic "no package state yet: call GHC.setSessionDynFlags", - wayNames = panic "defaultDynFlags: No wayNames", + ways = panic "defaultDynFlags: No ways", 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", @@ -589,30 +695,28 @@ defaultDynFlags = pgm_T = panic "defaultDynFlags: No pgm_T", pgm_sysman = panic "defaultDynFlags: No pgm_sysman", pgm_windres = panic "defaultDynFlags: No pgm_windres", + pgm_lo = panic "defaultDynFlags: No pgm_lo", + pgm_lc = panic "defaultDynFlags: No pgm_lc", -- end of initSysTools values -- ghc -M values depMakefile = "Makefile", 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, 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_MethodSharing, Opt_DoAsmMangling, + Opt_SharedImplib, + Opt_GenManifest, Opt_EmbedManifest, Opt_PrintBindContents @@ -621,6 +725,17 @@ defaultDynFlags = -- 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) @@ -634,9 +749,8 @@ defaultDynFlags = } {- - #verbosity_levels# - Verbosity levels: - +Note [Verbosity levels] +~~~~~~~~~~~~~~~~~~~~~~~ 0 | print errors & warnings only 1 | minimal verbosity: print "compiling M ... done." for each module. 2 | equivalent to -dshow-passes @@ -645,17 +759,46 @@ defaultDynFlags = 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 -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) } + +-- | 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 @@ -671,9 +814,11 @@ getVerbFlag dflags | verbosity dflags >= 3 = "-v" | otherwise = "" -setObjectDir, setHiDir, setStubDir, setObjectSuf, setHiSuf, setHcSuf, parseDynLibLoaderMode, +setObjectDir, setHiDir, setStubDir, setOutputDir, setDylibInstallName, + setObjectSuf, setHiSuf, setHcSuf, parseDynLibLoaderMode, setPgmP, setPgmL, setPgmF, setPgmc, setPgmm, setPgms, setPgma, setPgml, setPgmdll, setPgmwindres, - addOptL, addOptP, addOptF, addOptc, addOptm, addOpta, addOptl, addOptwindres, + setPgmlo, setPgmlc, + addOptL, addOptP, addOptF, addOptc, addOptm, addOpta, addOptl, addOptwindres, addOptlo, addOptlc, addCmdlineFramework, addHaddockOpts :: String -> DynFlags -> DynFlags setOutputFile, setOutputHi, setDumpPrefixForce @@ -684,6 +829,8 @@ 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 +setDylibInstallName f d = d{ dylibInstallName = Just f} setObjectSuf f d = d{ objectSuf = f} setHiSuf f d = d{ hiSuf = f} @@ -699,7 +846,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} @@ -716,6 +863,8 @@ 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} +setPgmlo f d = d{ pgm_lo = (f,[])} +setPgmlc f d = d{ pgm_lc = (f,[])} addOptL f d = d{ opt_L = f : opt_L d} addOptP f d = d{ opt_P = f : opt_P d} @@ -725,6 +874,8 @@ 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} +addOptlo f d = d{ opt_lo = f : opt_lo d} +addOptlc f d = d{ opt_lc = f : opt_lc d} setDepMakefile :: FilePath -> DynFlags -> DynFlags setDepMakefile f d = d { depMakefile = deOptDep f } @@ -739,14 +890,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 @@ -770,6 +918,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 @@ -798,6 +950,8 @@ optLevelFlags , ([1,2], Opt_Strictness) , ([1,2], Opt_CSE) , ([1,2], Opt_FullLaziness) + , ([1,2], Opt_Specialise) + , ([1,2], Opt_FloatIn) , ([2], Opt_LiberateCase) , ([2], Opt_SpecConstr) @@ -831,7 +985,10 @@ standardWarnings Opt_WarnMissingFields, Opt_WarnMissingMethods, Opt_WarnDuplicateExports, - Opt_WarnDodgyForeignImports + Opt_WarnLazyUnliftedBindings, + Opt_WarnDodgyForeignImports, + Opt_WarnWrongDoBind, + Opt_WarnAlternativeLayoutRuleTransitional ] minusWOpts :: [DynFlag] @@ -841,6 +998,7 @@ minusWOpts Opt_WarnUnusedMatches, Opt_WarnUnusedImports, Opt_WarnIncompletePatterns, + Opt_WarnDodgyExports, Opt_WarnDodgyImports ] @@ -851,7 +1009,8 @@ minusWallOpts Opt_WarnNameShadowing, Opt_WarnMissingSigs, Opt_WarnHiShadows, - Opt_WarnOrphans + Opt_WarnOrphans, + Opt_WarnUnusedDoBind ] -- minuswRemovesOpts should be every warning option @@ -867,210 +1026,6 @@ minuswRemovesOpts ] -- ----------------------------------------------------------------------------- --- CoreToDo: abstraction of core-to-core passes to run. - -data CoreToDo -- These are diff core-to-core passes, - -- which may be invoked in any order, - -- as many times as you like. - - = CoreDoSimplify -- The core-to-core simplifier. - SimplifierMode - [SimplifierSwitch] - -- Each run of the simplifier can take a different - -- set of simplifier-specific flags. - | CoreDoFloatInwards - | CoreDoFloatOutwards FloatOutSwitches - | CoreLiberateCase - | CoreDoPrintCore - | CoreDoStaticArgs - | CoreDoStrictness - | CoreDoWorkerWrapper - | CoreDoSpecialising - | CoreDoSpecConstr - | CoreDoOldStrictness - | CoreDoGlomBinds - | CoreCSE - | CoreDoRuleCheck Int{-CompilerPhase-} String -- Check for non-application of rules - -- matching this string - | CoreDoVectorisation DPHBackend - | CoreDoNothing -- Useful when building up - | CoreDoPasses [CoreToDo] -- lists of these things - -data SimplifierMode -- See comments in SimplMonad - = SimplGently - | SimplPhase Int [String] - -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 - - --- The core-to-core pass ordering is derived from the DynFlags: -runWhen :: Bool -> CoreToDo -> CoreToDo -runWhen True do_this = do_this -runWhen False _ = CoreDoNothing - -runMaybe :: Maybe a -> (a -> CoreToDo) -> CoreToDo -runMaybe (Just x) f = f x -runMaybe Nothing _ = CoreDoNothing - -getCoreToDo :: DynFlags -> [CoreToDo] -getCoreToDo dflags - | Just todo <- coreToDo dflags = todo -- set explicitly by user - | otherwise = core_todo - where - opt_level = optLevel dflags - phases = simplPhases dflags - max_iter = maxSimplIterations dflags - strictness = dopt Opt_Strictness dflags - full_laziness = dopt Opt_FullLaziness dflags - cse = dopt Opt_CSE dflags - spec_constr = dopt Opt_SpecConstr dflags - liberate_case = dopt Opt_LiberateCase dflags - rule_check = ruleCheck dflags - static_args = dopt Opt_StaticArgumentTransformation dflags - - maybe_rule_check phase = runMaybe rule_check (CoreDoRuleCheck phase) - - simpl_phase phase names iter - = CoreDoPasses - [ CoreDoSimplify (SimplPhase phase names) [ - MaxSimplifierIterations iter - ], - maybe_rule_check phase - ] - - vectorisation - = runWhen (dopt Opt_Vectorise dflags) - $ CoreDoPasses [ simpl_gently, CoreDoVectorisation (dphBackend dflags) ] - - - -- By default, we have 2 phases before phase 0. - - -- Want to run with inline phase 2 after the specialiser to give - -- maximum chance for fusion to work before we inline build/augment - -- in phase 1. This made a difference in 'ansi' where an - -- overloaded function wasn't inlined till too late. - - -- Need phase 1 so that build/augment get - -- inlined. I found that spectral/hartel/genfft lost some useful - -- strictness in the function sumcode' if augment is not inlined - -- before strictness analysis runs - simpl_phases = CoreDoPasses [ simpl_phase phase ["main"] max_iter - | phase <- [phases, phases-1 .. 1] ] - - - -- initial simplify: mk specialiser happy: minimum effort please - simpl_gently = CoreDoSimplify SimplGently [ - -- Simplify "gently" - -- Don't inline anything till full laziness has bitten - -- In particular, inlining wrappers inhibits floating - -- e.g. ...(case f x of ...)... - -- ==> ...(case (case x of I# x# -> fw x#) of ...)... - -- ==> ...(case x of I# x# -> case fw x# of ...)... - -- and now the redex (f x) isn't floatable any more - -- Similarly, don't apply any rules until after full - -- laziness. Notably, list fusion can prevent floating. - - NoCaseOfCase, -- Don't do case-of-case transformations. - -- This makes full laziness work better - MaxSimplifierIterations max_iter - ] - - core_todo = - if opt_level == 0 then - [vectorisation, - simpl_phase 0 ["final"] max_iter] - else {- opt_level >= 1 -} [ - - -- We want to do the static argument transform before full laziness as it - -- may expose extra opportunities to float things outwards. However, to fix - -- up the output of the transformation we need at do at least one simplify - -- after this before anything else - runWhen static_args (CoreDoPasses [ simpl_gently, CoreDoStaticArgs ]), - - -- We run vectorisation here for now, but we might also try to run - -- it later - vectorisation, - - -- initial simplify: mk specialiser happy: minimum effort please - simpl_gently, - - -- Specialisation is best done before full laziness - -- so that overloaded functions have all their dictionary lambdas manifest - CoreDoSpecialising, - - runWhen full_laziness (CoreDoFloatOutwards (FloatOutSw False False)), - - CoreDoFloatInwards, - - simpl_phases, - - -- Phase 0: allow all Ids to be inlined now - -- This gets foldr inlined before strictness analysis - - -- At least 3 iterations because otherwise we land up with - -- huge dead expressions because of an infelicity in the - -- simpifier. - -- let k = BIG in foldr k z xs - -- ==> let k = BIG in letrec go = \xs -> ...(k x).... in go xs - -- ==> let k = BIG in letrec go = \xs -> ...(BIG x).... in go xs - -- Don't stop now! - simpl_phase 0 ["main"] (max max_iter 3), - - -#ifdef OLD_STRICTNESS - CoreDoOldStrictness, -#endif - runWhen strictness (CoreDoPasses [ - CoreDoStrictness, - CoreDoWorkerWrapper, - CoreDoGlomBinds, - simpl_phase 0 ["post-worker-wrapper"] max_iter - ]), - - runWhen full_laziness - (CoreDoFloatOutwards (FloatOutSw False -- Not lambdas - True)), -- Float constants - -- 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 - -- catch it. For the record, the redex is - -- f_el22 (f_el21 r_midblock) - - - runWhen cse CoreCSE, - -- We want CSE to follow the final full-laziness pass, because it may - -- succeed in commoning up things floated out by full laziness. - -- CSE used to rely on the no-shadowing invariant, but it doesn't any more - - CoreDoFloatInwards, - - maybe_rule_check 0, - - -- Case-liberation for -O2. This should be after - -- strictness analysis and the simplification which follows it. - runWhen liberate_case (CoreDoPasses [ - CoreLiberateCase, - simpl_phase 0 ["post-liberate-case"] max_iter - ]), -- Run the simplifier after LiberateCase to vastly - -- reduce the possiblility of shadowing - -- Reason: see Note [Shadowing] in SpecConstr.lhs - - runWhen spec_constr CoreDoSpecConstr, - - maybe_rule_check 0, - - -- Final clean-up simplification: - simpl_phase 0 ["final"] max_iter - ] - --- ----------------------------------------------------------------------------- -- StgToDo: abstraction of stg-to-stg passes to run. data StgToDo @@ -1081,8 +1036,7 @@ data StgToDo getStgToDo :: DynFlags -> [StgToDo] getStgToDo dflags - | Just todo <- stgToDo dflags = todo -- set explicitly by user - | otherwise = todo2 + = todo2 where stg_stats = dopt Opt_StgStats dflags @@ -1101,21 +1055,27 @@ allFlags = map ('-':) $ [ flagName flag | flag <- dynamic_flags, ok (flagOptKind flag) ] ++ map ("fno-"++) flags ++ map ("f"++) flags ++ - map ("X"++) supportedLanguages ++ - map ("XNo"++) supportedLanguages + map ("f"++) flags' ++ + 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 - , 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)) Supported + , Flag "#include" (HasArg (addCmdlineHCInclude)) + (DeprecatedFullText "-#include and INCLUDE pragmas are deprecated: They no longer have any effect") , Flag "v" (OptIntSuffix setVerbosity) Supported ------- Specific phases -------------------------------------------- + -- need to appear before -pgmL to be parsed as LLVM flags. + , Flag "pgmlo" (HasArg (upd . setPgmlo)) Supported + , Flag "pgmlc" (HasArg (upd . setPgmlc)) Supported + , Flag "pgmL" (HasArg (upd . setPgmL)) Supported , Flag "pgmP" (HasArg (upd . setPgmP)) Supported , Flag "pgmF" (HasArg (upd . setPgmF)) Supported @@ -1127,6 +1087,10 @@ dynamic_flags = [ , Flag "pgmdll" (HasArg (upd . setPgmdll)) Supported , Flag "pgmwindres" (HasArg (upd . setPgmwindres)) Supported + -- need to appear before -optl/-opta to be parsed as LLVM flags. + , Flag "optlo" (HasArg (upd . addOptlo)) Supported + , Flag "optlc" (HasArg (upd . addOptlc)) Supported + , Flag "optL" (HasArg (upd . addOptL)) Supported , Flag "optP" (HasArg (upd . addOptP)) Supported , Flag "optF" (HasArg (upd . addOptF)) Supported @@ -1147,7 +1111,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))) @@ -1161,14 +1125,13 @@ dynamic_flags = [ (Deprecated "Use -exclude-module instead") -------- Linking ---------------------------------------------------- - , Flag "c" (NoArg (upd $ \d -> d{ ghcLink=NoLink } )) - Supported , Flag "no-link" (NoArg (upd $ \d -> d{ ghcLink=NoLink } )) - (Deprecated "Use -c instead") + Supported , Flag "shared" (NoArg (upd $ \d -> d{ ghcLink=LinkDynLib } )) Supported , Flag "dynload" (HasArg (upd . parseDynLibLoaderMode)) Supported + , Flag "dylib-install-name" (HasArg (upd . setDylibInstallName)) Supported ------- Libraries --------------------------------------------------- , Flag "L" (Prefix addLibraryPath ) Supported @@ -1189,6 +1152,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 @@ -1200,12 +1164,17 @@ dynamic_flags = [ , Flag "keep-s-files" (NoArg (setDynFlag Opt_KeepSFiles)) Supported , Flag "keep-raw-s-file" (NoArg (setDynFlag Opt_KeepRawSFiles)) Supported , Flag "keep-raw-s-files" (NoArg (setDynFlag Opt_KeepRawSFiles)) Supported + , Flag "keep-llvm-file" (NoArg (setDynFlag Opt_KeepLlvmFiles)) Supported + , Flag "keep-llvm-files" (NoArg (setDynFlag Opt_KeepLlvmFiles)) Supported -- This only makes sense as plural , Flag "keep-tmp-files" (NoArg (setDynFlag Opt_KeepTmpFiles)) Supported ------- Miscellaneous ---------------------------------------------- , Flag "no-auto-link-packages" (NoArg (unSetDynFlag Opt_AutoLinkPackages)) Supported , Flag "no-hs-main" (NoArg (setDynFlag Opt_NoHsMain)) Supported + , Flag "with-rtsopts" (HasArg setRtsOpts) Supported + , Flag "rtsopts" (NoArg (setDynFlag Opt_RtsOptsEnabled)) Supported + , Flag "no-rtsopts" (NoArg (unSetDynFlag Opt_RtsOptsEnabled)) Supported , Flag "main-is" (SepArg setMainIs ) Supported , Flag "haddock" (NoArg (setDynFlag Opt_Haddock)) Supported , Flag "haddock-opts" (HasArg (upd . addHaddockOpts)) Supported @@ -1217,20 +1186,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 @@ -1269,6 +1224,11 @@ 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-llvm" (NoArg (do { setObjTarget HscLlvm + ; setDumpFlag' Opt_D_dump_llvm})) + Supported , Flag "ddump-cpranal" (setDumpFlag Opt_D_dump_cpranal) Supported , Flag "ddump-deriv" (setDumpFlag Opt_D_dump_deriv) @@ -1331,7 +1291,8 @@ dynamic_flags = [ Supported , Flag "dsource-stats" (setDumpFlag Opt_D_source_stats) Supported - , Flag "dverbose-core2core" (NoArg setVerboseCore2Core) + , Flag "dverbose-core2core" (NoArg (do { setVerbosity (Just 2) + ; setVerboseCore2Core })) Supported , Flag "dverbose-stg2stg" (setDumpFlag Opt_D_verbose_stg2stg) Supported @@ -1351,6 +1312,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 @@ -1361,7 +1324,7 @@ dynamic_flags = [ , Flag "dasm-lint" (NoArg (setDynFlag Opt_DoAsmLinting)) Supported , Flag "dshow-passes" - (NoArg (do setDynFlag Opt_ForceRecomp + (NoArg (do forceRecompile setVerbosity (Just 2))) Supported , Flag "dfaststring-stats" (NoArg (setDynFlag Opt_D_faststring_stats)) @@ -1376,6 +1339,9 @@ dynamic_flags = [ , Flag "monly-4-regs" (NoArg (upd (\s -> s{stolen_x86_regs = 4}) )) Supported + , Flag "msse2" (NoArg (setDynFlag Opt_SSE2)) + Supported + ------ Warning opts ------------------------------------------------- , Flag "W" (NoArg (mapM_ setDynFlag minusWOpts)) Supported @@ -1432,6 +1398,42 @@ dynamic_flags = [ (IntSuffix $ \n -> upd $ \dfs -> dfs{ ctxtStkDepth = n }) Supported + , Flag "fstrictness-before" + (IntSuffix (\n -> upd (\dfs -> dfs{ strictnessBefore = n : strictnessBefore dfs }))) + 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" @@ -1447,34 +1449,59 @@ dynamic_flags = [ ------ Compiler flags ----------------------------------------------- , Flag "fasm" (NoArg (setObjTarget HscAsm)) Supported - , Flag "fvia-c" (NoArg (setObjTarget HscC)) Supported - , Flag "fvia-C" (NoArg (setObjTarget HscC)) Supported - - , Flag "fno-code" (NoArg (setTarget HscNothing)) 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 } + setTarget HscNothing)) + 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 - , 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 - ++ 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 = [ + ------- 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-id" (HasArg exposePackageId) 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 ()) - -> (String, DynFlag, Bool -> Deprecated) + -> (flag -> DynP ()) + -> (String, flag, Bool -> Deprecated) -> 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 - = Deprecated ("use -X" ++ flag ++ " or pragma {-# LANGUAGE " ++ flag ++ "#-} instead") + = Deprecated ("use -X" ++ flag ++ " or pragma {-# LANGUAGE " ++ flag ++ " #-} instead") where flag | turn_on = lang | otherwise = "No"++lang @@ -1489,6 +1516,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 ), @@ -1496,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-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 ), @@ -1512,8 +1541,15 @@ 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 ), + ( "warn-alternative-layout-rule-transitional", Opt_WarnAlternativeLayoutRuleTransitional, const Supported ), ( "print-explicit-foralls", Opt_PrintExplicitForalls, const Supported ), ( "strictness", Opt_Strictness, const Supported ), + ( "specialise", Opt_Specialise, const Supported ), + ( "float-in", Opt_FloatIn, const Supported ), ( "static-argument-transformation", Opt_StaticArgumentTransformation, const Supported ), ( "full-laziness", Opt_FullLaziness, const Supported ), ( "liberate-case", Opt_LiberateCase, const Supported ), @@ -1521,6 +1557,7 @@ fFlags = [ ( "cse", Opt_CSE, const Supported ), ( "ignore-interface-pragmas", Opt_IgnoreInterfacePragmas, const Supported ), ( "omit-interface-pragmas", Opt_OmitInterfacePragmas, const Supported ), + ( "expose-all-unfoldings", Opt_ExposeAllUnfoldings, const Supported ), ( "do-lambda-eta-expansion", Opt_DoLambdaEtaExpansion, const Supported ), ( "ignore-asserts", Opt_IgnoreAsserts, const Supported ), ( "do-eta-reduction", Opt_DoEtaReduction, const Supported ), @@ -1529,6 +1566,7 @@ fFlags = [ ( "method-sharing", Opt_MethodSharing, const Supported ), ( "dicts-cheap", Opt_DictsCheap, 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 ), @@ -1539,11 +1577,24 @@ 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 ), ( "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\@ flags can all be reversed with @-fno-\@ +fLangFlags :: [(String, LanguageFlag, Bool -> Deprecated)] +fLangFlags = [ ( "th", Opt_TemplateHaskell, deprecatedForLanguage "TemplateHaskell" ), ( "fi", Opt_ForeignFunctionInterface, @@ -1575,24 +1626,22 @@ fFlags = [ ( "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 ), - ( "implicit-import-qualified", Opt_ImplicitImportQualified, const Supported ) + deprecatedForLanguage "IncoherentInstances" ) ] supportedLanguages :: [String] -supportedLanguages = [ name | (name, _, _) <- xFlags ] +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 flags can all be reversed with -XNo -xFlags :: [(String, DynFlag, Bool -> Deprecated)] +xFlags :: [(String, LanguageFlag, 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 ), @@ -1604,12 +1653,16 @@ 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 ), - ( "ImpredicativeTypes", Opt_ImpredicativeTypes, const Supported ), + ( "ImpredicativeTypes", Opt_ImpredicativeTypes, + const $ Deprecated "impredicative polymorphism will be simplified or removed in GHC 6.14" ), ( "TypeOperators", Opt_TypeOperators, const Supported ), - ( "RecursiveDo", Opt_RecursiveDo, const Supported ), + ( "RecursiveDo", Opt_RecursiveDo, + deprecatedForLanguage "DoRec"), + ( "DoRec", Opt_DoRec, const Supported ), ( "Arrows", Opt_Arrows, const Supported ), ( "PArr", Opt_PArr, const Supported ), ( "TemplateHaskell", Opt_TemplateHaskell, const Supported ), @@ -1629,8 +1682,16 @@ xFlags = [ ( "BangPatterns", Opt_BangPatterns, const Supported ), -- On by default: ( "MonomorphismRestriction", Opt_MonomorphismRestriction, const Supported ), + -- On by default: + ( "NPlusKPatterns", Opt_NPlusKPatterns, const Supported ), -- On by default (which is not strictly H98): ( "MonoPatBinds", Opt_MonoPatBinds, 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 ), ( "ImplicitParams", Opt_ImplicitParams, const Supported ), @@ -1642,6 +1703,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 ), @@ -1652,22 +1716,49 @@ 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 $ Deprecated "The new qualified operator syntax was rejected by Haskell'" ) ] -impliedFlags :: [(DynFlag, DynFlag)] +impliedFlags :: [(LanguageFlag, LanguageFlag)] impliedFlags - = [ (Opt_GADTs, Opt_RelaxedPolyRec) -- We want type-sig variables to + = [ (Opt_RankNTypes, Opt_ExplicitForAll) + , (Opt_Rank2Types, Opt_ExplicitForAll) + , (Opt_ScopedTypeVariables, Opt_ExplicitForAll) + , (Opt_LiberalTypeSynonyms, Opt_ExplicitForAll) + , (Opt_ExistentialQuantification, Opt_ExplicitForAll) + , (Opt_PolymorphicComponents, Opt_ExplicitForAll) + + , (Opt_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) + + -- Record wild-cards implies field disambiguation + -- Otherwise if you write (C {..}) you may well get + -- stuff like " 'a' not in scope ", which is a bit silly + -- if the compiler has just filled in field 'a' of constructor 'C' + , (Opt_RecordWildCards, Opt_DisambiguateRecordFields) ] -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 = [ - Opt_PrintExplicitForalls - , Opt_ForeignFunctionInterface + Opt_ForeignFunctionInterface , Opt_UnliftedFFITypes , Opt_GADTs , Opt_ImplicitParams @@ -1676,6 +1767,9 @@ glasgowExtsFlags = [ , Opt_TypeSynonymInstances , Opt_StandaloneDeriving , Opt_DeriveDataTypeable + , Opt_DeriveFunctor + , Opt_DeriveFoldable + , Opt_DeriveTraversable , Opt_FlexibleContexts , Opt_FlexibleInstances , Opt_ConstrainedClassMethods @@ -1689,9 +1783,8 @@ glasgowExtsFlags = [ , Opt_PatternGuards , Opt_LiberalTypeSynonyms , Opt_RankNTypes - , Opt_ImpredicativeTypes , Opt_TypeOperators - , Opt_RecursiveDo + , Opt_DoRec , Opt_ParallelListComp , Opt_EmptyDataDecls , Opt_KindSignatures @@ -1701,7 +1794,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). @@ -1710,7 +1803,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_ dflags0 args pkg_flags = do -- XXX Legacy support code -- We used to accept things like -- optdep-f -optdepdepend @@ -1722,10 +1829,28 @@ parseDynamicFlags dflags args = do f (x : xs) = x : f xs f xs = xs args' = f args - let ((leftover, errs, warns), dflags') - = runCmdLine (processArgs dynamic_flags args') dflags + + -- 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), dflags1) + = runCmdLine (processArgs flag_spec args') dflags0 when (not (null errs)) $ ghcError $ errorsToGhcException errs - return (dflags', leftover, warns) + + -- Cannot use -fPIC with registerised -fvia-C, because the mangler + -- isn't up to the job. We know that if hscTarget == HscC, then the + -- user has explicitly used -fvia-C, because -fasm is the default, + -- unless there is no NCG on this platform. The latter case is + -- checked when the -fPIC flag is parsed. + -- + let (pic_warns, dflags2) = + if opt_PIC && hscTarget dflags1 == HscC && cGhcUnregisterised == "NO" + then ([L noSrcSpan $ "Warning: -fvia-C is incompatible with -fPIC; ignoring -fvia-C"], + dflags1{ hscTarget = HscAsm }) + else ([], dflags1) + + return (dflags2, leftover, pic_warns ++ warns) type DynP = CmdLineP DynFlags @@ -1736,68 +1861,59 @@ upd f = do -------------------------- 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 - -- 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) -unSetDynFlag f = upd (\dfs -> dopt_unset dfs f) +unSetLanguageFlag f = upd (\dfs -> lopt_unset dfs f) -------------------------- setDumpFlag :: DynFlag -> OptKind DynP -setDumpFlag dump_flag - | force_recomp = NoArg (setDynFlag Opt_ForceRecomp >> setDynFlag dump_flag) - | otherwise = NoArg (setDynFlag dump_flag) +setDumpFlag dump_flag = NoArg (setDumpFlag' dump_flag) + +setDumpFlag' :: DynFlag -> DynP () +setDumpFlag' dump_flag + = do { setDynFlag dump_flag + ; when want_recomp forceRecompile } where - -- Whenver we -ddump, switch off the recompilation checker, - -- else you don't see the dump! - -- However, certain dumpy-things are really interested in what's going + -- Certain dumpy-things are really interested in what's going -- on during recompilation checking, so in those cases we -- don't want to turn it off. - force_recomp = dump_flag `notElem` [Opt_D_dump_if_trace, - Opt_D_dump_hi_diffs] + want_recomp = dump_flag `notElem` [Opt_D_dump_if_trace, + Opt_D_dump_hi_diffs] + +forceRecompile :: DynP () +-- Whenver we -ddump, force recompilation (by switching off the +-- recompilation checker), else you don't see the dump! However, +-- don't switch it off in --make mode, else *everything* gets +-- recompiled which probably isn't what you want +forceRecompile = do { dfs <- getCmdLineState + ; when (force_recomp dfs) (setDynFlag Opt_ForceRecomp) } + where + force_recomp dfs = isOneShot (ghcMode dfs) setVerboseCore2Core :: DynP () -setVerboseCore2Core = do setDynFlag Opt_ForceRecomp - setDynFlag Opt_D_verbose_core2core - upd (\s -> s { shouldDumpSimplPhase = const True }) +setVerboseCore2Core = do forceRecompile + setDynFlag Opt_D_verbose_core2core + upd (\dfs -> dfs { shouldDumpSimplPhase = Nothing }) + setDumpSimplPhases :: String -> DynP () -setDumpSimplPhases s = do setDynFlag Opt_ForceRecomp - upd (\s -> s { shouldDumpSimplPhase = spec }) +setDumpSimplPhases s = do forceRecompile + upd (\dfs -> dfs { shouldDumpSimplPhase = Just spec }) where - spec :: SimplifierMode -> Bool - spec = join (||) - . map (join (&&) . map match . split ':') - . split ',' - $ case s of - '=' : s' -> s' - _ -> s - - join :: (Bool -> Bool -> Bool) - -> [SimplifierMode -> Bool] - -> SimplifierMode -> Bool - join _ [] = const True - join op ss = foldr1 (\f g x -> f x `op` g x) ss - - match :: String -> SimplifierMode -> Bool - match "" = const True - match s = case reads s of - [(n,"")] -> phase_num n - _ -> phase_name s - - phase_num :: Int -> SimplifierMode -> Bool - phase_num n (SimplPhase k _) = n == k - phase_num _ _ = False - - phase_name :: String -> SimplifierMode -> Bool - phase_name s SimplGently = s == "gentle" - phase_name s (SimplPhase _ ss) = s `elem` ss + spec = case s of { ('=' : s') -> s'; _ -> s } setVerbosity :: Maybe Int -> DynP () setVerbosity mb_n = upd (\dfs -> dfs{ verbosity = mb_n `orElse` 3 }) @@ -1808,22 +1924,18 @@ addCmdlineHCInclude a = upd (\s -> s{cmdlineHcIncludes = a : cmdlineHcIncludes extraPkgConf_ :: FilePath -> DynP () extraPkgConf_ p = upd (\s -> s{ extraPkgConfs = p : extraPkgConfs s }) -exposePackage, hidePackage, ignorePackage :: String -> DynP () +exposePackage, exposePackageId, hidePackage, ignorePackage :: String -> DynP () exposePackage p = upd (\s -> s{ packageFlags = ExposePackage p : packageFlags s }) +exposePackageId p = + upd (\s -> s{ packageFlags = ExposePackageId p : packageFlags s }) hidePackage p = upd (\s -> s{ packageFlags = HidePackage p : packageFlags s }) ignorePackage p = upd (\s -> s{ packageFlags = IgnorePackage p : packageFlags s }) setPackageName :: String -> DynFlags -> DynFlags -setPackageName p - | Nothing <- unpackPackageId pid - = ghcError (CmdLineError ("cannot parse \'" ++ p ++ "\' as a package identifier")) - | otherwise - = \s -> s{ thisPackage = pid } - where - pid = stringToPackageId p +setPackageName p s = s{ thisPackage = stringToPackageId p } -- If we're linking a binary, then only targets that produce object -- code are allowed (requests for other target types are ignored). @@ -1862,11 +1974,15 @@ 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 }) @@ -1888,6 +2004,12 @@ setDPHBackend backend dph_packages DPHPar = ["dph-prim-par", "dph-par"] dph_packages DPHSeq = ["dph-prim-seq", "dph-seq"] +dphPackage :: DynFlags -> PackageId +dphPackage dflags = case dphBackend dflags of + DPHPar -> dphParPackageId + DPHSeq -> dphSeqPackageId + DPHThis -> thisPackage dflags + setMainIs :: String -> DynP () setMainIs arg | not (null main_fn) && isLower (head main_fn) @@ -1903,13 +2025,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 @@ -1995,6 +2110,12 @@ setTmpDir dir dflags = dflags{ tmpDir = normalise dir } -- seem necessary now --SDM 7/2/2008 ----------------------------------------------------------------------------- +-- RTS opts + +setRtsOpts :: String -> DynP () +setRtsOpts arg = upd $ \ d -> d {rtsOpts = Just arg} + +----------------------------------------------------------------------------- -- Hpc stuff setOptHpcDir :: String -> DynP () @@ -2051,10 +2172,20 @@ machdepCCOpts _dflags -- -fomit-frame-pointer : *must* in .hc files; because we're stealing -- the fp (%ebp) for our register maps. = let n_regs = stolen_x86_regs _dflags - sta = opt_Static in - ( [ if sta then "-DDONT_WANT_WIN32_DLL_SUPPORT" else "" + ( +#if darwin_TARGET_OS + -- By default, gcc on OS X will generate SSE + -- instructions, which need things 16-byte aligned, + -- but we don't 16-byte align things. Thus drop + -- back to generic i686 compatibility. Trac #2983. + -- + -- Since Snow Leopard (10.6), gcc defaults to x86_64. + ["-march=i686", "-m32"], +#else + [ if opt_Static then "-DDONT_WANT_WIN32_DLL_SUPPORT" else "" ], +#endif [ "-fno-defer-pop", "-fomit-frame-pointer", -- we want -fno-builtin, because when gcc inlines @@ -2068,7 +2199,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 @@ -2108,18 +2245,23 @@ 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__"] + -- 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 = [] #endif @@ -2133,21 +2275,28 @@ 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), + ("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 llvm code generator", String cGhcWithLlvmCodeGen), + ("Support SMP", String cGhcWithSMP), + ("Unregisterised", String cGhcUnregisterised), + ("Tables next to code", String cGhcEnableTablesNextToCode), + ("RTS ways", String cGhcRTSWays), + ("Leading underscore", String cLeadingUnderscore), + ("Debug on", String (show debugIsOn)), + ("LibDir", FromDynFlags topDir), + ("Global Package DB", FromDynFlags systemPackageConfig) ]