ghc-7.6.2: The GHC API

Safe HaskellNone

DynFlags

Contents

Description

Dynamic flags

Most flags are dynamic flags, which means they can change from compilation to compilation using OPTIONS_GHC pragmas, and in a multi-session GHC each session can be using different dynamic flags. Dynamic flags can also be set at the prompt in GHCi.

(c) The University of Glasgow 2005

Synopsis

Dynamic flags and associated configuration types

data DynFlag Source

Enumerates the simple on-or-off dynamic flags

Constructors

Opt_D_dump_cmm 
Opt_D_dump_raw_cmm 
Opt_D_dump_cmmz 
Opt_D_dump_cmmz_cfg 
Opt_D_dump_cmmz_cbe 
Opt_D_dump_cmmz_proc 
Opt_D_dump_cmmz_spills 
Opt_D_dump_cmmz_rewrite 
Opt_D_dump_cmmz_dead 
Opt_D_dump_cmmz_stub 
Opt_D_dump_cmmz_sp 
Opt_D_dump_cmmz_procmap 
Opt_D_dump_cmmz_split 
Opt_D_dump_cmmz_lower 
Opt_D_dump_cmmz_info 
Opt_D_dump_cmmz_cafs 
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_core_stats 
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_rule_rewrites 
Opt_D_dump_occur_anal 
Opt_D_dump_parsed 
Opt_D_dump_rn 
Opt_D_dump_core_pipeline 
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_vt_trace 
Opt_D_dump_splices 
Opt_D_dump_BCOs 
Opt_D_dump_vect 
Opt_D_dump_avoid_vect 
Opt_D_dump_ticked 
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

Append dump output to files instead of stdout.

Opt_D_no_debug_output 
Opt_DoCoreLinting 
Opt_DoStgLinting 
Opt_DoCmmLinting 
Opt_DoAsmLinting 
Opt_NoLlvmMangler 
Opt_WarnIsError 
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_DictsCheap 
Opt_EnableRewriteRules 
Opt_Vectorise 
Opt_AvoidVect 
Opt_RegsGraph 
Opt_RegsIterative 
Opt_PedanticBottoms 
Opt_LlvmTBAA 
Opt_RegLiveness 
Opt_IrrefutableTuples 
Opt_IgnoreInterfacePragmas 
Opt_OmitInterfacePragmas 
Opt_ExposeAllUnfoldings 
Opt_AutoSccsOnIndividualCafs 
Opt_ProfCountEntries 
Opt_Pp 
Opt_ForceRecomp 
Opt_ExcessPrecision 
Opt_EagerBlackHoling 
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_SSE4_2 
Opt_IgnoreDotGhci 
Opt_GhciSandbox 
Opt_GhciHistory 
Opt_HelpfulErrors 
Opt_DeferTypeErrors 
Opt_Parallel 
Opt_GranMacros 
Opt_PprCaseAsLet 
Opt_RunCPS 
Opt_RunCPSZ 
Opt_AutoLinkPackages 
Opt_ImplicitImportQualified 
Opt_TryNewCodeGen 
Opt_KeepHiDiffs 
Opt_KeepHcFiles 
Opt_KeepSFiles 
Opt_KeepTmpFiles 
Opt_KeepRawTokenStream 
Opt_KeepLlvmFiles 
Opt_DistrustAllPackages 
Opt_PackageTrust 

data ExtensionFlag Source

Constructors

Opt_Cpp 
Opt_OverlappingInstances 
Opt_UndecidableInstances 
Opt_IncoherentInstances 
Opt_MonomorphismRestriction 
Opt_MonoPatBinds 
Opt_MonoLocalBinds 
Opt_RelaxedPolyRec 
Opt_ExtendedDefaultRules 
Opt_ForeignFunctionInterface 
Opt_UnliftedFFITypes 
Opt_InterruptibleFFI 
Opt_CApiFFI 
Opt_GHCForeignImportPrim 
Opt_ParallelArrays 
Opt_Arrows 
Opt_TemplateHaskell 
Opt_QuasiQuotes 
Opt_ImplicitParams 
Opt_ImplicitPrelude 
Opt_ScopedTypeVariables 
Opt_UnboxedTuples 
Opt_BangPatterns 
Opt_TypeFamilies 
Opt_OverloadedStrings 
Opt_DisambiguateRecordFields 
Opt_RecordWildCards 
Opt_RecordPuns 
Opt_ViewPatterns 
Opt_GADTs 
Opt_GADTSyntax 
Opt_NPlusKPatterns 
Opt_DoAndIfThenElse 
Opt_RebindableSyntax 
Opt_ConstraintKinds 
Opt_PolyKinds 
Opt_DataKinds 
Opt_InstanceSigs 
Opt_StandaloneDeriving 
Opt_DeriveDataTypeable 
Opt_DeriveFunctor 
Opt_DeriveTraversable 
Opt_DeriveFoldable 
Opt_DeriveGeneric 
Opt_DefaultSignatures 
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_MonadComprehensions 
Opt_GeneralizedNewtypeDeriving 
Opt_RecursiveDo 
Opt_PostfixOperators 
Opt_TupleSections 
Opt_PatternGuards 
Opt_LiberalTypeSynonyms 
Opt_Rank2Types 
Opt_RankNTypes 
Opt_ImpredicativeTypes 
Opt_TypeOperators 
Opt_ExplicitNamespaces 
Opt_PackageImports 
Opt_ExplicitForAll 
Opt_AlternativeLayoutRule 
Opt_AlternativeLayoutRuleTransitional 
Opt_DatatypeContexts 
Opt_NondecreasingIndentation 
Opt_RelaxedLayout 
Opt_TraditionalRecordSyntax 
Opt_LambdaCase 
Opt_MultiWayIf 

data Language Source

Constructors

Haskell98 
Haskell2010 

Instances

newtype FlushOut Source

Constructors

FlushOut (IO ()) 

newtype FlushErr Source

Constructors

FlushErr (IO ()) 

data ProfAuto Source

Constructors

NoProfAuto

no SCC annotations added

ProfAutoAll

top-level and nested functions are annotated

ProfAutoTop

top-level functions annotated only

ProfAutoExports

exported functions annotated only

ProfAutoCalls

annotate call-sites

Instances

dopt :: DynFlag -> DynFlags -> BoolSource

Test whether a DynFlag is set

wopt :: WarningFlag -> DynFlags -> BoolSource

Test whether a WarningFlag is set

xopt :: ExtensionFlag -> DynFlags -> BoolSource

Test whether a ExtensionFlag is set

data DynFlags Source

Contains not only a collection of DynFlags but also a plethora of information relating to the compilation of a single file or GHC session

Constructors

DynFlags 

Fields

ghcMode :: GhcMode
 
ghcLink :: GhcLink
 
hscTarget :: HscTarget
 
settings :: Settings
 
hscOutName :: String

Name of the output file

extCoreName :: String

Name of the .hcr output file

verbosity :: Int

Verbosity level: see Note [Verbosity levels]

optLevel :: Int

Optimisation level

simplPhases :: Int

Number of simplifier phases

maxSimplIterations :: Int

Max simplifier iterations

shouldDumpSimplPhase :: Maybe String
 
ruleCheck :: Maybe String
 
strictnessBefore :: [Int]

Additional demand analysis

simplTickFactor :: Int

Multiplier for simplifier ticks

specConstrThreshold :: Maybe Int

Threshold for SpecConstr

specConstrCount :: Maybe Int

Max number of specialisations for any one function

liberateCaseThreshold :: Maybe Int

Threshold for LiberateCase

floatLamArgs :: Maybe Int

Arg count for lambda floating See CoreMonad.FloatOutSwitches

cmdlineHcIncludes :: [String]
-#includes
importPaths :: [FilePath]
 
mainModIs :: Module
 
mainFunIs :: Maybe String
 
ctxtStkDepth :: Int

Typechecker context stack depth

thisPackage :: PackageId

name of package currently being compiled

ways :: [Way]

Way flags from the command line

buildTag :: String

The global "way" (e.g. "p" for prof)

rtsBuildTag :: String

The RTS "way"

splitInfo :: Maybe (String, Int)
 
objectDir :: Maybe String
 
dylibInstallName :: Maybe String
 
hiDir :: Maybe String
 
stubDir :: Maybe String
 
dumpDir :: Maybe String
 
objectSuf :: String
 
hcSuf :: String
 
hiSuf :: String
 
outputFile :: Maybe String
 
outputHi :: Maybe String
 
dynLibLoader :: DynLibLoader
 
dumpPrefix :: Maybe FilePath

This is set by runPipeline based on where its output is going.

dumpPrefixForce :: Maybe FilePath

Override the dumpPrefix set by runPipeline. Set by -ddump-file-prefix

includePaths :: [String]
 
libraryPaths :: [String]
 
frameworkPaths :: [String]
 
cmdlineFrameworks :: [String]
 
rtsOpts :: Maybe String
 
rtsOptsEnabled :: RtsOptsEnabled
 
hpcDir :: String

Path to store the .mix files

pluginModNames :: [ModuleName]
 
pluginModNameOpts :: [(ModuleName, String)]
 
depMakefile :: FilePath
 
depIncludePkgDeps :: Bool
 
depExcludeMods :: [ModuleName]
 
depSuffixes :: [String]
 
extraPkgConfs :: [PkgConfRef] -> [PkgConfRef]

The -package-db flags given on the command line, in the order they appeared.

packageFlags :: [PackageFlag]

The -package and -hide-package flags from the command-line

pkgDatabase :: Maybe [PackageConfig]
 
pkgState :: PackageState
 
filesToClean :: IORef [FilePath]
 
dirsToClean :: IORef (Map FilePath FilePath)
 
generatedDumps :: IORef (Set FilePath)
 
flags :: IntSet
 
warningFlags :: IntSet
 
language :: Maybe Language
 
safeHaskell :: SafeHaskellMode

Safe Haskell mode

thOnLoc :: SrcSpan
 
newDerivOnLoc :: SrcSpan
 
pkgTrustOnLoc :: SrcSpan
 
warnSafeOnLoc :: SrcSpan
 
warnUnsafeOnLoc :: SrcSpan
 
extensions :: [OnOff ExtensionFlag]
 
extensionFlags :: IntSet
 
log_action :: LogAction

MsgDoc output action: use ErrUtils instead of this if you can

flushOut :: FlushOut
 
flushErr :: FlushErr
 
haddockOptions :: Maybe String
 
ghciScripts :: [String]
 
pprUserLength :: Int
 
pprCols :: Int
 
traceLevel :: Int
 
profAuto :: ProfAuto

what kind of {--} to add automatically

interactivePrint :: Maybe String
 
llvmVersion :: IORef Int
 

class ContainsDynFlags t whereSource

Instances

ContainsDynFlags (Env gbl lcl) 

data HscTarget Source

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 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 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 be preferable for security reasons.)

Constructors

HscC

Generate C code.

HscAsm

Generate assembly using the native code generator.

HscLlvm

Generate assembly using the llvm code generator.

HscInterpreted

Generate bytecode. (Requires LinkInMemory)

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.

targetRetainsAllBindings :: HscTarget -> BoolSource

Does this target retain *all* top-level bindings for a module, rather than just the exported bindings, in the TypeEnv and compiled code (if any)? In interpreted mode we do this, so that GHCi can call functions inside a module. In HscNothing mode we also do it, so that Haddock can get access to the GlobalRdrEnv for a module after typechecking it.

data GhcMode Source

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.

Constructors

CompManager

--make, GHCi, etc.

OneShot
ghc -c Foo.hs
MkDepend

ghc -M, see Finder for why we need this

data GhcLink Source

What to do in the link step, if there is one.

Constructors

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 Option 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.

Instances

fFlags :: [FlagSpec DynFlag]Source

These -f<blah> flags can all be reversed with -fno-<blah>

fWarningFlags :: [FlagSpec WarningFlag]Source

These -f<blah> flags can all be reversed with -fno-<blah>

fLangFlags :: [FlagSpec ExtensionFlag]Source

These -f<blah> flags can all be reversed with -fno-<blah>

xFlags :: [FlagSpec ExtensionFlag]Source

These -Xblah flags can all be reversed with -XNoblah

dynFlagDependencies :: DynFlags -> [ModuleName]Source

Some modules have dependencies on others through the DynFlags rather than textual imports

Safe Haskell

safeHaskellOn :: DynFlags -> BoolSource

Is Safe Haskell on in some way (including inference mode)

safeImportsOn :: DynFlags -> BoolSource

Test if Safe Imports are on in some form

safeLanguageOn :: DynFlags -> BoolSource

Is the Safe Haskell safe language in use

safeInferOn :: DynFlags -> BoolSource

Is the Safe Haskell safe inference mode active

packageTrustOn :: DynFlags -> BoolSource

Is the -fpackage-trust mode on

safeDirectImpsReq :: DynFlags -> BoolSource

Are all direct imports required to be safe for this Safe Haskell mode? Direct imports are when the code explicitly imports a module

safeImplicitImpsReq :: DynFlags -> BoolSource

Are all implicit imports required to be safe for this Safe Haskell mode? Implicit imports are things in the prelude. e.g System.IO when print is used.

unsafeFlags :: [(String, DynFlags -> SrcSpan, DynFlags -> Bool, DynFlags -> DynFlags)]Source

A list of unsafe flags under Safe Haskell. Tuple elements are: * name of the flag * function to get srcspan that enabled the flag * function to test if the flag is on * function to turn the flag off

System tool settings and locations

Manipulating DynFlags

defaultDynFlags :: Settings -> DynFlagsSource

The normal DynFlags. Note that they is not suitable for use in this form and must be fully initialized by newSession first.

initDynFlags :: DynFlags -> IO DynFlagsSource

Used by newSession to partially initialize a new DynFlags value

getOptsSource

Arguments

:: DynFlags

DynFlags to retrieve the options from

-> (DynFlags -> [a])

Relevant record accessor: one of the opt_* accessors

-> [a]

Correctly ordered extracted options

Retrieve the options corresponding to a particular opt_* field in the correct order

getVerbFlags :: DynFlags -> [String]Source

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

Parsing DynFlags

parseDynamicFlagsCmdLineSource

Arguments

:: Monad m 
=> DynFlags 
-> [Located String] 
-> m (DynFlags, [Located String], [Located String])

Updated DynFlags, left-over arguments, and list of warnings.

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).

parseDynamicFilePragmaSource

Arguments

:: Monad m 
=> DynFlags 
-> [Located String] 
-> m (DynFlags, [Located String], [Located String])

Updated DynFlags, left-over arguments, and list of warnings.

Like parseDynamicFlagsCmdLine but does not allow the package flags (-package, -hide-package, -ignore-package, -hide-all-packages, -package-db). Used to parse flags set in a modules pragma.

parseDynamicFlagsFullSource

Arguments

:: Monad m 
=> [Flag (CmdLineP DynFlags)]

valid flags to match against

-> Bool

are the arguments from the command line?

-> DynFlags

current dynamic flags

-> [Located String]

arguments to parse

-> m (DynFlags, [Located String], [Located String]) 

Parses the dynamically set flags for GHC. This is the most general form of the dynamic flag parser that the other methods simply wrap. It allows saying which flags are valid flags and indicating if we are parsing arguments from the command line or from a file pragma.

Available DynFlags

allFlags :: [String]Source

All dynamic flags option strings. These are the user facing strings for enabling and disabling options.

DynFlag C compiler options

Configuration of the stg-to-stg passes

Compiler configuration suitable for display to the user

Only for use in the tracing functions in Outputable