Dynamic flags
(c) The University of Glasgow 2005
- data DynFlag
- = Opt_D_dump_cmm
- | Opt_D_dump_cmmz
- | Opt_D_dump_cmmz_pretty
- | Opt_D_dump_cps_cmm
- | Opt_D_dump_cvt_cmm
- | Opt_D_dump_asm
- | Opt_D_dump_asm_native
- | Opt_D_dump_asm_liveness
- | Opt_D_dump_asm_coalesce
- | Opt_D_dump_asm_regalloc
- | 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
- | Opt_D_dump_flatC
- | Opt_D_dump_foreign
- | Opt_D_dump_inlinings
- | Opt_D_dump_rule_firings
- | Opt_D_dump_occur_anal
- | Opt_D_dump_parsed
- | Opt_D_dump_rn
- | Opt_D_dump_simpl
- | Opt_D_dump_simpl_iterations
- | Opt_D_dump_simpl_phases
- | Opt_D_dump_spec
- | Opt_D_dump_prep
- | Opt_D_dump_stg
- | Opt_D_dump_stranal
- | Opt_D_dump_tc
- | Opt_D_dump_types
- | Opt_D_dump_rules
- | Opt_D_dump_cse
- | Opt_D_dump_worker_wrapper
- | Opt_D_dump_rn_trace
- | Opt_D_dump_rn_stats
- | Opt_D_dump_opt_cmm
- | Opt_D_dump_simpl_stats
- | Opt_D_dump_cs_trace
- | Opt_D_dump_tc_trace
- | Opt_D_dump_if_trace
- | Opt_D_dump_splices
- | 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
- | Opt_D_dump_hi
- | Opt_D_dump_hi_diffs
- | Opt_D_dump_minimal_imports
- | Opt_D_dump_mod_cycles
- | Opt_D_dump_view_pattern_commoning
- | Opt_D_faststring_stats
- | Opt_DumpToFile
- | Opt_D_no_debug_output
- | Opt_DoCoreLinting
- | Opt_DoStgLinting
- | Opt_DoCmmLinting
- | Opt_DoAsmLinting
- | Opt_WarnIsError
- | Opt_WarnDuplicateExports
- | Opt_WarnHiShadows
- | Opt_WarnImplicitPrelude
- | Opt_WarnIncompletePatterns
- | Opt_WarnIncompletePatternsRecUpd
- | Opt_WarnMissingFields
- | Opt_WarnMissingImportList
- | Opt_WarnMissingMethods
- | Opt_WarnMissingSigs
- | Opt_WarnMissingLocalSigs
- | Opt_WarnNameShadowing
- | Opt_WarnOverlappingPatterns
- | Opt_WarnTypeDefaults
- | Opt_WarnMonomorphism
- | Opt_WarnUnusedBinds
- | Opt_WarnUnusedImports
- | Opt_WarnUnusedMatches
- | Opt_WarnWarningsDeprecations
- | Opt_WarnDeprecatedFlags
- | Opt_WarnDodgyExports
- | Opt_WarnDodgyImports
- | Opt_WarnOrphans
- | Opt_WarnAutoOrphans
- | Opt_WarnTabs
- | Opt_WarnUnrecognisedPragmas
- | Opt_WarnDodgyForeignImports
- | Opt_WarnLazyUnliftedBindings
- | Opt_WarnUnusedDoBind
- | Opt_WarnWrongDoBind
- | Opt_WarnAlternativeLayoutRuleTransitional
- | Opt_PrintExplicitForalls
- | Opt_Strictness
- | Opt_FullLaziness
- | Opt_FloatIn
- | Opt_Specialise
- | Opt_StaticArgumentTransformation
- | Opt_CSE
- | Opt_LiberateCase
- | Opt_SpecConstr
- | Opt_DoLambdaEtaExpansion
- | Opt_IgnoreAsserts
- | Opt_DoEtaReduction
- | Opt_CaseMerge
- | Opt_UnboxStrictFields
- | Opt_MethodSharing
- | Opt_DictsCheap
- | Opt_EnableRewriteRules
- | Opt_Vectorise
- | Opt_RegsGraph
- | Opt_RegsIterative
- | Opt_IgnoreInterfacePragmas
- | Opt_OmitInterfacePragmas
- | Opt_ExposeAllUnfoldings
- | Opt_AutoSccsOnAllToplevs
- | Opt_AutoSccsOnExportedToplevs
- | Opt_AutoSccsOnIndividualCafs
- | Opt_Pp
- | Opt_ForceRecomp
- | Opt_DryRun
- | Opt_DoAsmMangling
- | Opt_ExcessPrecision
- | Opt_EagerBlackHoling
- | Opt_ReadUserPackageConf
- | Opt_NoHsMain
- | Opt_SplitObjs
- | Opt_StgStats
- | Opt_HideAllPackages
- | Opt_PrintBindResult
- | Opt_Haddock
- | Opt_HaddockOptions
- | Opt_Hpc_No_Auto
- | Opt_BreakOnException
- | Opt_BreakOnError
- | Opt_PrintEvldWithShow
- | Opt_PrintBindContents
- | Opt_GenManifest
- | Opt_EmbedManifest
- | Opt_EmitExternalCore
- | Opt_SharedImplib
- | Opt_BuildingCabalPackage
- | Opt_SSE2
- | Opt_GhciSandbox
- | Opt_RunCPS
- | Opt_RunCPSZ
- | Opt_ConvertToZipCfgAndBack
- | Opt_AutoLinkPackages
- | Opt_ImplicitImportQualified
- | Opt_TryNewCodeGen
- | Opt_KeepHiDiffs
- | Opt_KeepHcFiles
- | Opt_KeepSFiles
- | Opt_KeepRawSFiles
- | Opt_KeepTmpFiles
- | Opt_KeepRawTokenStream
- | Opt_KeepLlvmFiles
- data ExtensionFlag
- = Opt_Cpp
- | Opt_OverlappingInstances
- | Opt_UndecidableInstances
- | Opt_IncoherentInstances
- | Opt_MonomorphismRestriction
- | Opt_MonoPatBinds
- | Opt_MonoLocalBinds
- | Opt_RelaxedPolyRec
- | Opt_ExtendedDefaultRules
- | Opt_ForeignFunctionInterface
- | Opt_UnliftedFFITypes
- | Opt_GHCForeignImportPrim
- | Opt_PArr
- | Opt_Arrows
- | Opt_TemplateHaskell
- | Opt_QuasiQuotes
- | Opt_ImplicitParams
- | Opt_Generics
- | Opt_ImplicitPrelude
- | Opt_ScopedTypeVariables
- | Opt_UnboxedTuples
- | Opt_BangPatterns
- | Opt_TypeFamilies
- | Opt_OverloadedStrings
- | Opt_DisambiguateRecordFields
- | Opt_RecordWildCards
- | Opt_RecordPuns
- | Opt_ViewPatterns
- | Opt_GADTs
- | Opt_NPlusKPatterns
- | Opt_DoAndIfThenElse
- | Opt_RebindableSyntax
- | 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
- glasgowExtsFlags :: [ExtensionFlag]
- dopt :: DynFlag -> DynFlags -> Bool
- dopt_set :: DynFlags -> DynFlag -> DynFlags
- dopt_unset :: DynFlags -> DynFlag -> DynFlags
- xopt :: ExtensionFlag -> DynFlags -> Bool
- xopt_set :: DynFlags -> ExtensionFlag -> DynFlags
- xopt_unset :: DynFlags -> ExtensionFlag -> DynFlags
- data DynFlags = DynFlags {
- ghcMode :: GhcMode
- ghcLink :: GhcLink
- hscTarget :: HscTarget
- hscOutName :: String
- extCoreName :: String
- verbosity :: Int
- optLevel :: Int
- simplPhases :: Int
- maxSimplIterations :: Int
- shouldDumpSimplPhase :: Maybe String
- ruleCheck :: Maybe String
- strictnessBefore :: [Int]
- specConstrThreshold :: Maybe Int
- specConstrCount :: Maybe Int
- liberateCaseThreshold :: Maybe Int
- floatLamArgs :: Maybe Int
- targetPlatform :: Platform
- stolen_x86_regs :: Int
- cmdlineHcIncludes :: [String]
- importPaths :: [FilePath]
- mainModIs :: Module
- mainFunIs :: Maybe String
- ctxtStkDepth :: Int
- dphBackend :: DPHBackend
- thisPackage :: PackageId
- ways :: [Way]
- buildTag :: String
- rtsBuildTag :: String
- splitInfo :: Maybe (String, Int)
- objectDir :: Maybe String
- dylibInstallName :: Maybe String
- hiDir :: Maybe String
- stubDir :: Maybe String
- objectSuf :: String
- hcSuf :: String
- hiSuf :: String
- outputFile :: Maybe String
- outputHi :: Maybe String
- dynLibLoader :: DynLibLoader
- dumpPrefix :: Maybe FilePath
- dumpPrefixForce :: Maybe FilePath
- includePaths :: [String]
- libraryPaths :: [String]
- frameworkPaths :: [String]
- cmdlineFrameworks :: [String]
- tmpDir :: String
- ghcUsagePath :: FilePath
- ghciUsagePath :: FilePath
- rtsOpts :: Maybe String
- rtsOptsEnabled :: RtsOptsEnabled
- hpcDir :: String
- opt_L :: [String]
- opt_P :: [String]
- opt_F :: [String]
- opt_c :: [String]
- opt_m :: [String]
- opt_a :: [String]
- opt_l :: [String]
- opt_windres :: [String]
- opt_lo :: [String]
- opt_lc :: [String]
- pgm_L :: String
- pgm_P :: (String, [Option])
- pgm_F :: String
- pgm_c :: (String, [Option])
- pgm_m :: (String, [Option])
- pgm_s :: (String, [Option])
- pgm_a :: (String, [Option])
- pgm_l :: (String, [Option])
- pgm_dll :: (String, [Option])
- pgm_T :: String
- pgm_sysman :: String
- pgm_windres :: String
- pgm_lo :: (String, [Option])
- pgm_lc :: (String, [Option])
- depMakefile :: FilePath
- depIncludePkgDeps :: Bool
- depExcludeMods :: [ModuleName]
- depSuffixes :: [String]
- extraPkgConfs :: [FilePath]
- topDir :: FilePath
- systemPackageConfig :: FilePath
- packageFlags :: [PackageFlag]
- pkgDatabase :: Maybe [PackageConfig]
- pkgState :: PackageState
- filesToClean :: IORef [FilePath]
- dirsToClean :: IORef (Map FilePath FilePath)
- flags :: [DynFlag]
- language :: Maybe Language
- extensions :: [OnOff ExtensionFlag]
- extensionFlags :: [ExtensionFlag]
- log_action :: Severity -> SrcSpan -> PprStyle -> Message -> IO ()
- haddockOptions :: Maybe String
- data RtsOptsEnabled
- data HscTarget
- = HscC
- | HscAsm
- | HscLlvm
- | HscJava
- | HscInterpreted
- | HscNothing
- isObjectTarget :: HscTarget -> Bool
- defaultObjectTarget :: HscTarget
- data GhcMode
- = CompManager
- | OneShot
- | MkDepend
- isOneShot :: GhcMode -> Bool
- data GhcLink
- = NoLink
- | LinkBinary
- | LinkInMemory
- | LinkDynLib
- isNoLink :: GhcLink -> Bool
- data PackageFlag
- data Option
- showOpt :: Option -> String
- data DynLibLoader
- fFlags :: [FlagSpec DynFlag]
- fLangFlags :: [FlagSpec ExtensionFlag]
- xFlags :: [FlagSpec ExtensionFlag]
- dphPackage :: DynFlags -> PackageId
- wayNames :: DynFlags -> [WayName]
- defaultDynFlags :: DynFlags
- initDynFlags :: DynFlags -> IO DynFlags
- getOpts :: DynFlags -> (DynFlags -> [a]) -> [a]
- getVerbFlag :: DynFlags -> String
- updOptLevel :: Int -> DynFlags -> DynFlags
- setTmpDir :: FilePath -> DynFlags -> DynFlags
- setPackageName :: String -> DynFlags -> DynFlags
- doingTickyProfiling :: DynFlags -> Bool
- parseDynamicFlags :: Monad m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Located String])
- parseDynamicNoPackageFlags :: Monad m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Located String])
- allFlags :: [String]
- supportedLanguagesAndExtensions :: [String]
- machdepCCOpts :: DynFlags -> ([String], [String])
- picCCOpts :: DynFlags -> [String]
- data StgToDo
- getStgToDo :: DynFlags -> [StgToDo]
- data Printable
- = String String
- | FromDynFlags (DynFlags -> String)
- compilerInfo :: [(String, Printable)]
- rtsIsProfiled :: Bool
Dynamic flags and associated configuration types
Enumerates the simple on-or-off dynamic flags
data ExtensionFlag Source
xopt :: ExtensionFlag -> DynFlags -> BoolSource
Test whether a ExtensionFlag
is set
xopt_set :: DynFlags -> ExtensionFlag -> DynFlagsSource
Set a ExtensionFlag
xopt_unset :: DynFlags -> ExtensionFlag -> DynFlagsSource
Unset a ExtensionFlag
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
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.)
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 |
HscNothing | Don't generate any code. See notes above. |
isObjectTarget :: HscTarget -> BoolSource
Will this target result in an object file on the disk?
defaultObjectTarget :: HscTargetSource
The HscTarget
value corresponding to the default way to create
object files on the current platform.
The GhcMode
tells us whether we're doing multi-module
compilation (controlled via the GHC API) or one-shot
(single-module) compilation. This makes a difference primarily to
the Finder: in one-shot mode we look for interface files for
imported modules, but in multi-module mode we look for source files
in order to check whether they need to be recompiled.
CompManager |
|
OneShot | ghc -c Foo.hs |
MkDepend |
|
What to do in the link step, if there is one.
NoLink | Don't link at all |
LinkBinary | Link object code into a binary |
LinkInMemory | Use the in-memory dynamic linker (works for both bytecode and object code). |
LinkDynLib | Link objects into a dynamic lib (DLL on Windows, DSO on ELF platforms) |
data PackageFlag Source
When invoking external tools as part of the compilation pipeline, we pass these a sequence of options on the command-line. Rather than just using a list of Strings, we use a type that allows us to distinguish between filepaths and 'other stuff'. The reason for this is that this type gives us a handle on transforming filenames, and filenames only, to whatever format they're expected to be on a particular platform.
fLangFlags :: [FlagSpec ExtensionFlag]Source
These -f<blah>
flags can all be reversed with -fno-<blah>
xFlags :: [FlagSpec ExtensionFlag]Source
Manipulating DynFlags
defaultDynFlags :: DynFlagsSource
The normal DynFlags
. Note that they is not suitable for use in this form
and must be fully initialized by GHC.newSession
first.
initDynFlags :: DynFlags -> IO DynFlagsSource
Used by GHC.newSession
to partially initialize a new DynFlags
value
:: DynFlags |
|
-> (DynFlags -> [a]) | Relevant record accessor: one of the |
-> [a] | Correctly ordered extracted options |
Retrieve the options corresponding to a particular opt_*
field in the correct order
getVerbFlag :: DynFlags -> StringSource
Gets the verbosity flag for the current verbosity level. This is fed to
other tools, so GHC-specific verbosity flags like -ddump-most
are not included
updOptLevel :: Int -> DynFlags -> DynFlagsSource
Sets the DynFlags
to be appropriate to the optimisation level
setPackageName :: String -> DynFlags -> DynFlagsSource
Parsing DynFlags
:: Monad m | |
=> DynFlags | |
-> [Located String] | |
-> m (DynFlags, [Located String], [Located String]) | Updated |
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).
parseDynamicNoPackageFlagsSource
:: Monad m | |
=> DynFlags | |
-> [Located String] | |
-> m (DynFlags, [Located String], [Located String]) | Updated |
Like parseDynamicFlags
but does not allow the package flags (-package,
-hide-package, -ignore-package, -hide-all-packages, -package-conf).
DynFlag C compiler options
machdepCCOpts :: DynFlags -> ([String], [String])Source
Configuration of the stg-to-stg passes
getStgToDo :: DynFlags -> [StgToDo]Source
Compiler configuration suitable for display to the user
compilerInfo :: [(String, Printable)]Source