|
|
|
|
|
| Description |
Dynamic flags
(c) The University of Glasgow 2005
|
|
| Synopsis |
|
| | | data DynFlags = DynFlags {} | | | | | isObjectTarget :: HscTarget -> Bool | | | defaultObjectTarget :: HscTarget | | | | | isOneShot :: GhcMode -> Bool | | | | | isNoLink :: GhcLink -> Bool | | | | | | | | | fFlags :: [(String, DynFlag, Bool -> Deprecated)] | | | xFlags :: [(String, DynFlag, Bool -> Deprecated)] | | | dphPackage :: DynFlags -> PackageId | | | defaultDynFlags :: DynFlags | | | initDynFlags :: DynFlags -> IO DynFlags | | | dopt :: DynFlag -> DynFlags -> Bool | | | dopt_set :: DynFlags -> DynFlag -> DynFlags | | | dopt_unset :: DynFlags -> DynFlag -> DynFlags | | | getOpts :: DynFlags -> (DynFlags -> [a]) -> [a] | | | getVerbFlag :: DynFlags -> String | | | getMainFun :: DynFlags -> RdrName | | | updOptLevel :: Int -> DynFlags -> DynFlags | | | setTmpDir :: FilePath -> DynFlags -> DynFlags | | | setPackageName :: String -> DynFlags -> DynFlags | | | 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] | | | supportedLanguages :: [String] | | | languageOptions :: [DynFlag] | | | machdepCCOpts :: DynFlags -> ([String], [String]) | | | picCCOpts :: DynFlags -> [String] | | | | | | | | | data FloatOutSwitches = FloatOutSw Bool Bool | | | getCoreToDo :: DynFlags -> [CoreToDo] | | | | | getStgToDo :: DynFlags -> [StgToDo] | | | compilerInfo :: [(String, String)] |
|
|
|
| Dynamic flags and associated configuration types
|
|
| data DynFlag |
| Enumerates the simple on-or-off dynamic flags
| | Constructors | | 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_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_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 | Append dump output to files instead of stdout.
| | 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_WarnMissingMethods | | | Opt_WarnMissingSigs | | | Opt_WarnNameShadowing | | | Opt_WarnOverlappingPatterns | | | Opt_WarnSimplePatterns | | | Opt_WarnTypeDefaults | | | Opt_WarnMonomorphism | | | Opt_WarnUnusedBinds | | | Opt_WarnUnusedImports | | | Opt_WarnUnusedMatches | | | Opt_WarnWarningsDeprecations | | | Opt_WarnDeprecatedFlags | | | Opt_WarnDodgyImports | | | Opt_WarnOrphans | | | Opt_WarnTabs | | | Opt_WarnUnrecognisedPragmas | | | Opt_WarnDodgyForeignImports | | | Opt_OverlappingInstances | | | Opt_UndecidableInstances | | | Opt_IncoherentInstances | | | Opt_MonomorphismRestriction | | | Opt_MonoPatBinds | | | Opt_ExtendedDefaultRules | | | Opt_ForeignFunctionInterface | | | Opt_UnliftedFFITypes | | | 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_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_NewQualifiedOperators | | | Opt_PrintExplicitForalls | | | Opt_Strictness | | | Opt_FullLaziness | | | Opt_StaticArgumentTransformation | | | Opt_CSE | | | Opt_LiberateCase | | | Opt_SpecConstr | | | Opt_IgnoreInterfacePragmas | | | Opt_OmitInterfacePragmas | | | Opt_DoLambdaEtaExpansion | | | Opt_IgnoreAsserts | | | Opt_DoEtaReduction | | | Opt_CaseMerge | | | Opt_UnboxStrictFields | | | Opt_MethodSharing | | | Opt_DictsCheap | | | Opt_InlineIfEnoughArgs | | | Opt_EnableRewriteRules | | | Opt_Vectorise | | | Opt_RegsGraph | | | Opt_RegsIterative | | | Opt_Cpp | | | Opt_Pp | | | Opt_ForceRecomp | | | Opt_DryRun | | | Opt_DoAsmMangling | | | Opt_ExcessPrecision | | | 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_RunCPSZ | | | Opt_ConvertToZipCfgAndBack | | | Opt_AutoLinkPackages | | | Opt_ImplicitImportQualified | | | Opt_KeepHiDiffs | | | Opt_KeepHcFiles | | | Opt_KeepSFiles | | | Opt_KeepRawSFiles | | | Opt_KeepTmpFiles | | | Opt_KeepRawTokenStream | |
| Instances | |
|
|
| data DynFlags |
| 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 | |
|
|
| data HscTarget |
The target code type of the compilation (if any).
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.
- At the moment switching from HscNothing to HscInterpreted without
unloading first is not safe. To unload use
GHC.setTargets [] >> GHC.load LoadAllTargets.
| | Constructors | | HscC | | | HscAsm | | | HscJava | | | HscInterpreted | | | HscNothing | |
| Instances | |
|
|
| isObjectTarget :: HscTarget -> Bool |
| Will this target result in an object file on the disk?
|
|
| defaultObjectTarget :: HscTarget |
| The HscTarget value corresponding to the default way to create
object files on the current platform.
|
|
| data GhcMode |
| 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
|
| Instances | |
|
|
| isOneShot :: GhcMode -> Bool |
|
| data GhcLink |
| 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
| | LinkDynLib | Link objects into a dynamic lib (DLL on Windows, DSO on ELF platforms)
|
| Instances | |
|
|
| isNoLink :: GhcLink -> Bool |
|
| data PackageFlag |
| Constructors | | Instances | |
|
|
| data Option |
| 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.
| | Constructors | |
|
|
| data DynLibLoader |
| Constructors | | Instances | |
|
|
| fFlags :: [(String, DynFlag, Bool -> Deprecated)] |
| These -f<blah> flags can all be reversed with -fno-<blah>
|
|
| xFlags :: [(String, DynFlag, Bool -> Deprecated)] |
| These -Xblah> flags can all be reversed with -XNo<blah
|
|
| dphPackage :: DynFlags -> PackageId |
|
| Manipulating DynFlags
|
|
| defaultDynFlags :: DynFlags |
| 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 DynFlags |
| Used by GHC.newSession to partially initialize a new DynFlags value
|
|
| dopt :: DynFlag -> DynFlags -> Bool |
| Test whether a DynFlag is set
|
|
| dopt_set :: DynFlags -> DynFlag -> DynFlags |
| Set a DynFlag
|
|
| dopt_unset :: DynFlags -> DynFlag -> DynFlags |
| Unset a DynFlag
|
|
| getOpts |
| :: | | | => 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
|
|
|
| getVerbFlag :: DynFlags -> String |
| 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
|
|
| getMainFun :: DynFlags -> RdrName |
| 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
|
|
| updOptLevel :: Int -> DynFlags -> DynFlags |
| Sets the DynFlags to be appropriate to the optimisation level
|
|
| setTmpDir :: FilePath -> DynFlags -> DynFlags |
|
| setPackageName :: String -> DynFlags -> DynFlags |
|
| Parsing DynFlags
|
|
| parseDynamicFlags |
|
|
| parseDynamicNoPackageFlags |
|
|
| allFlags :: [String] |
|
| supportedLanguages :: [String] |
|
| languageOptions :: [DynFlag] |
|
| DynFlag C compiler options
|
|
| machdepCCOpts :: DynFlags -> ([String], [String]) |
|
| picCCOpts :: DynFlags -> [String] |
|
| Configuration of the core-to-core passes
|
|
| data CoreToDo |
|
|
| data SimplifierMode |
|
|
| data SimplifierSwitch |
| Constructors | | MaxSimplifierIterations Int | | | NoCaseOfCase | |
| Instances | |
|
|
| data FloatOutSwitches |
|
|
| getCoreToDo :: DynFlags -> [CoreToDo] |
|
| Configuration of the stg-to-stg passes
|
|
| data StgToDo |
| Constructors | | StgDoMassageForProfiling | | | D_stg_stats | |
|
|
|
| getStgToDo :: DynFlags -> [StgToDo] |
|
| Compiler configuration suitable for display to the user
|
|
| compilerInfo :: [(String, String)] |
|
| Produced by Haddock version 2.4.2 |