1{-# LANGUAGE CPP #-}
2{-# LANGUAGE FlexibleInstances #-}
3
4-------------------------------------------------------------------------------
5--
6-- | Dynamic flags
7--
8-- Most flags are dynamic flags, which means they can change from compilation
9-- to compilation using @OPTIONS_GHC@ pragmas, and in a multi-session GHC each
10-- session can be using different dynamic flags. Dynamic flags can also be set
11-- at the prompt in GHCi.
12--
13-- (c) The University of Glasgow 2005
14--
15-------------------------------------------------------------------------------
16
17{-# OPTIONS_GHC -fno-cse #-}
18-- -fno-cse is needed for GLOBAL_VAR's to behave properly
19
20module DynFlags (
21        -- * Dynamic flags and associated configuration types
22        DumpFlag(..),
23        GeneralFlag(..),
24        WarningFlag(..), WarnReason(..),
25        Language(..),
26        PlatformConstants(..),
27        FatalMessager, LogAction, FlushOut(..), FlushErr(..),
28        ProfAuto(..),
29        glasgowExtsFlags,
30        warningGroups, warningHierarchies,
31        hasPprDebug, hasNoDebugOutput, hasNoStateHack, hasNoOptCoercion,
32        dopt, dopt_set, dopt_unset,
33        gopt, gopt_set, gopt_unset, setGeneralFlag', unSetGeneralFlag',
34        wopt, wopt_set, wopt_unset,
35        wopt_fatal, wopt_set_fatal, wopt_unset_fatal,
36        xopt, xopt_set, xopt_unset,
37        xopt_set_unlessExplSpec,
38        lang_set,
39        useUnicodeSyntax,
40        useStarIsType,
41        whenGeneratingDynamicToo, ifGeneratingDynamicToo,
42        whenCannotGenerateDynamicToo,
43        dynamicTooMkDynamicDynFlags,
44        dynamicOutputFile,
45        DynFlags(..),
46        FlagSpec(..),
47        HasDynFlags(..), ContainsDynFlags(..),
48        RtsOptsEnabled(..),
49        HscTarget(..), isObjectTarget, defaultObjectTarget,
50        targetRetainsAllBindings,
51        GhcMode(..), isOneShot,
52        GhcLink(..), isNoLink,
53        PackageFlag(..), PackageArg(..), ModRenaming(..),
54        packageFlagsChanged,
55        IgnorePackageFlag(..), TrustFlag(..),
56        PackageDBFlag(..), PkgConfRef(..),
57        Option(..), showOpt,
58        DynLibLoader(..),
59        fFlags, fLangFlags, xFlags,
60        wWarningFlags,
61        dynFlagDependencies,
62        makeDynFlagsConsistent,
63        shouldUseColor,
64        shouldUseHexWordLiterals,
65        positionIndependent,
66        optimisationFlags,
67        setFlagsFromEnvFile,
68
69        Way(..), mkBuildTag, wayRTSOnly, addWay', updateWays,
70        wayGeneralFlags, wayUnsetGeneralFlags,
71
72        thisPackage, thisComponentId, thisUnitIdInsts,
73
74        -- ** Log output
75        putLogMsg,
76
77        -- ** Safe Haskell
78        SafeHaskellMode(..),
79        safeHaskellOn, safeHaskellModeEnabled,
80        safeImportsOn, safeLanguageOn, safeInferOn,
81        packageTrustOn,
82        safeDirectImpsReq, safeImplicitImpsReq,
83        unsafeFlags, unsafeFlagsForInfer,
84
85        -- ** LLVM Targets
86        LlvmTarget(..), LlvmConfig(..),
87
88        -- ** System tool settings and locations
89        Settings(..),
90        sProgramName,
91        sProjectVersion,
92        sGhcUsagePath,
93        sGhciUsagePath,
94        sToolDir,
95        sTopDir,
96        sTmpDir,
97        sSystemPackageConfig,
98        sLdSupportsCompactUnwind,
99        sLdSupportsBuildId,
100        sLdSupportsFilelist,
101        sLdIsGnuLd,
102        sGccSupportsNoPie,
103        sPgm_L,
104        sPgm_P,
105        sPgm_F,
106        sPgm_c,
107        sPgm_a,
108        sPgm_l,
109        sPgm_lm,
110        sPgm_dll,
111        sPgm_T,
112        sPgm_windres,
113        sPgm_libtool,
114        sPgm_ar,
115        sPgm_ranlib,
116        sPgm_lo,
117        sPgm_lc,
118        sPgm_lcc,
119        sPgm_i,
120        sOpt_L,
121        sOpt_P,
122        sOpt_P_fingerprint,
123        sOpt_F,
124        sOpt_c,
125        sOpt_cxx,
126        sOpt_a,
127        sOpt_l,
128        sOpt_lm,
129        sOpt_windres,
130        sOpt_lo,
131        sOpt_lc,
132        sOpt_lcc,
133        sOpt_i,
134        sExtraGccViaCFlags,
135        sTargetPlatformString,
136        sIntegerLibrary,
137        sIntegerLibraryType,
138        sGhcWithInterpreter,
139        sGhcWithNativeCodeGen,
140        sGhcWithSMP,
141        sGhcRTSWays,
142        sTablesNextToCode,
143        sLeadingUnderscore,
144        sLibFFI,
145        sGhcThreaded,
146        sGhcDebugged,
147        sGhcRtsWithLibdw,
148        IntegerLibrary(..),
149        GhcNameVersion(..),
150        FileSettings(..),
151        PlatformMisc(..),
152        settings,
153        programName, projectVersion,
154        ghcUsagePath, ghciUsagePath, topDir, tmpDir,
155        versionedAppDir, versionedFilePath,
156        extraGccViaCFlags, systemPackageConfig,
157        pgm_L, pgm_P, pgm_F, pgm_c, pgm_a, pgm_l, pgm_lm, pgm_dll, pgm_T,
158        pgm_windres, pgm_libtool, pgm_ar, pgm_otool, pgm_install_name_tool,
159        pgm_ranlib, pgm_lo, pgm_lc, pgm_lcc, pgm_i,
160        opt_L, opt_P, opt_F, opt_c, opt_cxx, opt_a, opt_l, opt_lm, opt_i,
161        opt_P_signature,
162        opt_windres, opt_lo, opt_lc, opt_lcc,
163        tablesNextToCode,
164
165        -- ** Manipulating DynFlags
166        addPluginModuleName,
167        defaultDynFlags,                -- Settings -> DynFlags
168        defaultWays,
169        interpWays,
170        interpreterProfiled, interpreterDynamic,
171        initDynFlags,                   -- DynFlags -> IO DynFlags
172        defaultFatalMessager,
173        defaultLogAction,
174        defaultLogActionHPrintDoc,
175        defaultLogActionHPutStrDoc,
176        defaultFlushOut,
177        defaultFlushErr,
178
179        getOpts,                        -- DynFlags -> (DynFlags -> [a]) -> [a]
180        getVerbFlags,
181        updOptLevel,
182        setTmpDir,
183        setUnitId,
184        canonicalizeHomeModule,
185        canonicalizeModuleIfHome,
186
187        -- ** Parsing DynFlags
188        parseDynamicFlagsCmdLine,
189        parseDynamicFilePragma,
190        parseDynamicFlagsFull,
191
192        -- ** Available DynFlags
193        allNonDeprecatedFlags,
194        flagsAll,
195        flagsDynamic,
196        flagsPackage,
197        flagsForCompletion,
198
199        supportedLanguagesAndExtensions,
200        languageExtensions,
201
202        -- ** DynFlags C compiler options
203        picCCOpts, picPOpts,
204
205        -- * Compiler configuration suitable for display to the user
206        compilerInfo,
207
208        rtsIsProfiled,
209        dynamicGhc,
210
211#include "GHCConstantsHaskellExports.hs"
212        bLOCK_SIZE_W,
213        wORD_SIZE_IN_BITS,
214        wordAlignment,
215        tAG_MASK,
216        mAX_PTR_TAG,
217        tARGET_MIN_INT, tARGET_MAX_INT, tARGET_MAX_WORD,
218
219        unsafeGlobalDynFlags, setUnsafeGlobalDynFlags,
220
221        -- * SSE and AVX
222        isSseEnabled,
223        isSse2Enabled,
224        isSse4_2Enabled,
225        isBmiEnabled,
226        isBmi2Enabled,
227        isAvxEnabled,
228        isAvx2Enabled,
229        isAvx512cdEnabled,
230        isAvx512erEnabled,
231        isAvx512fEnabled,
232        isAvx512pfEnabled,
233
234        -- * Linker/compiler information
235        LinkerInfo(..),
236        CompilerInfo(..),
237        useXLinkerRPath,
238
239        -- * File cleanup
240        FilesToClean(..), emptyFilesToClean,
241
242        -- * Include specifications
243        IncludeSpecs(..), addGlobalInclude, addQuoteInclude, flattenIncludes,
244
245
246        -- * Make use of the Cmm CFG
247        CfgWeights(..), backendMaintainsCfg
248  ) where
249
250#include "HsVersions.h"
251
252import GhcPrelude
253
254import GHC.Platform
255import GHC.UniqueSubdir (uniqueSubdir)
256import PlatformConstants
257import Module
258import PackageConfig
259import {-# SOURCE #-} Plugins
260import {-# SOURCE #-} Hooks
261import {-# SOURCE #-} PrelNames ( mAIN )
262import {-# SOURCE #-} Packages (PackageState, emptyPackageState)
263import DriverPhases     ( Phase(..), phaseInputExt )
264import Config
265import CliOption
266import CmdLineParser hiding (WarnReason(..))
267import qualified CmdLineParser as Cmd
268import Constants
269import GhcNameVersion
270import Panic
271import qualified PprColour as Col
272import Util
273import Maybes
274import MonadUtils
275import qualified Pretty
276import SrcLoc
277import BasicTypes       ( Alignment, alignmentOf, IntWithInf, treatZeroAsInf )
278import FastString
279import Fingerprint
280import FileSettings
281import Outputable
282import Settings
283import ToolSettings
284
285import Foreign.C        ( CInt(..) )
286import System.IO.Unsafe ( unsafeDupablePerformIO )
287import {-# SOURCE #-} ErrUtils ( Severity(..), MsgDoc, mkLocMessageAnn
288                               , getCaretDiagnostic )
289import Json
290import SysTools.Terminal ( stderrSupportsAnsiColors )
291import SysTools.BaseDir ( expandToolDir, expandTopDir )
292
293import System.IO.Unsafe ( unsafePerformIO )
294import Data.IORef
295import Control.Arrow ((&&&))
296import Control.Monad
297import Control.Monad.Trans.Class
298import Control.Monad.Trans.Writer
299import Control.Monad.Trans.Reader
300import Control.Monad.Trans.Except
301
302import Data.Ord
303import Data.Bits
304import Data.Char
305import Data.Int
306import Data.List
307import Data.Map (Map)
308import qualified Data.Map as Map
309import Data.Set (Set)
310import qualified Data.Set as Set
311import Data.Word
312import System.FilePath
313import System.Directory
314import System.Environment (lookupEnv)
315import System.IO
316import System.IO.Error
317import Text.ParserCombinators.ReadP hiding (char)
318import Text.ParserCombinators.ReadP as R
319
320import EnumSet (EnumSet)
321import qualified EnumSet
322
323import GHC.Foreign (withCString, peekCString)
324import qualified GHC.LanguageExtensions as LangExt
325
326#if GHC_STAGE >= 2
327-- used by SHARED_GLOBAL_VAR
328import Foreign (Ptr)
329#endif
330
331-- Note [Updating flag description in the User's Guide]
332-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
333--
334-- If you modify anything in this file please make sure that your changes are
335-- described in the User's Guide. Please update the flag description in the
336-- users guide (docs/users_guide) whenever you add or change a flag.
337
338-- Note [Supporting CLI completion]
339-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
340--
341-- The command line interface completion (in for example bash) is an easy way
342-- for the developer to learn what flags are available from GHC.
343-- GHC helps by separating which flags are available when compiling with GHC,
344-- and which flags are available when using GHCi.
345-- A flag is assumed to either work in both these modes, or only in one of them.
346-- When adding or changing a flag, please consider for which mode the flag will
347-- have effect, and annotate it accordingly. For Flags use defFlag, defGhcFlag,
348-- defGhciFlag, and for FlagSpec use flagSpec or flagGhciSpec.
349
350-- Note [Adding a language extension]
351-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
352--
353-- There are a few steps to adding (or removing) a language extension,
354--
355--  * Adding the extension to GHC.LanguageExtensions
356--
357--    The Extension type in libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs
358--    is the canonical list of language extensions known by GHC.
359--
360--  * Adding a flag to DynFlags.xFlags
361--
362--    This is fairly self-explanatory. The name should be concise, memorable,
363--    and consistent with any previous implementations of the similar idea in
364--    other Haskell compilers.
365--
366--  * Adding the flag to the documentation
367--
368--    This is the same as any other flag. See
369--    Note [Updating flag description in the User's Guide]
370--
371--  * Adding the flag to Cabal
372--
373--    The Cabal library has its own list of all language extensions supported
374--    by all major compilers. This is the list that user code being uploaded
375--    to Hackage is checked against to ensure language extension validity.
376--    Consequently, it is very important that this list remains up-to-date.
377--
378--    To this end, there is a testsuite test (testsuite/tests/driver/T4437.hs)
379--    whose job it is to ensure these GHC's extensions are consistent with
380--    Cabal.
381--
382--    The recommended workflow is,
383--
384--     1. Temporarily add your new language extension to the
385--        expectedGhcOnlyExtensions list in T4437 to ensure the test doesn't
386--        break while Cabal is updated.
387--
388--     2. After your GHC change is accepted, submit a Cabal pull request adding
389--        your new extension to Cabal's list (found in
390--        Cabal/Language/Haskell/Extension.hs).
391--
392--     3. After your Cabal change is accepted, let the GHC developers know so
393--        they can update the Cabal submodule and remove the extensions from
394--        expectedGhcOnlyExtensions.
395--
396--  * Adding the flag to the GHC Wiki
397--
398--    There is a change log tracking language extension additions and removals
399--    on the GHC wiki:  https://gitlab.haskell.org/ghc/ghc/wikis/language-pragma-history
400--
401--  See #4437 and #8176.
402
403-- -----------------------------------------------------------------------------
404-- DynFlags
405
406data DumpFlag
407-- See Note [Updating flag description in the User's Guide]
408
409   -- debugging flags
410   = Opt_D_dump_cmm
411   | Opt_D_dump_cmm_from_stg
412   | Opt_D_dump_cmm_raw
413   | Opt_D_dump_cmm_verbose_by_proc
414   -- All of the cmm subflags (there are a lot!) automatically
415   -- enabled if you run -ddump-cmm-verbose-by-proc
416   -- Each flag corresponds to exact stage of Cmm pipeline.
417   | Opt_D_dump_cmm_verbose
418   -- same as -ddump-cmm-verbose-by-proc but writes each stage
419   -- to a separate file (if used with -ddump-to-file)
420   | Opt_D_dump_cmm_cfg
421   | Opt_D_dump_cmm_cbe
422   | Opt_D_dump_cmm_switch
423   | Opt_D_dump_cmm_proc
424   | Opt_D_dump_cmm_sp
425   | Opt_D_dump_cmm_sink
426   | Opt_D_dump_cmm_caf
427   | Opt_D_dump_cmm_procmap
428   | Opt_D_dump_cmm_split
429   | Opt_D_dump_cmm_info
430   | Opt_D_dump_cmm_cps
431   -- end cmm subflags
432   | Opt_D_dump_cfg_weights -- ^ Dump the cfg used for block layout.
433   | Opt_D_dump_asm
434   | Opt_D_dump_asm_native
435   | Opt_D_dump_asm_liveness
436   | Opt_D_dump_asm_regalloc
437   | Opt_D_dump_asm_regalloc_stages
438   | Opt_D_dump_asm_conflicts
439   | Opt_D_dump_asm_stats
440   | Opt_D_dump_asm_expanded
441   | Opt_D_dump_llvm
442   | Opt_D_dump_core_stats
443   | Opt_D_dump_deriv
444   | Opt_D_dump_ds
445   | Opt_D_dump_ds_preopt
446   | Opt_D_dump_foreign
447   | Opt_D_dump_inlinings
448   | Opt_D_dump_rule_firings
449   | Opt_D_dump_rule_rewrites
450   | Opt_D_dump_simpl_trace
451   | Opt_D_dump_occur_anal
452   | Opt_D_dump_parsed
453   | Opt_D_dump_parsed_ast
454   | Opt_D_dump_rn
455   | Opt_D_dump_rn_ast
456   | Opt_D_dump_simpl
457   | Opt_D_dump_simpl_iterations
458   | Opt_D_dump_spec
459   | Opt_D_dump_prep
460   | Opt_D_dump_stg -- CoreToStg output
461   | Opt_D_dump_stg_unarised -- STG after unarise
462   | Opt_D_dump_stg_final -- STG after stg2stg
463   | Opt_D_dump_call_arity
464   | Opt_D_dump_exitify
465   | Opt_D_dump_stranal
466   | Opt_D_dump_str_signatures
467   | Opt_D_dump_tc
468   | Opt_D_dump_tc_ast
469   | Opt_D_dump_types
470   | Opt_D_dump_rules
471   | Opt_D_dump_cse
472   | Opt_D_dump_worker_wrapper
473   | Opt_D_dump_rn_trace
474   | Opt_D_dump_rn_stats
475   | Opt_D_dump_opt_cmm
476   | Opt_D_dump_simpl_stats
477   | Opt_D_dump_cs_trace -- Constraint solver in type checker
478   | Opt_D_dump_tc_trace
479   | Opt_D_dump_ec_trace -- Pattern match exhaustiveness checker
480   | Opt_D_dump_if_trace
481   | Opt_D_dump_vt_trace
482   | Opt_D_dump_splices
483   | Opt_D_th_dec_file
484   | Opt_D_dump_BCOs
485   | Opt_D_dump_ticked
486   | Opt_D_dump_rtti
487   | Opt_D_source_stats
488   | Opt_D_verbose_stg2stg
489   | Opt_D_dump_hi
490   | Opt_D_dump_hi_diffs
491   | Opt_D_dump_mod_cycles
492   | Opt_D_dump_mod_map
493   | Opt_D_dump_timings
494   | Opt_D_dump_view_pattern_commoning
495   | Opt_D_verbose_core2core
496   | Opt_D_dump_debug
497   | Opt_D_dump_json
498   | Opt_D_ppr_debug
499   | Opt_D_no_debug_output
500   deriving (Eq, Show, Enum)
501
502
503-- | Enumerates the simple on-or-off dynamic flags
504data GeneralFlag
505-- See Note [Updating flag description in the User's Guide]
506
507   = Opt_DumpToFile                     -- ^ Append dump output to files instead of stdout.
508   | Opt_D_faststring_stats
509   | Opt_D_dump_minimal_imports
510   | Opt_DoCoreLinting
511   | Opt_DoStgLinting
512   | Opt_DoCmmLinting
513   | Opt_DoAsmLinting
514   | Opt_DoAnnotationLinting
515   | Opt_NoLlvmMangler                  -- hidden flag
516   | Opt_FastLlvm                       -- hidden flag
517   | Opt_NoTypeableBinds
518
519   | Opt_WarnIsError                    -- -Werror; makes warnings fatal
520   | Opt_ShowWarnGroups                 -- Show the group a warning belongs to
521   | Opt_HideSourcePaths                -- Hide module source/object paths
522
523   | Opt_PrintExplicitForalls
524   | Opt_PrintExplicitKinds
525   | Opt_PrintExplicitCoercions
526   | Opt_PrintExplicitRuntimeReps
527   | Opt_PrintEqualityRelations
528   | Opt_PrintAxiomIncomps
529   | Opt_PrintUnicodeSyntax
530   | Opt_PrintExpandedSynonyms
531   | Opt_PrintPotentialInstances
532   | Opt_PrintTypecheckerElaboration
533
534   -- optimisation opts
535   | Opt_CallArity
536   | Opt_Exitification
537   | Opt_Strictness
538   | Opt_LateDmdAnal                    -- #6087
539   | Opt_KillAbsence
540   | Opt_KillOneShot
541   | Opt_FullLaziness
542   | Opt_FloatIn
543   | Opt_LateSpecialise
544   | Opt_Specialise
545   | Opt_SpecialiseAggressively
546   | Opt_CrossModuleSpecialise
547   | Opt_StaticArgumentTransformation
548   | Opt_CSE
549   | Opt_StgCSE
550   | Opt_StgLiftLams
551   | Opt_LiberateCase
552   | Opt_SpecConstr
553   | Opt_SpecConstrKeen
554   | Opt_DoLambdaEtaExpansion
555   | Opt_IgnoreAsserts
556   | Opt_DoEtaReduction
557   | Opt_CaseMerge
558   | Opt_CaseFolding                    -- Constant folding through case-expressions
559   | Opt_UnboxStrictFields
560   | Opt_UnboxSmallStrictFields
561   | Opt_DictsCheap
562   | Opt_EnableRewriteRules             -- Apply rewrite rules during simplification
563   | Opt_EnableThSpliceWarnings         -- Enable warnings for TH splices
564   | Opt_RegsGraph                      -- do graph coloring register allocation
565   | Opt_RegsIterative                  -- do iterative coalescing graph coloring register allocation
566   | Opt_PedanticBottoms                -- Be picky about how we treat bottom
567   | Opt_LlvmTBAA                       -- Use LLVM TBAA infastructure for improving AA (hidden flag)
568   | Opt_LlvmFillUndefWithGarbage       -- Testing for undef bugs (hidden flag)
569   | Opt_IrrefutableTuples
570   | Opt_CmmSink
571   | Opt_CmmElimCommonBlocks
572   | Opt_AsmShortcutting
573   | Opt_OmitYields
574   | Opt_FunToThunk               -- allow WwLib.mkWorkerArgs to remove all value lambdas
575   | Opt_DictsStrict                     -- be strict in argument dictionaries
576   | Opt_DmdTxDictSel              -- use a special demand transformer for dictionary selectors
577   | Opt_Loopification                  -- See Note [Self-recursive tail calls]
578   | Opt_CfgBlocklayout             -- ^ Use the cfg based block layout algorithm.
579   | Opt_WeightlessBlocklayout         -- ^ Layout based on last instruction per block.
580   | Opt_CprAnal
581   | Opt_WorkerWrapper
582   | Opt_SolveConstantDicts
583   | Opt_AlignmentSanitisation
584   | Opt_CatchBottoms
585   | Opt_NumConstantFolding
586
587   -- PreInlining is on by default. The option is there just to see how
588   -- bad things get if you turn it off!
589   | Opt_SimplPreInlining
590
591   -- Interface files
592   | Opt_IgnoreInterfacePragmas
593   | Opt_OmitInterfacePragmas
594   | Opt_ExposeAllUnfoldings
595   | Opt_WriteInterface -- forces .hi files to be written even with -fno-code
596   | Opt_WriteHie -- generate .hie files
597
598   -- profiling opts
599   | Opt_AutoSccsOnIndividualCafs
600   | Opt_ProfCountEntries
601
602   -- misc opts
603   | Opt_Pp
604   | Opt_ForceRecomp
605   | Opt_IgnoreOptimChanges
606   | Opt_IgnoreHpcChanges
607   | Opt_ExcessPrecision
608   | Opt_EagerBlackHoling
609   | Opt_NoHsMain
610   | Opt_SplitSections
611   | Opt_StgStats
612   | Opt_HideAllPackages
613   | Opt_HideAllPluginPackages
614   | Opt_PrintBindResult
615   | Opt_Haddock
616   | Opt_HaddockOptions
617   | Opt_BreakOnException
618   | Opt_BreakOnError
619   | Opt_PrintEvldWithShow
620   | Opt_PrintBindContents
621   | Opt_GenManifest
622   | Opt_EmbedManifest
623   | Opt_SharedImplib
624   | Opt_BuildingCabalPackage
625   | Opt_IgnoreDotGhci
626   | Opt_GhciSandbox
627   | Opt_GhciHistory
628   | Opt_GhciLeakCheck
629   | Opt_ValidateHie
630   | Opt_LocalGhciHistory
631   | Opt_NoIt
632   | Opt_HelpfulErrors
633   | Opt_DeferTypeErrors
634   | Opt_DeferTypedHoles
635   | Opt_DeferOutOfScopeVariables
636   | Opt_PIC                         -- ^ @-fPIC@
637   | Opt_PIE                         -- ^ @-fPIE@
638   | Opt_PICExecutable               -- ^ @-pie@
639   | Opt_ExternalDynamicRefs
640   | Opt_SccProfilingOn
641   | Opt_Ticky
642   | Opt_Ticky_Allocd
643   | Opt_Ticky_LNE
644   | Opt_Ticky_Dyn_Thunk
645   | Opt_RPath
646   | Opt_RelativeDynlibPaths
647   | Opt_Hpc
648   | Opt_FlatCache
649   | Opt_ExternalInterpreter
650   | Opt_OptimalApplicativeDo
651   | Opt_VersionMacros
652   | Opt_WholeArchiveHsLibs
653   -- copy all libs into a single folder prior to linking binaries
654   -- this should elivate the excessive command line limit restrictions
655   -- on windows, by only requiring a single -L argument instead of
656   -- one for each dependency.  At the time of this writing, gcc
657   -- forwards all -L flags to the collect2 command without using a
658   -- response file and as such breaking apart.
659   | Opt_SingleLibFolder
660   | Opt_KeepCAFs
661   | Opt_KeepGoing
662   | Opt_ByteCodeIfUnboxed
663
664   -- output style opts
665   | Opt_ErrorSpans -- Include full span info in error messages,
666                    -- instead of just the start position.
667   | Opt_DeferDiagnostics
668   | Opt_DiagnosticsShowCaret -- Show snippets of offending code
669   | Opt_PprCaseAsLet
670   | Opt_PprShowTicks
671   | Opt_ShowHoleConstraints
672    -- Options relating to the display of valid hole fits
673    -- when generating an error message for a typed hole
674    -- See Note [Valid hole fits include] in TcHoleErrors.hs
675   | Opt_ShowValidHoleFits
676   | Opt_SortValidHoleFits
677   | Opt_SortBySizeHoleFits
678   | Opt_SortBySubsumHoleFits
679   | Opt_AbstractRefHoleFits
680   | Opt_UnclutterValidHoleFits
681   | Opt_ShowTypeAppOfHoleFits
682   | Opt_ShowTypeAppVarsOfHoleFits
683   | Opt_ShowDocsOfHoleFits
684   | Opt_ShowTypeOfHoleFits
685   | Opt_ShowProvOfHoleFits
686   | Opt_ShowMatchesOfHoleFits
687
688   | Opt_ShowLoadedModules
689   | Opt_HexWordLiterals -- See Note [Print Hexadecimal Literals]
690
691   -- Suppress all coercions, them replacing with '...'
692   | Opt_SuppressCoercions
693   | Opt_SuppressVarKinds
694   -- Suppress module id prefixes on variables.
695   | Opt_SuppressModulePrefixes
696   -- Suppress type applications.
697   | Opt_SuppressTypeApplications
698   -- Suppress info such as arity and unfoldings on identifiers.
699   | Opt_SuppressIdInfo
700   -- Suppress separate type signatures in core, but leave types on
701   -- lambda bound vars
702   | Opt_SuppressUnfoldings
703   -- Suppress the details of even stable unfoldings
704   | Opt_SuppressTypeSignatures
705   -- Suppress unique ids on variables.
706   -- Except for uniques, as some simplifier phases introduce new
707   -- variables that have otherwise identical names.
708   | Opt_SuppressUniques
709   | Opt_SuppressStgExts
710   | Opt_SuppressTicks     -- Replaces Opt_PprShowTicks
711   | Opt_SuppressTimestamps -- ^ Suppress timestamps in dumps
712
713   -- temporary flags
714   | Opt_AutoLinkPackages
715   | Opt_ImplicitImportQualified
716
717   -- keeping stuff
718   | Opt_KeepHscppFiles
719   | Opt_KeepHiDiffs
720   | Opt_KeepHcFiles
721   | Opt_KeepSFiles
722   | Opt_KeepTmpFiles
723   | Opt_KeepRawTokenStream
724   | Opt_KeepLlvmFiles
725   | Opt_KeepHiFiles
726   | Opt_KeepOFiles
727
728   | Opt_BuildDynamicToo
729
730   -- safe haskell flags
731   | Opt_DistrustAllPackages
732   | Opt_PackageTrust
733   | Opt_PluginTrustworthy
734
735   | Opt_G_NoStateHack
736   | Opt_G_NoOptCoercion
737   deriving (Eq, Show, Enum)
738
739-- Check whether a flag should be considered an "optimisation flag"
740-- for purposes of recompilation avoidance (see
741-- Note [Ignoring some flag changes] in FlagChecker). Being listed here is
742-- not a guarantee that the flag has no other effect. We could, and
743-- perhaps should, separate out the flags that have some minor impact on
744-- program semantics and/or error behavior (e.g., assertions), but
745-- then we'd need to go to extra trouble (and an additional flag)
746-- to allow users to ignore the optimisation level even though that
747-- means ignoring some change.
748optimisationFlags :: EnumSet GeneralFlag
749optimisationFlags = EnumSet.fromList
750   [ Opt_CallArity
751   , Opt_Strictness
752   , Opt_LateDmdAnal
753   , Opt_KillAbsence
754   , Opt_KillOneShot
755   , Opt_FullLaziness
756   , Opt_FloatIn
757   , Opt_LateSpecialise
758   , Opt_Specialise
759   , Opt_SpecialiseAggressively
760   , Opt_CrossModuleSpecialise
761   , Opt_StaticArgumentTransformation
762   , Opt_CSE
763   , Opt_StgCSE
764   , Opt_StgLiftLams
765   , Opt_LiberateCase
766   , Opt_SpecConstr
767   , Opt_SpecConstrKeen
768   , Opt_DoLambdaEtaExpansion
769   , Opt_IgnoreAsserts
770   , Opt_DoEtaReduction
771   , Opt_CaseMerge
772   , Opt_CaseFolding
773   , Opt_UnboxStrictFields
774   , Opt_UnboxSmallStrictFields
775   , Opt_DictsCheap
776   , Opt_EnableRewriteRules
777   , Opt_RegsGraph
778   , Opt_RegsIterative
779   , Opt_PedanticBottoms
780   , Opt_LlvmTBAA
781   , Opt_LlvmFillUndefWithGarbage
782   , Opt_IrrefutableTuples
783   , Opt_CmmSink
784   , Opt_CmmElimCommonBlocks
785   , Opt_AsmShortcutting
786   , Opt_OmitYields
787   , Opt_FunToThunk
788   , Opt_DictsStrict
789   , Opt_DmdTxDictSel
790   , Opt_Loopification
791   , Opt_CfgBlocklayout
792   , Opt_WeightlessBlocklayout
793   , Opt_CprAnal
794   , Opt_WorkerWrapper
795   , Opt_SolveConstantDicts
796   , Opt_CatchBottoms
797   , Opt_IgnoreAsserts
798   ]
799
800-- | Used when outputting warnings: if a reason is given, it is
801-- displayed. If a warning isn't controlled by a flag, this is made
802-- explicit at the point of use.
803data WarnReason
804  = NoReason
805  -- | Warning was enabled with the flag
806  | Reason !WarningFlag
807  -- | Warning was made an error because of -Werror or -Werror=WarningFlag
808  | ErrReason !(Maybe WarningFlag)
809  deriving Show
810
811-- | Used to differentiate the scope an include needs to apply to.
812-- We have to split the include paths to avoid accidentally forcing recursive
813-- includes since -I overrides the system search paths. See #14312.
814data IncludeSpecs
815  = IncludeSpecs { includePathsQuote  :: [String]
816                 , includePathsGlobal :: [String]
817                 }
818  deriving Show
819
820-- | Append to the list of includes a path that shall be included using `-I`
821-- when the C compiler is called. These paths override system search paths.
822addGlobalInclude :: IncludeSpecs -> [String] -> IncludeSpecs
823addGlobalInclude spec paths  = let f = includePathsGlobal spec
824                               in spec { includePathsGlobal = f ++ paths }
825
826-- | Append to the list of includes a path that shall be included using
827-- `-iquote` when the C compiler is called. These paths only apply when quoted
828-- includes are used. e.g. #include "foo.h"
829addQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs
830addQuoteInclude spec paths  = let f = includePathsQuote spec
831                              in spec { includePathsQuote = f ++ paths }
832
833-- | Concatenate and flatten the list of global and quoted includes returning
834-- just a flat list of paths.
835flattenIncludes :: IncludeSpecs -> [String]
836flattenIncludes specs = includePathsQuote specs ++ includePathsGlobal specs
837
838instance Outputable WarnReason where
839  ppr = text . show
840
841instance ToJson WarnReason where
842  json NoReason = JSNull
843  json (Reason wf) = JSString (show wf)
844  json (ErrReason Nothing) = JSString "Opt_WarnIsError"
845  json (ErrReason (Just wf)) = JSString (show wf)
846
847data WarningFlag =
848-- See Note [Updating flag description in the User's Guide]
849     Opt_WarnDuplicateExports
850   | Opt_WarnDuplicateConstraints
851   | Opt_WarnRedundantConstraints
852   | Opt_WarnHiShadows
853   | Opt_WarnImplicitPrelude
854   | Opt_WarnIncompletePatterns
855   | Opt_WarnIncompleteUniPatterns
856   | Opt_WarnIncompletePatternsRecUpd
857   | Opt_WarnOverflowedLiterals
858   | Opt_WarnEmptyEnumerations
859   | Opt_WarnMissingFields
860   | Opt_WarnMissingImportList
861   | Opt_WarnMissingMethods
862   | Opt_WarnMissingSignatures
863   | Opt_WarnMissingLocalSignatures
864   | Opt_WarnNameShadowing
865   | Opt_WarnOverlappingPatterns
866   | Opt_WarnTypeDefaults
867   | Opt_WarnMonomorphism
868   | Opt_WarnUnusedTopBinds
869   | Opt_WarnUnusedLocalBinds
870   | Opt_WarnUnusedPatternBinds
871   | Opt_WarnUnusedImports
872   | Opt_WarnUnusedMatches
873   | Opt_WarnUnusedTypePatterns
874   | Opt_WarnUnusedForalls
875   | Opt_WarnUnusedRecordWildcards
876   | Opt_WarnRedundantRecordWildcards
877   | Opt_WarnWarningsDeprecations
878   | Opt_WarnDeprecatedFlags
879   | Opt_WarnMissingMonadFailInstances -- since 8.0
880   | Opt_WarnSemigroup -- since 8.0
881   | Opt_WarnDodgyExports
882   | Opt_WarnDodgyImports
883   | Opt_WarnOrphans
884   | Opt_WarnAutoOrphans
885   | Opt_WarnIdentities
886   | Opt_WarnTabs
887   | Opt_WarnUnrecognisedPragmas
888   | Opt_WarnDodgyForeignImports
889   | Opt_WarnUnusedDoBind
890   | Opt_WarnWrongDoBind
891   | Opt_WarnAlternativeLayoutRuleTransitional
892   | Opt_WarnUnsafe
893   | Opt_WarnSafe
894   | Opt_WarnTrustworthySafe
895   | Opt_WarnMissedSpecs
896   | Opt_WarnAllMissedSpecs
897   | Opt_WarnUnsupportedCallingConventions
898   | Opt_WarnUnsupportedLlvmVersion
899   | Opt_WarnMissedExtraSharedLib
900   | Opt_WarnInlineRuleShadowing
901   | Opt_WarnTypedHoles
902   | Opt_WarnPartialTypeSignatures
903   | Opt_WarnMissingExportedSignatures
904   | Opt_WarnUntickedPromotedConstructors
905   | Opt_WarnDerivingTypeable
906   | Opt_WarnDeferredTypeErrors
907   | Opt_WarnDeferredOutOfScopeVariables
908   | Opt_WarnNonCanonicalMonadInstances   -- since 8.0
909   | Opt_WarnNonCanonicalMonadFailInstances   -- since 8.0, removed 8.8
910   | Opt_WarnNonCanonicalMonoidInstances  -- since 8.0
911   | Opt_WarnMissingPatternSynonymSignatures -- since 8.0
912   | Opt_WarnUnrecognisedWarningFlags     -- since 8.0
913   | Opt_WarnSimplifiableClassConstraints -- Since 8.2
914   | Opt_WarnCPPUndef                     -- Since 8.2
915   | Opt_WarnUnbangedStrictPatterns       -- Since 8.2
916   | Opt_WarnMissingHomeModules           -- Since 8.2
917   | Opt_WarnPartialFields                -- Since 8.4
918   | Opt_WarnMissingExportList
919   | Opt_WarnInaccessibleCode
920   | Opt_WarnStarIsType                   -- Since 8.6
921   | Opt_WarnStarBinder                   -- Since 8.6
922   | Opt_WarnImplicitKindVars             -- Since 8.6
923   | Opt_WarnSpaceAfterBang
924   | Opt_WarnMissingDerivingStrategies    -- Since 8.8
925   | Opt_WarnPrepositiveQualifiedModule   -- Since TBD
926   | Opt_WarnUnusedPackages               -- Since 8.10
927   | Opt_WarnInferredSafeImports          -- Since 8.10
928   | Opt_WarnMissingSafeHaskellMode       -- Since 8.10
929   | Opt_WarnCompatUnqualifiedImports     -- Since 8.10
930   | Opt_WarnDerivingDefaults
931   deriving (Eq, Show, Enum)
932
933data Language = Haskell98 | Haskell2010
934   deriving (Eq, Enum, Show)
935
936instance Outputable Language where
937    ppr = text . show
938
939-- | The various Safe Haskell modes
940data SafeHaskellMode
941   = Sf_None          -- ^ inferred unsafe
942   | Sf_Unsafe        -- ^ declared and checked
943   | Sf_Trustworthy   -- ^ declared and checked
944   | Sf_Safe          -- ^ declared and checked
945   | Sf_SafeInferred  -- ^ inferred as safe
946   | Sf_Ignore        -- ^ @-fno-safe-haskell@ state
947   deriving (Eq)
948
949instance Show SafeHaskellMode where
950    show Sf_None         = "None"
951    show Sf_Unsafe       = "Unsafe"
952    show Sf_Trustworthy  = "Trustworthy"
953    show Sf_Safe         = "Safe"
954    show Sf_SafeInferred = "Safe-Inferred"
955    show Sf_Ignore       = "Ignore"
956
957instance Outputable SafeHaskellMode where
958    ppr = text . show
959
960-- | Contains not only a collection of 'GeneralFlag's but also a plethora of
961-- information relating to the compilation of a single file or GHC session
962data DynFlags = DynFlags {
963  ghcMode               :: GhcMode,
964  ghcLink               :: GhcLink,
965  hscTarget             :: HscTarget,
966
967  -- formerly Settings
968  ghcNameVersion    :: {-# UNPACK #-} !GhcNameVersion,
969  fileSettings      :: {-# UNPACK #-} !FileSettings,
970  targetPlatform    :: Platform,       -- Filled in by SysTools
971  toolSettings      :: {-# UNPACK #-} !ToolSettings,
972  platformMisc      :: {-# UNPACK #-} !PlatformMisc,
973  platformConstants :: PlatformConstants,
974  rawSettings       :: [(String, String)],
975
976  integerLibrary        :: IntegerLibrary,
977    -- ^ IntegerGMP or IntegerSimple. Set at configure time, but may be overriden
978    --   by GHC-API users. See Note [The integer library] in PrelNames
979  llvmConfig            :: LlvmConfig,
980    -- ^ N.B. It's important that this field is lazy since we load the LLVM
981    -- configuration lazily. See Note [LLVM Configuration] in SysTools.
982  verbosity             :: Int,         -- ^ Verbosity level: see Note [Verbosity levels]
983  optLevel              :: Int,         -- ^ Optimisation level
984  debugLevel            :: Int,         -- ^ How much debug information to produce
985  simplPhases           :: Int,         -- ^ Number of simplifier phases
986  maxSimplIterations    :: Int,         -- ^ Max simplifier iterations
987  ruleCheck             :: Maybe String,
988  inlineCheck           :: Maybe String, -- ^ A prefix to report inlining decisions about
989  strictnessBefore      :: [Int],       -- ^ Additional demand analysis
990
991  parMakeCount          :: Maybe Int,   -- ^ The number of modules to compile in parallel
992                                        --   in --make mode, where Nothing ==> compile as
993                                        --   many in parallel as there are CPUs.
994
995  enableTimeStats       :: Bool,        -- ^ Enable RTS timing statistics?
996  ghcHeapSize           :: Maybe Int,   -- ^ The heap size to set.
997
998  maxRelevantBinds      :: Maybe Int,   -- ^ Maximum number of bindings from the type envt
999                                        --   to show in type error messages
1000  maxValidHoleFits      :: Maybe Int,   -- ^ Maximum number of hole fits to show
1001                                        --   in typed hole error messages
1002  maxRefHoleFits        :: Maybe Int,   -- ^ Maximum number of refinement hole
1003                                        --   fits to show in typed hole error
1004                                        --   messages
1005  refLevelHoleFits      :: Maybe Int,   -- ^ Maximum level of refinement for
1006                                        --   refinement hole fits in typed hole
1007                                        --   error messages
1008  maxUncoveredPatterns  :: Int,         -- ^ Maximum number of unmatched patterns to show
1009                                        --   in non-exhaustiveness warnings
1010  maxPmCheckModels      :: Int,         -- ^ Soft limit on the number of models
1011                                        --   the pattern match checker checks
1012                                        --   a pattern against. A safe guard
1013                                        --   against exponential blow-up.
1014  simplTickFactor       :: Int,         -- ^ Multiplier for simplifier ticks
1015  specConstrThreshold   :: Maybe Int,   -- ^ Threshold for SpecConstr
1016  specConstrCount       :: Maybe Int,   -- ^ Max number of specialisations for any one function
1017  specConstrRecursive   :: Int,         -- ^ Max number of specialisations for recursive types
1018                                        --   Not optional; otherwise ForceSpecConstr can diverge.
1019  binBlobThreshold      :: Word,        -- ^ Binary literals (e.g. strings) whose size is above
1020                                        --   this threshold will be dumped in a binary file
1021                                        --   by the assembler code generator (0 to disable)
1022  liberateCaseThreshold :: Maybe Int,   -- ^ Threshold for LiberateCase
1023  floatLamArgs          :: Maybe Int,   -- ^ Arg count for lambda floating
1024                                        --   See CoreMonad.FloatOutSwitches
1025
1026  liftLamsRecArgs       :: Maybe Int,   -- ^ Maximum number of arguments after lambda lifting a
1027                                        --   recursive function.
1028  liftLamsNonRecArgs    :: Maybe Int,   -- ^ Maximum number of arguments after lambda lifting a
1029                                        --   non-recursive function.
1030  liftLamsKnown         :: Bool,        -- ^ Lambda lift even when this turns a known call
1031                                        --   into an unknown call.
1032
1033  cmmProcAlignment      :: Maybe Int,   -- ^ Align Cmm functions at this boundary or use default.
1034
1035  historySize           :: Int,         -- ^ Simplification history size
1036
1037  importPaths           :: [FilePath],
1038  mainModIs             :: Module,
1039  mainFunIs             :: Maybe String,
1040  reductionDepth        :: IntWithInf,   -- ^ Typechecker maximum stack depth
1041  solverIterations      :: IntWithInf,   -- ^ Number of iterations in the constraints solver
1042                                         --   Typically only 1 is needed
1043
1044  thisInstalledUnitId   :: InstalledUnitId,
1045  thisComponentId_      :: Maybe ComponentId,
1046  thisUnitIdInsts_      :: Maybe [(ModuleName, Module)],
1047
1048  -- ways
1049  ways                  :: [Way],       -- ^ Way flags from the command line
1050  buildTag              :: String,      -- ^ The global \"way\" (e.g. \"p\" for prof)
1051
1052  -- For object splitting
1053  splitInfo             :: Maybe (String,Int),
1054
1055  -- paths etc.
1056  objectDir             :: Maybe String,
1057  dylibInstallName      :: Maybe String,
1058  hiDir                 :: Maybe String,
1059  hieDir                :: Maybe String,
1060  stubDir               :: Maybe String,
1061  dumpDir               :: Maybe String,
1062
1063  objectSuf             :: String,
1064  hcSuf                 :: String,
1065  hiSuf                 :: String,
1066  hieSuf                :: String,
1067
1068  canGenerateDynamicToo :: IORef Bool,
1069  dynObjectSuf          :: String,
1070  dynHiSuf              :: String,
1071
1072  outputFile            :: Maybe String,
1073  dynOutputFile         :: Maybe String,
1074  outputHi              :: Maybe String,
1075  dynLibLoader          :: DynLibLoader,
1076
1077  -- | This is set by 'DriverPipeline.runPipeline' based on where
1078  --    its output is going.
1079  dumpPrefix            :: Maybe FilePath,
1080
1081  -- | Override the 'dumpPrefix' set by 'DriverPipeline.runPipeline'.
1082  --    Set by @-ddump-file-prefix@
1083  dumpPrefixForce       :: Maybe FilePath,
1084
1085  ldInputs              :: [Option],
1086
1087  includePaths          :: IncludeSpecs,
1088  libraryPaths          :: [String],
1089  frameworkPaths        :: [String],    -- used on darwin only
1090  cmdlineFrameworks     :: [String],    -- ditto
1091
1092  rtsOpts               :: Maybe String,
1093  rtsOptsEnabled        :: RtsOptsEnabled,
1094  rtsOptsSuggestions    :: Bool,
1095
1096  hpcDir                :: String,      -- ^ Path to store the .mix files
1097
1098  -- Plugins
1099  pluginModNames        :: [ModuleName],
1100  pluginModNameOpts     :: [(ModuleName,String)],
1101  frontendPluginOpts    :: [String],
1102    -- ^ the @-ffrontend-opt@ flags given on the command line, in *reverse*
1103    -- order that they're specified on the command line.
1104  cachedPlugins         :: [LoadedPlugin],
1105    -- ^ plugins dynamically loaded after processing arguments. What will be
1106    -- loaded here is directed by pluginModNames. Arguments are loaded from
1107    -- pluginModNameOpts. The purpose of this field is to cache the plugins so
1108    -- they don't have to be loaded each time they are needed.  See
1109    -- 'DynamicLoading.initializePlugins'.
1110  staticPlugins            :: [StaticPlugin],
1111    -- ^ staic plugins which do not need dynamic loading. These plugins are
1112    -- intended to be added by GHC API users directly to this list.
1113    --
1114    -- To add dynamically loaded plugins through the GHC API see
1115    -- 'addPluginModuleName' instead.
1116
1117  -- GHC API hooks
1118  hooks                 :: Hooks,
1119
1120  --  For ghc -M
1121  depMakefile           :: FilePath,
1122  depIncludePkgDeps     :: Bool,
1123  depIncludeCppDeps     :: Bool,
1124  depExcludeMods        :: [ModuleName],
1125  depSuffixes           :: [String],
1126
1127  --  Package flags
1128  packageDBFlags        :: [PackageDBFlag],
1129        -- ^ The @-package-db@ flags given on the command line, In
1130        -- *reverse* order that they're specified on the command line.
1131        -- This is intended to be applied with the list of "initial"
1132        -- package databases derived from @GHC_PACKAGE_PATH@; see
1133        -- 'getPackageConfRefs'.
1134
1135  ignorePackageFlags    :: [IgnorePackageFlag],
1136        -- ^ The @-ignore-package@ flags from the command line.
1137        -- In *reverse* order that they're specified on the command line.
1138  packageFlags          :: [PackageFlag],
1139        -- ^ The @-package@ and @-hide-package@ flags from the command-line.
1140        -- In *reverse* order that they're specified on the command line.
1141  pluginPackageFlags    :: [PackageFlag],
1142        -- ^ The @-plugin-package-id@ flags from command line.
1143        -- In *reverse* order that they're specified on the command line.
1144  trustFlags            :: [TrustFlag],
1145        -- ^ The @-trust@ and @-distrust@ flags.
1146        -- In *reverse* order that they're specified on the command line.
1147  packageEnv            :: Maybe FilePath,
1148        -- ^ Filepath to the package environment file (if overriding default)
1149
1150  -- Package state
1151  -- NB. do not modify this field, it is calculated by
1152  -- Packages.initPackages
1153  pkgDatabase           :: Maybe [(FilePath, [PackageConfig])],
1154  pkgState              :: PackageState,
1155
1156  -- Temporary files
1157  -- These have to be IORefs, because the defaultCleanupHandler needs to
1158  -- know what to clean when an exception happens
1159  filesToClean          :: IORef FilesToClean,
1160  dirsToClean           :: IORef (Map FilePath FilePath),
1161  -- The next available suffix to uniquely name a temp file, updated atomically
1162  nextTempSuffix        :: IORef Int,
1163
1164  -- Names of files which were generated from -ddump-to-file; used to
1165  -- track which ones we need to truncate because it's our first run
1166  -- through
1167  generatedDumps        :: IORef (Set FilePath),
1168
1169  -- hsc dynamic flags
1170  dumpFlags             :: EnumSet DumpFlag,
1171  generalFlags          :: EnumSet GeneralFlag,
1172  warningFlags          :: EnumSet WarningFlag,
1173  fatalWarningFlags     :: EnumSet WarningFlag,
1174  -- Don't change this without updating extensionFlags:
1175  language              :: Maybe Language,
1176  -- | Safe Haskell mode
1177  safeHaskell           :: SafeHaskellMode,
1178  safeInfer             :: Bool,
1179  safeInferred          :: Bool,
1180  -- We store the location of where some extension and flags were turned on so
1181  -- we can produce accurate error messages when Safe Haskell fails due to
1182  -- them.
1183  thOnLoc               :: SrcSpan,
1184  newDerivOnLoc         :: SrcSpan,
1185  overlapInstLoc        :: SrcSpan,
1186  incoherentOnLoc       :: SrcSpan,
1187  pkgTrustOnLoc         :: SrcSpan,
1188  warnSafeOnLoc         :: SrcSpan,
1189  warnUnsafeOnLoc       :: SrcSpan,
1190  trustworthyOnLoc      :: SrcSpan,
1191  -- Don't change this without updating extensionFlags:
1192  -- Here we collect the settings of the language extensions
1193  -- from the command line, the ghci config file and
1194  -- from interactive :set / :seti commands.
1195  extensions            :: [OnOff LangExt.Extension],
1196  -- extensionFlags should always be equal to
1197  --     flattenExtensionFlags language extensions
1198  -- LangExt.Extension is defined in libraries/ghc-boot so that it can be used
1199  -- by template-haskell
1200  extensionFlags        :: EnumSet LangExt.Extension,
1201
1202  -- Unfolding control
1203  -- See Note [Discounts and thresholds] in CoreUnfold
1204  ufCreationThreshold   :: Int,
1205  ufUseThreshold        :: Int,
1206  ufFunAppDiscount      :: Int,
1207  ufDictDiscount        :: Int,
1208  ufKeenessFactor       :: Float,
1209  ufDearOp              :: Int,
1210  ufVeryAggressive      :: Bool,
1211
1212  maxWorkerArgs         :: Int,
1213
1214  ghciHistSize          :: Int,
1215
1216  -- | MsgDoc output action: use "ErrUtils" instead of this if you can
1217  log_action            :: LogAction,
1218  flushOut              :: FlushOut,
1219  flushErr              :: FlushErr,
1220
1221  ghcVersionFile        :: Maybe FilePath,
1222  haddockOptions        :: Maybe String,
1223
1224  -- | GHCi scripts specified by -ghci-script, in reverse order
1225  ghciScripts           :: [String],
1226
1227  -- Output style options
1228  pprUserLength         :: Int,
1229  pprCols               :: Int,
1230
1231  useUnicode            :: Bool,
1232  useColor              :: OverridingBool,
1233  canUseColor           :: Bool,
1234  colScheme             :: Col.Scheme,
1235
1236  -- | what kind of {-# SCC #-} to add automatically
1237  profAuto              :: ProfAuto,
1238
1239  interactivePrint      :: Maybe String,
1240
1241  nextWrapperNum        :: IORef (ModuleEnv Int),
1242
1243  -- | Machine dependent flags (-m<blah> stuff)
1244  sseVersion            :: Maybe SseVersion,
1245  bmiVersion            :: Maybe BmiVersion,
1246  avx                   :: Bool,
1247  avx2                  :: Bool,
1248  avx512cd              :: Bool, -- Enable AVX-512 Conflict Detection Instructions.
1249  avx512er              :: Bool, -- Enable AVX-512 Exponential and Reciprocal Instructions.
1250  avx512f               :: Bool, -- Enable AVX-512 instructions.
1251  avx512pf              :: Bool, -- Enable AVX-512 PreFetch Instructions.
1252
1253  -- | Run-time linker information (what options we need, etc.)
1254  rtldInfo              :: IORef (Maybe LinkerInfo),
1255
1256  -- | Run-time compiler information
1257  rtccInfo              :: IORef (Maybe CompilerInfo),
1258
1259  -- Constants used to control the amount of optimization done.
1260
1261  -- | Max size, in bytes, of inline array allocations.
1262  maxInlineAllocSize    :: Int,
1263
1264  -- | Only inline memcpy if it generates no more than this many
1265  -- pseudo (roughly: Cmm) instructions.
1266  maxInlineMemcpyInsns  :: Int,
1267
1268  -- | Only inline memset if it generates no more than this many
1269  -- pseudo (roughly: Cmm) instructions.
1270  maxInlineMemsetInsns  :: Int,
1271
1272  -- | Reverse the order of error messages in GHC/GHCi
1273  reverseErrors         :: Bool,
1274
1275  -- | Limit the maximum number of errors to show
1276  maxErrors             :: Maybe Int,
1277
1278  -- | Unique supply configuration for testing build determinism
1279  initialUnique         :: Int,
1280  uniqueIncrement       :: Int,
1281
1282  -- | Temporary: CFG Edge weights for fast iterations
1283  cfgWeightInfo         :: CfgWeights
1284}
1285
1286-- | Edge weights to use when generating a CFG from CMM
1287data CfgWeights
1288    = CFGWeights
1289    { uncondWeight :: Int
1290    , condBranchWeight :: Int
1291    , switchWeight :: Int
1292    , callWeight :: Int
1293    , likelyCondWeight :: Int
1294    , unlikelyCondWeight :: Int
1295    , infoTablePenalty :: Int
1296    , backEdgeBonus :: Int
1297    }
1298
1299defaultCfgWeights :: CfgWeights
1300defaultCfgWeights
1301    = CFGWeights
1302    { uncondWeight = 1000
1303    , condBranchWeight = 800
1304    , switchWeight = 1
1305    , callWeight = -10
1306    , likelyCondWeight = 900
1307    , unlikelyCondWeight = 300
1308    , infoTablePenalty = 300
1309    , backEdgeBonus = 400
1310    }
1311
1312parseCfgWeights :: String -> CfgWeights -> CfgWeights
1313parseCfgWeights s oldWeights =
1314        foldl' (\cfg (n,v) -> update n v cfg) oldWeights assignments
1315    where
1316        assignments = map assignment $ settings s
1317        update "uncondWeight" n w =
1318            w {uncondWeight = n}
1319        update "condBranchWeight" n w =
1320            w {condBranchWeight = n}
1321        update "switchWeight" n w =
1322            w {switchWeight = n}
1323        update "callWeight" n w =
1324            w {callWeight = n}
1325        update "likelyCondWeight" n w =
1326            w {likelyCondWeight = n}
1327        update "unlikelyCondWeight" n w =
1328            w {unlikelyCondWeight = n}
1329        update "infoTablePenalty" n w =
1330            w {infoTablePenalty = n}
1331        update "backEdgeBonus" n w =
1332            w {backEdgeBonus = n}
1333        update other _ _
1334            = panic $ other ++
1335                      " is not a cfg weight parameter. " ++
1336                      exampleString
1337        settings s
1338            | (s1,rest) <- break (== ',') s
1339            , null rest
1340            = [s1]
1341            | (s1,rest) <- break (== ',') s
1342            = [s1] ++ settings (drop 1 rest)
1343            | otherwise = panic $ "Invalid cfg parameters." ++ exampleString
1344        assignment as
1345            | (name, _:val) <- break (== '=') as
1346            = (name,read val)
1347            | otherwise
1348            = panic $ "Invalid cfg parameters." ++ exampleString
1349        exampleString = "Example parameters: uncondWeight=1000," ++
1350            "condBranchWeight=800,switchWeight=0,callWeight=300" ++
1351            ",likelyCondWeight=900,unlikelyCondWeight=300" ++
1352            ",infoTablePenalty=300,backEdgeBonus=400"
1353
1354backendMaintainsCfg :: DynFlags -> Bool
1355backendMaintainsCfg dflags = case (platformArch $ targetPlatform dflags) of
1356    -- ArchX86 -- Should work but not tested so disabled currently.
1357    ArchX86_64 -> True
1358    _otherwise -> False
1359
1360class HasDynFlags m where
1361    getDynFlags :: m DynFlags
1362
1363{- It would be desirable to have the more generalised
1364
1365  instance (MonadTrans t, Monad m, HasDynFlags m) => HasDynFlags (t m) where
1366      getDynFlags = lift getDynFlags
1367
1368instance definition. However, that definition would overlap with the
1369`HasDynFlags (GhcT m)` instance. Instead we define instances for a
1370couple of common Monad transformers explicitly. -}
1371
1372instance (Monoid a, Monad m, HasDynFlags m) => HasDynFlags (WriterT a m) where
1373    getDynFlags = lift getDynFlags
1374
1375instance (Monad m, HasDynFlags m) => HasDynFlags (ReaderT a m) where
1376    getDynFlags = lift getDynFlags
1377
1378instance (Monad m, HasDynFlags m) => HasDynFlags (MaybeT m) where
1379    getDynFlags = lift getDynFlags
1380
1381instance (Monad m, HasDynFlags m) => HasDynFlags (ExceptT e m) where
1382    getDynFlags = lift getDynFlags
1383
1384class ContainsDynFlags t where
1385    extractDynFlags :: t -> DynFlags
1386
1387data ProfAuto
1388  = NoProfAuto         -- ^ no SCC annotations added
1389  | ProfAutoAll        -- ^ top-level and nested functions are annotated
1390  | ProfAutoTop        -- ^ top-level functions annotated only
1391  | ProfAutoExports    -- ^ exported functions annotated only
1392  | ProfAutoCalls      -- ^ annotate call-sites
1393  deriving (Eq,Enum)
1394
1395data LlvmTarget = LlvmTarget
1396  { lDataLayout :: String
1397  , lCPU        :: String
1398  , lAttributes :: [String]
1399  }
1400
1401-- | See Note [LLVM Configuration] in SysTools.
1402data LlvmConfig = LlvmConfig { llvmTargets :: [(String, LlvmTarget)]
1403                             , llvmPasses  :: [(Int, String)]
1404                             }
1405
1406-----------------------------------------------------------------------------
1407-- Accessessors from 'DynFlags'
1408
1409-- | "unbuild" a 'Settings' from a 'DynFlags'. This shouldn't be needed in the
1410-- vast majority of code. But GHCi questionably uses this to produce a default
1411-- 'DynFlags' from which to compute a flags diff for printing.
1412settings :: DynFlags -> Settings
1413settings dflags = Settings
1414  { sGhcNameVersion = ghcNameVersion dflags
1415  , sFileSettings = fileSettings dflags
1416  , sTargetPlatform = targetPlatform dflags
1417  , sToolSettings = toolSettings dflags
1418  , sPlatformMisc = platformMisc dflags
1419  , sPlatformConstants = platformConstants dflags
1420  , sRawSettings = rawSettings dflags
1421  }
1422
1423programName :: DynFlags -> String
1424programName dflags = ghcNameVersion_programName $ ghcNameVersion dflags
1425projectVersion :: DynFlags -> String
1426projectVersion dflags = ghcNameVersion_projectVersion (ghcNameVersion dflags)
1427ghcUsagePath          :: DynFlags -> FilePath
1428ghcUsagePath dflags = fileSettings_ghcUsagePath $ fileSettings dflags
1429ghciUsagePath         :: DynFlags -> FilePath
1430ghciUsagePath dflags = fileSettings_ghciUsagePath $ fileSettings dflags
1431toolDir               :: DynFlags -> Maybe FilePath
1432toolDir dflags = fileSettings_toolDir $ fileSettings dflags
1433topDir                :: DynFlags -> FilePath
1434topDir dflags = fileSettings_topDir $ fileSettings dflags
1435tmpDir                :: DynFlags -> String
1436tmpDir dflags = fileSettings_tmpDir $ fileSettings dflags
1437extraGccViaCFlags     :: DynFlags -> [String]
1438extraGccViaCFlags dflags = toolSettings_extraGccViaCFlags $ toolSettings dflags
1439systemPackageConfig   :: DynFlags -> FilePath
1440systemPackageConfig dflags = fileSettings_systemPackageConfig $ fileSettings dflags
1441pgm_L                 :: DynFlags -> String
1442pgm_L dflags = toolSettings_pgm_L $ toolSettings dflags
1443pgm_P                 :: DynFlags -> (String,[Option])
1444pgm_P dflags = toolSettings_pgm_P $ toolSettings dflags
1445pgm_F                 :: DynFlags -> String
1446pgm_F dflags = toolSettings_pgm_F $ toolSettings dflags
1447pgm_c                 :: DynFlags -> String
1448pgm_c dflags = toolSettings_pgm_c $ toolSettings dflags
1449pgm_a                 :: DynFlags -> (String,[Option])
1450pgm_a dflags = toolSettings_pgm_a $ toolSettings dflags
1451pgm_l                 :: DynFlags -> (String,[Option])
1452pgm_l dflags = toolSettings_pgm_l $ toolSettings dflags
1453pgm_lm                 :: DynFlags -> (String,[Option])
1454pgm_lm dflags = toolSettings_pgm_lm $ toolSettings dflags
1455pgm_dll               :: DynFlags -> (String,[Option])
1456pgm_dll dflags = toolSettings_pgm_dll $ toolSettings dflags
1457pgm_T                 :: DynFlags -> String
1458pgm_T dflags = toolSettings_pgm_T $ toolSettings dflags
1459pgm_windres           :: DynFlags -> String
1460pgm_windres dflags = toolSettings_pgm_windres $ toolSettings dflags
1461pgm_libtool           :: DynFlags -> String
1462pgm_libtool dflags = toolSettings_pgm_libtool $ toolSettings dflags
1463pgm_lcc               :: DynFlags -> (String,[Option])
1464pgm_lcc dflags = toolSettings_pgm_lcc $ toolSettings dflags
1465pgm_ar                :: DynFlags -> String
1466pgm_ar dflags = toolSettings_pgm_ar $ toolSettings dflags
1467pgm_otool             :: DynFlags -> String
1468pgm_otool dflags = toolSettings_pgm_otool $ toolSettings dflags
1469pgm_install_name_tool :: DynFlags -> String
1470pgm_install_name_tool dflags = toolSettings_pgm_install_name_tool $ toolSettings dflags
1471pgm_ranlib            :: DynFlags -> String
1472pgm_ranlib dflags = toolSettings_pgm_ranlib $ toolSettings dflags
1473pgm_lo                :: DynFlags -> (String,[Option])
1474pgm_lo dflags = toolSettings_pgm_lo $ toolSettings dflags
1475pgm_lc                :: DynFlags -> (String,[Option])
1476pgm_lc dflags = toolSettings_pgm_lc $ toolSettings dflags
1477pgm_i                 :: DynFlags -> String
1478pgm_i dflags = toolSettings_pgm_i $ toolSettings dflags
1479opt_L                 :: DynFlags -> [String]
1480opt_L dflags = toolSettings_opt_L $ toolSettings dflags
1481opt_P                 :: DynFlags -> [String]
1482opt_P dflags = concatMap (wayOptP (targetPlatform dflags)) (ways dflags)
1483            ++ toolSettings_opt_P (toolSettings dflags)
1484
1485-- This function packages everything that's needed to fingerprint opt_P
1486-- flags. See Note [Repeated -optP hashing].
1487opt_P_signature       :: DynFlags -> ([String], Fingerprint)
1488opt_P_signature dflags =
1489  ( concatMap (wayOptP (targetPlatform dflags)) (ways dflags)
1490  , toolSettings_opt_P_fingerprint $ toolSettings dflags
1491  )
1492
1493opt_F                 :: DynFlags -> [String]
1494opt_F dflags= toolSettings_opt_F $ toolSettings dflags
1495opt_c                 :: DynFlags -> [String]
1496opt_c dflags = concatMap (wayOptc (targetPlatform dflags)) (ways dflags)
1497            ++ toolSettings_opt_c (toolSettings dflags)
1498opt_cxx               :: DynFlags -> [String]
1499opt_cxx dflags= toolSettings_opt_cxx $ toolSettings dflags
1500opt_a                 :: DynFlags -> [String]
1501opt_a dflags= toolSettings_opt_a $ toolSettings dflags
1502opt_l                 :: DynFlags -> [String]
1503opt_l dflags = concatMap (wayOptl (targetPlatform dflags)) (ways dflags)
1504            ++ toolSettings_opt_l (toolSettings dflags)
1505opt_lm                :: DynFlags -> [String]
1506opt_lm dflags= toolSettings_opt_lm $ toolSettings dflags
1507opt_windres           :: DynFlags -> [String]
1508opt_windres dflags= toolSettings_opt_windres $ toolSettings dflags
1509opt_lcc                :: DynFlags -> [String]
1510opt_lcc dflags= toolSettings_opt_lcc $ toolSettings dflags
1511opt_lo                :: DynFlags -> [String]
1512opt_lo dflags= toolSettings_opt_lo $ toolSettings dflags
1513opt_lc                :: DynFlags -> [String]
1514opt_lc dflags= toolSettings_opt_lc $ toolSettings dflags
1515opt_i                 :: DynFlags -> [String]
1516opt_i dflags= toolSettings_opt_i $ toolSettings dflags
1517
1518tablesNextToCode :: DynFlags -> Bool
1519tablesNextToCode = platformMisc_tablesNextToCode . platformMisc
1520
1521-- | The directory for this version of ghc in the user's app directory
1522-- (typically something like @~/.ghc/x86_64-linux-7.6.3@)
1523--
1524versionedAppDir :: DynFlags -> MaybeT IO FilePath
1525versionedAppDir dflags = do
1526  -- Make sure we handle the case the HOME isn't set (see #11678)
1527  appdir <- tryMaybeT $ getAppUserDataDirectory (programName dflags)
1528  return $ appdir </> versionedFilePath dflags
1529
1530versionedFilePath :: DynFlags -> FilePath
1531versionedFilePath dflags = uniqueSubdir $ platformMini $ targetPlatform dflags
1532
1533-- | The target code type of the compilation (if any).
1534--
1535-- Whenever you change the target, also make sure to set 'ghcLink' to
1536-- something sensible.
1537--
1538-- 'HscNothing' can be used to avoid generating any output, however, note
1539-- that:
1540--
1541--  * If a program uses Template Haskell the typechecker may need to run code
1542--    from an imported module.  To facilitate this, code generation is enabled
1543--    for modules imported by modules that use template haskell.
1544--    See Note [-fno-code mode].
1545--
1546data HscTarget
1547  = HscC           -- ^ Generate C code.
1548  | HscAsm         -- ^ Generate assembly using the native code generator.
1549  | HscLlvm        -- ^ Generate assembly using the llvm code generator.
1550  | HscInterpreted -- ^ Generate bytecode.  (Requires 'LinkInMemory')
1551  | HscNothing     -- ^ Don't generate any code.  See notes above.
1552  deriving (Eq, Show)
1553
1554-- | Will this target result in an object file on the disk?
1555isObjectTarget :: HscTarget -> Bool
1556isObjectTarget HscC     = True
1557isObjectTarget HscAsm   = True
1558isObjectTarget HscLlvm  = True
1559isObjectTarget _        = False
1560
1561-- | Does this target retain *all* top-level bindings for a module,
1562-- rather than just the exported bindings, in the TypeEnv and compiled
1563-- code (if any)?  In interpreted mode we do this, so that GHCi can
1564-- call functions inside a module.  In HscNothing mode we also do it,
1565-- so that Haddock can get access to the GlobalRdrEnv for a module
1566-- after typechecking it.
1567targetRetainsAllBindings :: HscTarget -> Bool
1568targetRetainsAllBindings HscInterpreted = True
1569targetRetainsAllBindings HscNothing     = True
1570targetRetainsAllBindings _              = False
1571
1572-- | The 'GhcMode' tells us whether we're doing multi-module
1573-- compilation (controlled via the "GHC" API) or one-shot
1574-- (single-module) compilation.  This makes a difference primarily to
1575-- the "Finder": in one-shot mode we look for interface files for
1576-- imported modules, but in multi-module mode we look for source files
1577-- in order to check whether they need to be recompiled.
1578data GhcMode
1579  = CompManager         -- ^ @\-\-make@, GHCi, etc.
1580  | OneShot             -- ^ @ghc -c Foo.hs@
1581  | MkDepend            -- ^ @ghc -M@, see "Finder" for why we need this
1582  deriving Eq
1583
1584instance Outputable GhcMode where
1585  ppr CompManager = text "CompManager"
1586  ppr OneShot     = text "OneShot"
1587  ppr MkDepend    = text "MkDepend"
1588
1589isOneShot :: GhcMode -> Bool
1590isOneShot OneShot = True
1591isOneShot _other  = False
1592
1593-- | What to do in the link step, if there is one.
1594data GhcLink
1595  = NoLink              -- ^ Don't link at all
1596  | LinkBinary          -- ^ Link object code into a binary
1597  | LinkInMemory        -- ^ Use the in-memory dynamic linker (works for both
1598                        --   bytecode and object code).
1599  | LinkDynLib          -- ^ Link objects into a dynamic lib (DLL on Windows, DSO on ELF platforms)
1600  | LinkStaticLib       -- ^ Link objects into a static lib
1601  deriving (Eq, Show)
1602
1603isNoLink :: GhcLink -> Bool
1604isNoLink NoLink = True
1605isNoLink _      = False
1606
1607-- | We accept flags which make packages visible, but how they select
1608-- the package varies; this data type reflects what selection criterion
1609-- is used.
1610data PackageArg =
1611      PackageArg String    -- ^ @-package@, by 'PackageName'
1612    | UnitIdArg UnitId     -- ^ @-package-id@, by 'UnitId'
1613  deriving (Eq, Show)
1614instance Outputable PackageArg where
1615    ppr (PackageArg pn) = text "package" <+> text pn
1616    ppr (UnitIdArg uid) = text "unit" <+> ppr uid
1617
1618-- | Represents the renaming that may be associated with an exposed
1619-- package, e.g. the @rns@ part of @-package "foo (rns)"@.
1620--
1621-- Here are some example parsings of the package flags (where
1622-- a string literal is punned to be a 'ModuleName':
1623--
1624--      * @-package foo@ is @ModRenaming True []@
1625--      * @-package foo ()@ is @ModRenaming False []@
1626--      * @-package foo (A)@ is @ModRenaming False [("A", "A")]@
1627--      * @-package foo (A as B)@ is @ModRenaming False [("A", "B")]@
1628--      * @-package foo with (A as B)@ is @ModRenaming True [("A", "B")]@
1629data ModRenaming = ModRenaming {
1630    modRenamingWithImplicit :: Bool, -- ^ Bring all exposed modules into scope?
1631    modRenamings :: [(ModuleName, ModuleName)] -- ^ Bring module @m@ into scope
1632                                               --   under name @n@.
1633  } deriving (Eq)
1634instance Outputable ModRenaming where
1635    ppr (ModRenaming b rns) = ppr b <+> parens (ppr rns)
1636
1637-- | Flags for manipulating the set of non-broken packages.
1638newtype IgnorePackageFlag = IgnorePackage String -- ^ @-ignore-package@
1639  deriving (Eq)
1640
1641-- | Flags for manipulating package trust.
1642data TrustFlag
1643  = TrustPackage    String -- ^ @-trust@
1644  | DistrustPackage String -- ^ @-distrust@
1645  deriving (Eq)
1646
1647-- | Flags for manipulating packages visibility.
1648data PackageFlag
1649  = ExposePackage   String PackageArg ModRenaming -- ^ @-package@, @-package-id@
1650  | HidePackage     String -- ^ @-hide-package@
1651  deriving (Eq) -- NB: equality instance is used by packageFlagsChanged
1652
1653data PackageDBFlag
1654  = PackageDB PkgConfRef
1655  | NoUserPackageDB
1656  | NoGlobalPackageDB
1657  | ClearPackageDBs
1658  deriving (Eq)
1659
1660packageFlagsChanged :: DynFlags -> DynFlags -> Bool
1661packageFlagsChanged idflags1 idflags0 =
1662  packageFlags idflags1 /= packageFlags idflags0 ||
1663  ignorePackageFlags idflags1 /= ignorePackageFlags idflags0 ||
1664  pluginPackageFlags idflags1 /= pluginPackageFlags idflags0 ||
1665  trustFlags idflags1 /= trustFlags idflags0 ||
1666  packageDBFlags idflags1 /= packageDBFlags idflags0 ||
1667  packageGFlags idflags1 /= packageGFlags idflags0
1668 where
1669   packageGFlags dflags = map (`gopt` dflags)
1670     [ Opt_HideAllPackages
1671     , Opt_HideAllPluginPackages
1672     , Opt_AutoLinkPackages ]
1673
1674instance Outputable PackageFlag where
1675    ppr (ExposePackage n arg rn) = text n <> braces (ppr arg <+> ppr rn)
1676    ppr (HidePackage str) = text "-hide-package" <+> text str
1677
1678-- | The 'HscTarget' value corresponding to the default way to create
1679-- object files on the current platform.
1680
1681defaultHscTarget :: Platform -> PlatformMisc -> HscTarget
1682defaultHscTarget platform pMisc
1683  | platformUnregisterised platform = HscC
1684  | platformMisc_ghcWithNativeCodeGen pMisc = HscAsm
1685  | otherwise = HscLlvm
1686
1687defaultObjectTarget :: DynFlags -> HscTarget
1688defaultObjectTarget dflags = defaultHscTarget
1689  (targetPlatform dflags)
1690  (platformMisc dflags)
1691
1692data DynLibLoader
1693  = Deployable
1694  | SystemDependent
1695  deriving Eq
1696
1697data RtsOptsEnabled
1698  = RtsOptsNone | RtsOptsIgnore | RtsOptsIgnoreAll | RtsOptsSafeOnly
1699  | RtsOptsAll
1700  deriving (Show)
1701
1702shouldUseColor :: DynFlags -> Bool
1703shouldUseColor dflags = overrideWith (canUseColor dflags) (useColor dflags)
1704
1705shouldUseHexWordLiterals :: DynFlags -> Bool
1706shouldUseHexWordLiterals dflags =
1707  Opt_HexWordLiterals `EnumSet.member` generalFlags dflags
1708
1709-- | Are we building with @-fPIE@ or @-fPIC@ enabled?
1710positionIndependent :: DynFlags -> Bool
1711positionIndependent dflags = gopt Opt_PIC dflags || gopt Opt_PIE dflags
1712
1713-----------------------------------------------------------------------------
1714-- Ways
1715
1716-- The central concept of a "way" is that all objects in a given
1717-- program must be compiled in the same "way".  Certain options change
1718-- parameters of the virtual machine, eg. profiling adds an extra word
1719-- to the object header, so profiling objects cannot be linked with
1720-- non-profiling objects.
1721
1722-- After parsing the command-line options, we determine which "way" we
1723-- are building - this might be a combination way, eg. profiling+threaded.
1724
1725-- We then find the "build-tag" associated with this way, and this
1726-- becomes the suffix used to find .hi files and libraries used in
1727-- this compilation.
1728
1729data Way
1730  = WayCustom String -- for GHC API clients building custom variants
1731  | WayThreaded
1732  | WayDebug
1733  | WayProf
1734  | WayEventLog
1735  | WayDyn
1736  deriving (Eq, Ord, Show)
1737
1738allowed_combination :: [Way] -> Bool
1739allowed_combination way = and [ x `allowedWith` y
1740                              | x <- way, y <- way, x < y ]
1741  where
1742        -- Note ordering in these tests: the left argument is
1743        -- <= the right argument, according to the Ord instance
1744        -- on Way above.
1745
1746        -- dyn is allowed with everything
1747        _ `allowedWith` WayDyn                  = True
1748        WayDyn `allowedWith` _                  = True
1749
1750        -- debug is allowed with everything
1751        _ `allowedWith` WayDebug                = True
1752        WayDebug `allowedWith` _                = True
1753
1754        (WayCustom {}) `allowedWith` _          = True
1755        WayThreaded `allowedWith` WayProf       = True
1756        WayThreaded `allowedWith` WayEventLog   = True
1757        WayProf     `allowedWith` WayEventLog   = True
1758        _ `allowedWith` _                       = False
1759
1760mkBuildTag :: [Way] -> String
1761mkBuildTag ways = concat (intersperse "_" (map wayTag ways))
1762
1763wayTag :: Way -> String
1764wayTag (WayCustom xs) = xs
1765wayTag WayThreaded = "thr"
1766wayTag WayDebug    = "debug"
1767wayTag WayDyn      = "dyn"
1768wayTag WayProf     = "p"
1769wayTag WayEventLog = "l"
1770
1771wayRTSOnly :: Way -> Bool
1772wayRTSOnly (WayCustom {}) = False
1773wayRTSOnly WayThreaded = True
1774wayRTSOnly WayDebug    = True
1775wayRTSOnly WayDyn      = False
1776wayRTSOnly WayProf     = False
1777wayRTSOnly WayEventLog = True
1778
1779wayDesc :: Way -> String
1780wayDesc (WayCustom xs) = xs
1781wayDesc WayThreaded = "Threaded"
1782wayDesc WayDebug    = "Debug"
1783wayDesc WayDyn      = "Dynamic"
1784wayDesc WayProf     = "Profiling"
1785wayDesc WayEventLog = "RTS Event Logging"
1786
1787-- Turn these flags on when enabling this way
1788wayGeneralFlags :: Platform -> Way -> [GeneralFlag]
1789wayGeneralFlags _ (WayCustom {}) = []
1790wayGeneralFlags _ WayThreaded = []
1791wayGeneralFlags _ WayDebug    = []
1792wayGeneralFlags _ WayDyn      = [Opt_PIC, Opt_ExternalDynamicRefs]
1793    -- We could get away without adding -fPIC when compiling the
1794    -- modules of a program that is to be linked with -dynamic; the
1795    -- program itself does not need to be position-independent, only
1796    -- the libraries need to be.  HOWEVER, GHCi links objects into a
1797    -- .so before loading the .so using the system linker.  Since only
1798    -- PIC objects can be linked into a .so, we have to compile even
1799    -- modules of the main program with -fPIC when using -dynamic.
1800wayGeneralFlags _ WayProf     = [Opt_SccProfilingOn]
1801wayGeneralFlags _ WayEventLog = []
1802
1803-- Turn these flags off when enabling this way
1804wayUnsetGeneralFlags :: Platform -> Way -> [GeneralFlag]
1805wayUnsetGeneralFlags _ (WayCustom {}) = []
1806wayUnsetGeneralFlags _ WayThreaded = []
1807wayUnsetGeneralFlags _ WayDebug    = []
1808wayUnsetGeneralFlags _ WayDyn      = [-- There's no point splitting
1809                                      -- when we're going to be dynamically
1810                                      -- linking. Plus it breaks compilation
1811                                      -- on OSX x86.
1812                                      Opt_SplitSections]
1813wayUnsetGeneralFlags _ WayProf     = []
1814wayUnsetGeneralFlags _ WayEventLog = []
1815
1816wayOptc :: Platform -> Way -> [String]
1817wayOptc _ (WayCustom {}) = []
1818wayOptc platform WayThreaded = case platformOS platform of
1819                               OSOpenBSD -> ["-pthread"]
1820                               OSNetBSD  -> ["-pthread"]
1821                               _         -> []
1822wayOptc _ WayDebug      = []
1823wayOptc _ WayDyn        = []
1824wayOptc _ WayProf       = ["-DPROFILING"]
1825wayOptc _ WayEventLog   = ["-DTRACING"]
1826
1827wayOptl :: Platform -> Way -> [String]
1828wayOptl _ (WayCustom {}) = []
1829wayOptl platform WayThreaded =
1830        case platformOS platform of
1831        -- N.B. FreeBSD cc throws a warning if we pass -pthread without
1832        -- actually using any pthread symbols.
1833        OSFreeBSD  -> ["-pthread", "-Wno-unused-command-line-argument"]
1834        OSOpenBSD  -> ["-pthread"]
1835        OSNetBSD   -> ["-pthread"]
1836        _          -> []
1837wayOptl _ WayDebug      = []
1838wayOptl _ WayDyn        = []
1839wayOptl _ WayProf       = []
1840wayOptl _ WayEventLog   = []
1841
1842wayOptP :: Platform -> Way -> [String]
1843wayOptP _ (WayCustom {}) = []
1844wayOptP _ WayThreaded = []
1845wayOptP _ WayDebug    = []
1846wayOptP _ WayDyn      = []
1847wayOptP _ WayProf     = ["-DPROFILING"]
1848wayOptP _ WayEventLog = ["-DTRACING"]
1849
1850whenGeneratingDynamicToo :: MonadIO m => DynFlags -> m () -> m ()
1851whenGeneratingDynamicToo dflags f = ifGeneratingDynamicToo dflags f (return ())
1852
1853ifGeneratingDynamicToo :: MonadIO m => DynFlags -> m a -> m a -> m a
1854ifGeneratingDynamicToo dflags f g = generateDynamicTooConditional dflags f g g
1855
1856whenCannotGenerateDynamicToo :: MonadIO m => DynFlags -> m () -> m ()
1857whenCannotGenerateDynamicToo dflags f
1858    = ifCannotGenerateDynamicToo dflags f (return ())
1859
1860ifCannotGenerateDynamicToo :: MonadIO m => DynFlags -> m a -> m a -> m a
1861ifCannotGenerateDynamicToo dflags f g
1862    = generateDynamicTooConditional dflags g f g
1863
1864generateDynamicTooConditional :: MonadIO m
1865                              => DynFlags -> m a -> m a -> m a -> m a
1866generateDynamicTooConditional dflags canGen cannotGen notTryingToGen
1867    = if gopt Opt_BuildDynamicToo dflags
1868      then do let ref = canGenerateDynamicToo dflags
1869              b <- liftIO $ readIORef ref
1870              if b then canGen else cannotGen
1871      else notTryingToGen
1872
1873dynamicTooMkDynamicDynFlags :: DynFlags -> DynFlags
1874dynamicTooMkDynamicDynFlags dflags0
1875    = let dflags1 = addWay' WayDyn dflags0
1876          dflags2 = dflags1 {
1877                        outputFile = dynOutputFile dflags1,
1878                        hiSuf = dynHiSuf dflags1,
1879                        objectSuf = dynObjectSuf dflags1
1880                    }
1881          dflags3 = updateWays dflags2
1882          dflags4 = gopt_unset dflags3 Opt_BuildDynamicToo
1883      in dflags4
1884
1885-- | Compute the path of the dynamic object corresponding to an object file.
1886dynamicOutputFile :: DynFlags -> FilePath -> FilePath
1887dynamicOutputFile dflags outputFile = dynOut outputFile
1888  where
1889    dynOut = flip addExtension (dynObjectSuf dflags) . dropExtension
1890
1891-----------------------------------------------------------------------------
1892
1893-- | Used by 'GHC.runGhc' to partially initialize a new 'DynFlags' value
1894initDynFlags :: DynFlags -> IO DynFlags
1895initDynFlags dflags = do
1896 let -- We can't build with dynamic-too on Windows, as labels before
1897     -- the fork point are different depending on whether we are
1898     -- building dynamically or not.
1899     platformCanGenerateDynamicToo
1900         = platformOS (targetPlatform dflags) /= OSMinGW32
1901 refCanGenerateDynamicToo <- newIORef platformCanGenerateDynamicToo
1902 refNextTempSuffix <- newIORef 0
1903 refFilesToClean <- newIORef emptyFilesToClean
1904 refDirsToClean <- newIORef Map.empty
1905 refGeneratedDumps <- newIORef Set.empty
1906 refRtldInfo <- newIORef Nothing
1907 refRtccInfo <- newIORef Nothing
1908 wrapperNum <- newIORef emptyModuleEnv
1909 canUseUnicode <- do let enc = localeEncoding
1910                         str = "‘’"
1911                     (withCString enc str $ \cstr ->
1912                          do str' <- peekCString enc cstr
1913                             return (str == str'))
1914                         `catchIOError` \_ -> return False
1915 maybeGhcNoUnicodeEnv <- lookupEnv "GHC_NO_UNICODE"
1916 let adjustNoUnicode (Just _) = False
1917     adjustNoUnicode Nothing = True
1918 let useUnicode' = (adjustNoUnicode maybeGhcNoUnicodeEnv) && canUseUnicode
1919 canUseColor <- stderrSupportsAnsiColors
1920 maybeGhcColorsEnv  <- lookupEnv "GHC_COLORS"
1921 maybeGhcColoursEnv <- lookupEnv "GHC_COLOURS"
1922 let adjustCols (Just env) = Col.parseScheme env
1923     adjustCols Nothing    = id
1924 let (useColor', colScheme') =
1925       (adjustCols maybeGhcColoursEnv . adjustCols maybeGhcColorsEnv)
1926       (useColor dflags, colScheme dflags)
1927 return dflags{
1928        canGenerateDynamicToo = refCanGenerateDynamicToo,
1929        nextTempSuffix = refNextTempSuffix,
1930        filesToClean   = refFilesToClean,
1931        dirsToClean    = refDirsToClean,
1932        generatedDumps = refGeneratedDumps,
1933        nextWrapperNum = wrapperNum,
1934        useUnicode    = useUnicode',
1935        useColor      = useColor',
1936        canUseColor   = canUseColor,
1937        colScheme     = colScheme',
1938        rtldInfo      = refRtldInfo,
1939        rtccInfo      = refRtccInfo
1940        }
1941
1942-- | The normal 'DynFlags'. Note that they are not suitable for use in this form
1943-- and must be fully initialized by 'GHC.runGhc' first.
1944defaultDynFlags :: Settings -> LlvmConfig -> DynFlags
1945defaultDynFlags mySettings llvmConfig =
1946-- See Note [Updating flag description in the User's Guide]
1947     DynFlags {
1948        ghcMode                 = CompManager,
1949        ghcLink                 = LinkBinary,
1950        hscTarget               = defaultHscTarget (sTargetPlatform mySettings) (sPlatformMisc mySettings),
1951        integerLibrary          = sIntegerLibraryType mySettings,
1952        verbosity               = 0,
1953        optLevel                = 0,
1954        debugLevel              = 0,
1955        simplPhases             = 2,
1956        maxSimplIterations      = 4,
1957        ruleCheck               = Nothing,
1958        inlineCheck             = Nothing,
1959        binBlobThreshold        = 500000, -- 500K is a good default (see #16190)
1960        maxRelevantBinds        = Just 6,
1961        maxValidHoleFits   = Just 6,
1962        maxRefHoleFits     = Just 6,
1963        refLevelHoleFits   = Nothing,
1964        maxUncoveredPatterns    = 4,
1965        maxPmCheckModels        = 100,
1966        simplTickFactor         = 100,
1967        specConstrThreshold     = Just 2000,
1968        specConstrCount         = Just 3,
1969        specConstrRecursive     = 3,
1970        liberateCaseThreshold   = Just 2000,
1971        floatLamArgs            = Just 0, -- Default: float only if no fvs
1972        liftLamsRecArgs         = Just 5, -- Default: the number of available argument hardware registers on x86_64
1973        liftLamsNonRecArgs      = Just 5, -- Default: the number of available argument hardware registers on x86_64
1974        liftLamsKnown           = False,  -- Default: don't turn known calls into unknown ones
1975        cmmProcAlignment        = Nothing,
1976
1977        historySize             = 20,
1978        strictnessBefore        = [],
1979
1980        parMakeCount            = Just 1,
1981
1982        enableTimeStats         = False,
1983        ghcHeapSize             = Nothing,
1984
1985        importPaths             = ["."],
1986        mainModIs               = mAIN,
1987        mainFunIs               = Nothing,
1988        reductionDepth          = treatZeroAsInf mAX_REDUCTION_DEPTH,
1989        solverIterations        = treatZeroAsInf mAX_SOLVER_ITERATIONS,
1990
1991        thisInstalledUnitId     = toInstalledUnitId mainUnitId,
1992        thisUnitIdInsts_        = Nothing,
1993        thisComponentId_        = Nothing,
1994
1995        objectDir               = Nothing,
1996        dylibInstallName        = Nothing,
1997        hiDir                   = Nothing,
1998        hieDir                  = Nothing,
1999        stubDir                 = Nothing,
2000        dumpDir                 = Nothing,
2001
2002        objectSuf               = phaseInputExt StopLn,
2003        hcSuf                   = phaseInputExt HCc,
2004        hiSuf                   = "hi",
2005        hieSuf                  = "hie",
2006
2007        canGenerateDynamicToo   = panic "defaultDynFlags: No canGenerateDynamicToo",
2008        dynObjectSuf            = "dyn_" ++ phaseInputExt StopLn,
2009        dynHiSuf                = "dyn_hi",
2010
2011        pluginModNames          = [],
2012        pluginModNameOpts       = [],
2013        frontendPluginOpts      = [],
2014        cachedPlugins           = [],
2015        staticPlugins           = [],
2016        hooks                   = emptyHooks,
2017
2018        outputFile              = Nothing,
2019        dynOutputFile           = Nothing,
2020        outputHi                = Nothing,
2021        dynLibLoader            = SystemDependent,
2022        dumpPrefix              = Nothing,
2023        dumpPrefixForce         = Nothing,
2024        ldInputs                = [],
2025        includePaths            = IncludeSpecs [] [],
2026        libraryPaths            = [],
2027        frameworkPaths          = [],
2028        cmdlineFrameworks       = [],
2029        rtsOpts                 = Nothing,
2030        rtsOptsEnabled          = RtsOptsSafeOnly,
2031        rtsOptsSuggestions      = True,
2032
2033        hpcDir                  = ".hpc",
2034
2035        packageDBFlags          = [],
2036        packageFlags            = [],
2037        pluginPackageFlags      = [],
2038        ignorePackageFlags      = [],
2039        trustFlags              = [],
2040        packageEnv              = Nothing,
2041        pkgDatabase             = Nothing,
2042        -- This gets filled in with GHC.setSessionDynFlags
2043        pkgState                = emptyPackageState,
2044        ways                    = defaultWays mySettings,
2045        buildTag                = mkBuildTag (defaultWays mySettings),
2046        splitInfo               = Nothing,
2047
2048        ghcNameVersion = sGhcNameVersion mySettings,
2049        fileSettings = sFileSettings mySettings,
2050        toolSettings = sToolSettings mySettings,
2051        targetPlatform = sTargetPlatform mySettings,
2052        platformMisc = sPlatformMisc mySettings,
2053        platformConstants = sPlatformConstants mySettings,
2054        rawSettings = sRawSettings mySettings,
2055
2056        -- See Note [LLVM configuration].
2057        llvmConfig              = llvmConfig,
2058
2059        -- ghc -M values
2060        depMakefile       = "Makefile",
2061        depIncludePkgDeps = False,
2062        depIncludeCppDeps = False,
2063        depExcludeMods    = [],
2064        depSuffixes       = [],
2065        -- end of ghc -M values
2066        nextTempSuffix = panic "defaultDynFlags: No nextTempSuffix",
2067        filesToClean   = panic "defaultDynFlags: No filesToClean",
2068        dirsToClean    = panic "defaultDynFlags: No dirsToClean",
2069        generatedDumps = panic "defaultDynFlags: No generatedDumps",
2070        ghcVersionFile = Nothing,
2071        haddockOptions = Nothing,
2072        dumpFlags = EnumSet.empty,
2073        generalFlags = EnumSet.fromList (defaultFlags mySettings),
2074        warningFlags = EnumSet.fromList standardWarnings,
2075        fatalWarningFlags = EnumSet.empty,
2076        ghciScripts = [],
2077        language = Nothing,
2078        safeHaskell = Sf_None,
2079        safeInfer   = True,
2080        safeInferred = True,
2081        thOnLoc = noSrcSpan,
2082        newDerivOnLoc = noSrcSpan,
2083        overlapInstLoc = noSrcSpan,
2084        incoherentOnLoc = noSrcSpan,
2085        pkgTrustOnLoc = noSrcSpan,
2086        warnSafeOnLoc = noSrcSpan,
2087        warnUnsafeOnLoc = noSrcSpan,
2088        trustworthyOnLoc = noSrcSpan,
2089        extensions = [],
2090        extensionFlags = flattenExtensionFlags Nothing [],
2091
2092        -- The ufCreationThreshold threshold must be reasonably high to
2093        -- take account of possible discounts.
2094        -- E.g. 450 is not enough in 'fulsom' for Interval.sqr to inline
2095        -- into Csg.calc (The unfolding for sqr never makes it into the
2096        -- interface file.)
2097        ufCreationThreshold = 750,
2098        ufUseThreshold      = 60,
2099        ufFunAppDiscount    = 60,
2100        -- Be fairly keen to inline a function if that means
2101        -- we'll be able to pick the right method from a dictionary
2102        ufDictDiscount      = 30,
2103        ufKeenessFactor     = 1.5,
2104        ufDearOp            = 40,
2105        ufVeryAggressive    = False,
2106
2107        maxWorkerArgs = 10,
2108
2109        ghciHistSize = 50, -- keep a log of length 50 by default
2110
2111        -- Logging
2112
2113        log_action = defaultLogAction,
2114
2115        flushOut = defaultFlushOut,
2116        flushErr = defaultFlushErr,
2117        pprUserLength = 5,
2118        pprCols = 100,
2119        useUnicode = False,
2120        useColor = Auto,
2121        canUseColor = False,
2122        colScheme = Col.defaultScheme,
2123        profAuto = NoProfAuto,
2124        interactivePrint = Nothing,
2125        nextWrapperNum = panic "defaultDynFlags: No nextWrapperNum",
2126        sseVersion = Nothing,
2127        bmiVersion = Nothing,
2128        avx = False,
2129        avx2 = False,
2130        avx512cd = False,
2131        avx512er = False,
2132        avx512f = False,
2133        avx512pf = False,
2134        rtldInfo = panic "defaultDynFlags: no rtldInfo",
2135        rtccInfo = panic "defaultDynFlags: no rtccInfo",
2136
2137        maxInlineAllocSize = 128,
2138        maxInlineMemcpyInsns = 32,
2139        maxInlineMemsetInsns = 32,
2140
2141        initialUnique = 0,
2142        uniqueIncrement = 1,
2143
2144        reverseErrors = False,
2145        maxErrors     = Nothing,
2146        cfgWeightInfo = defaultCfgWeights
2147      }
2148
2149defaultWays :: Settings -> [Way]
2150defaultWays settings = if pc_DYNAMIC_BY_DEFAULT (sPlatformConstants settings)
2151                       then [WayDyn]
2152                       else []
2153
2154interpWays :: [Way]
2155interpWays
2156  | dynamicGhc = [WayDyn]
2157  | rtsIsProfiled = [WayProf]
2158  | otherwise = []
2159
2160interpreterProfiled :: DynFlags -> Bool
2161interpreterProfiled dflags
2162  | gopt Opt_ExternalInterpreter dflags = gopt Opt_SccProfilingOn dflags
2163  | otherwise = rtsIsProfiled
2164
2165interpreterDynamic :: DynFlags -> Bool
2166interpreterDynamic dflags
2167  | gopt Opt_ExternalInterpreter dflags = WayDyn `elem` ways dflags
2168  | otherwise = dynamicGhc
2169
2170--------------------------------------------------------------------------
2171--
2172-- Note [JSON Error Messages]
2173--
2174-- When the user requests the compiler output to be dumped as json
2175-- we used to collect them all in an IORef and then print them at the end.
2176-- This doesn't work very well with GHCi. (See #14078) So instead we now
2177-- use the simpler method of just outputting a JSON document inplace to
2178-- stdout.
2179--
2180-- Before the compiler calls log_action, it has already turned the `ErrMsg`
2181-- into a formatted message. This means that we lose some possible
2182-- information to provide to the user but refactoring log_action is quite
2183-- invasive as it is called in many places. So, for now I left it alone
2184-- and we can refine its behaviour as users request different output.
2185
2186type FatalMessager = String -> IO ()
2187
2188type LogAction = DynFlags
2189              -> WarnReason
2190              -> Severity
2191              -> SrcSpan
2192              -> PprStyle
2193              -> MsgDoc
2194              -> IO ()
2195
2196defaultFatalMessager :: FatalMessager
2197defaultFatalMessager = hPutStrLn stderr
2198
2199
2200-- See Note [JSON Error Messages]
2201--
2202jsonLogAction :: LogAction
2203jsonLogAction dflags reason severity srcSpan _style msg
2204  = do
2205    defaultLogActionHPutStrDoc dflags stdout (doc $$ text "")
2206                               (mkCodeStyle CStyle)
2207    where
2208      doc = renderJSON $
2209              JSObject [ ( "span", json srcSpan )
2210                       , ( "doc" , JSString (showSDoc dflags msg) )
2211                       , ( "severity", json severity )
2212                       , ( "reason" ,   json reason )
2213                       ]
2214
2215
2216defaultLogAction :: LogAction
2217defaultLogAction dflags reason severity srcSpan style msg
2218    = case severity of
2219      SevOutput      -> printOut msg style
2220      SevDump        -> printOut (msg $$ blankLine) style
2221      SevInteractive -> putStrSDoc msg style
2222      SevInfo        -> printErrs msg style
2223      SevFatal       -> printErrs msg style
2224      SevWarning     -> printWarns
2225      SevError       -> printWarns
2226    where
2227      printOut   = defaultLogActionHPrintDoc  dflags stdout
2228      printErrs  = defaultLogActionHPrintDoc  dflags stderr
2229      putStrSDoc = defaultLogActionHPutStrDoc dflags stdout
2230      -- Pretty print the warning flag, if any (#10752)
2231      message = mkLocMessageAnn flagMsg severity srcSpan msg
2232
2233      printWarns = do
2234        hPutChar stderr '\n'
2235        caretDiagnostic <-
2236            if gopt Opt_DiagnosticsShowCaret dflags
2237            then getCaretDiagnostic severity srcSpan
2238            else pure empty
2239        printErrs (message $+$ caretDiagnostic)
2240            (setStyleColoured True style)
2241        -- careful (#2302): printErrs prints in UTF-8,
2242        -- whereas converting to string first and using
2243        -- hPutStr would just emit the low 8 bits of
2244        -- each unicode char.
2245
2246      flagMsg =
2247        case reason of
2248          NoReason -> Nothing
2249          Reason wflag -> do
2250            spec <- flagSpecOf wflag
2251            return ("-W" ++ flagSpecName spec ++ warnFlagGrp wflag)
2252          ErrReason Nothing ->
2253            return "-Werror"
2254          ErrReason (Just wflag) -> do
2255            spec <- flagSpecOf wflag
2256            return $
2257              "-W" ++ flagSpecName spec ++ warnFlagGrp wflag ++
2258              ", -Werror=" ++ flagSpecName spec
2259
2260      warnFlagGrp flag
2261          | gopt Opt_ShowWarnGroups dflags =
2262                case smallestGroups flag of
2263                    [] -> ""
2264                    groups -> " (in " ++ intercalate ", " (map ("-W"++) groups) ++ ")"
2265          | otherwise = ""
2266
2267-- | Like 'defaultLogActionHPutStrDoc' but appends an extra newline.
2268defaultLogActionHPrintDoc :: DynFlags -> Handle -> SDoc -> PprStyle -> IO ()
2269defaultLogActionHPrintDoc dflags h d sty
2270 = defaultLogActionHPutStrDoc dflags h (d $$ text "") sty
2271
2272defaultLogActionHPutStrDoc :: DynFlags -> Handle -> SDoc -> PprStyle -> IO ()
2273defaultLogActionHPutStrDoc dflags h d sty
2274  -- Don't add a newline at the end, so that successive
2275  -- calls to this log-action can output all on the same line
2276  = printSDoc Pretty.PageMode dflags h sty d
2277
2278newtype FlushOut = FlushOut (IO ())
2279
2280defaultFlushOut :: FlushOut
2281defaultFlushOut = FlushOut $ hFlush stdout
2282
2283newtype FlushErr = FlushErr (IO ())
2284
2285defaultFlushErr :: FlushErr
2286defaultFlushErr = FlushErr $ hFlush stderr
2287
2288{-
2289Note [Verbosity levels]
2290~~~~~~~~~~~~~~~~~~~~~~~
2291    0   |   print errors & warnings only
2292    1   |   minimal verbosity: print "compiling M ... done." for each module.
2293    2   |   equivalent to -dshow-passes
2294    3   |   equivalent to existing "ghc -v"
2295    4   |   "ghc -v -ddump-most"
2296    5   |   "ghc -v -ddump-all"
2297-}
2298
2299data OnOff a = On a
2300             | Off a
2301  deriving (Eq, Show)
2302
2303instance Outputable a => Outputable (OnOff a) where
2304  ppr (On x)  = text "On" <+> ppr x
2305  ppr (Off x) = text "Off" <+> ppr x
2306
2307-- OnOffs accumulate in reverse order, so we use foldr in order to
2308-- process them in the right order
2309flattenExtensionFlags :: Maybe Language -> [OnOff LangExt.Extension] -> EnumSet LangExt.Extension
2310flattenExtensionFlags ml = foldr f defaultExtensionFlags
2311    where f (On f)  flags = EnumSet.insert f flags
2312          f (Off f) flags = EnumSet.delete f flags
2313          defaultExtensionFlags = EnumSet.fromList (languageExtensions ml)
2314
2315-- | The language extensions implied by the various language variants.
2316-- When updating this be sure to update the flag documentation in
2317-- @docs/users-guide/glasgow_exts.rst@.
2318languageExtensions :: Maybe Language -> [LangExt.Extension]
2319
2320languageExtensions Nothing
2321    -- Nothing => the default case
2322    = LangExt.NondecreasingIndentation -- This has been on by default for some time
2323    : delete LangExt.DatatypeContexts  -- The Haskell' committee decided to
2324                                       -- remove datatype contexts from the
2325                                       -- language:
2326   -- http://www.haskell.org/pipermail/haskell-prime/2011-January/003335.html
2327      (languageExtensions (Just Haskell2010))
2328
2329   -- NB: MonoPatBinds is no longer the default
2330
2331languageExtensions (Just Haskell98)
2332    = [LangExt.ImplicitPrelude,
2333       -- See Note [When is StarIsType enabled]
2334       LangExt.StarIsType,
2335       LangExt.CUSKs,
2336       LangExt.MonomorphismRestriction,
2337       LangExt.NPlusKPatterns,
2338       LangExt.DatatypeContexts,
2339       LangExt.TraditionalRecordSyntax,
2340       LangExt.NondecreasingIndentation
2341           -- strictly speaking non-standard, but we always had this
2342           -- on implicitly before the option was added in 7.1, and
2343           -- turning it off breaks code, so we're keeping it on for
2344           -- backwards compatibility.  Cabal uses -XHaskell98 by
2345           -- default unless you specify another language.
2346      ]
2347
2348languageExtensions (Just Haskell2010)
2349    = [LangExt.ImplicitPrelude,
2350       -- See Note [When is StarIsType enabled]
2351       LangExt.StarIsType,
2352       LangExt.CUSKs,
2353       LangExt.MonomorphismRestriction,
2354       LangExt.DatatypeContexts,
2355       LangExt.TraditionalRecordSyntax,
2356       LangExt.EmptyDataDecls,
2357       LangExt.ForeignFunctionInterface,
2358       LangExt.PatternGuards,
2359       LangExt.DoAndIfThenElse,
2360       LangExt.RelaxedPolyRec]
2361
2362hasPprDebug :: DynFlags -> Bool
2363hasPprDebug = dopt Opt_D_ppr_debug
2364
2365hasNoDebugOutput :: DynFlags -> Bool
2366hasNoDebugOutput = dopt Opt_D_no_debug_output
2367
2368hasNoStateHack :: DynFlags -> Bool
2369hasNoStateHack = gopt Opt_G_NoStateHack
2370
2371hasNoOptCoercion :: DynFlags -> Bool
2372hasNoOptCoercion = gopt Opt_G_NoOptCoercion
2373
2374
2375-- | Test whether a 'DumpFlag' is set
2376dopt :: DumpFlag -> DynFlags -> Bool
2377dopt f dflags = (f `EnumSet.member` dumpFlags dflags)
2378             || (verbosity dflags >= 4 && enableIfVerbose f)
2379    where enableIfVerbose Opt_D_dump_tc_trace               = False
2380          enableIfVerbose Opt_D_dump_rn_trace               = False
2381          enableIfVerbose Opt_D_dump_cs_trace               = False
2382          enableIfVerbose Opt_D_dump_if_trace               = False
2383          enableIfVerbose Opt_D_dump_vt_trace               = False
2384          enableIfVerbose Opt_D_dump_tc                     = False
2385          enableIfVerbose Opt_D_dump_rn                     = False
2386          enableIfVerbose Opt_D_dump_rn_stats               = False
2387          enableIfVerbose Opt_D_dump_hi_diffs               = False
2388          enableIfVerbose Opt_D_verbose_core2core           = False
2389          enableIfVerbose Opt_D_verbose_stg2stg             = False
2390          enableIfVerbose Opt_D_dump_splices                = False
2391          enableIfVerbose Opt_D_th_dec_file                 = False
2392          enableIfVerbose Opt_D_dump_rule_firings           = False
2393          enableIfVerbose Opt_D_dump_rule_rewrites          = False
2394          enableIfVerbose Opt_D_dump_simpl_trace            = False
2395          enableIfVerbose Opt_D_dump_rtti                   = False
2396          enableIfVerbose Opt_D_dump_inlinings              = False
2397          enableIfVerbose Opt_D_dump_core_stats             = False
2398          enableIfVerbose Opt_D_dump_asm_stats              = False
2399          enableIfVerbose Opt_D_dump_types                  = False
2400          enableIfVerbose Opt_D_dump_simpl_iterations       = False
2401          enableIfVerbose Opt_D_dump_ticked                 = False
2402          enableIfVerbose Opt_D_dump_view_pattern_commoning = False
2403          enableIfVerbose Opt_D_dump_mod_cycles             = False
2404          enableIfVerbose Opt_D_dump_mod_map                = False
2405          enableIfVerbose Opt_D_dump_ec_trace               = False
2406          enableIfVerbose _                                 = True
2407
2408-- | Set a 'DumpFlag'
2409dopt_set :: DynFlags -> DumpFlag -> DynFlags
2410dopt_set dfs f = dfs{ dumpFlags = EnumSet.insert f (dumpFlags dfs) }
2411
2412-- | Unset a 'DumpFlag'
2413dopt_unset :: DynFlags -> DumpFlag -> DynFlags
2414dopt_unset dfs f = dfs{ dumpFlags = EnumSet.delete f (dumpFlags dfs) }
2415
2416-- | Test whether a 'GeneralFlag' is set
2417gopt :: GeneralFlag -> DynFlags -> Bool
2418gopt f dflags  = f `EnumSet.member` generalFlags dflags
2419
2420-- | Set a 'GeneralFlag'
2421gopt_set :: DynFlags -> GeneralFlag -> DynFlags
2422gopt_set dfs f = dfs{ generalFlags = EnumSet.insert f (generalFlags dfs) }
2423
2424-- | Unset a 'GeneralFlag'
2425gopt_unset :: DynFlags -> GeneralFlag -> DynFlags
2426gopt_unset dfs f = dfs{ generalFlags = EnumSet.delete f (generalFlags dfs) }
2427
2428-- | Test whether a 'WarningFlag' is set
2429wopt :: WarningFlag -> DynFlags -> Bool
2430wopt f dflags  = f `EnumSet.member` warningFlags dflags
2431
2432-- | Set a 'WarningFlag'
2433wopt_set :: DynFlags -> WarningFlag -> DynFlags
2434wopt_set dfs f = dfs{ warningFlags = EnumSet.insert f (warningFlags dfs) }
2435
2436-- | Unset a 'WarningFlag'
2437wopt_unset :: DynFlags -> WarningFlag -> DynFlags
2438wopt_unset dfs f = dfs{ warningFlags = EnumSet.delete f (warningFlags dfs) }
2439
2440-- | Test whether a 'WarningFlag' is set as fatal
2441wopt_fatal :: WarningFlag -> DynFlags -> Bool
2442wopt_fatal f dflags = f `EnumSet.member` fatalWarningFlags dflags
2443
2444-- | Mark a 'WarningFlag' as fatal (do not set the flag)
2445wopt_set_fatal :: DynFlags -> WarningFlag -> DynFlags
2446wopt_set_fatal dfs f
2447    = dfs { fatalWarningFlags = EnumSet.insert f (fatalWarningFlags dfs) }
2448
2449-- | Mark a 'WarningFlag' as not fatal
2450wopt_unset_fatal :: DynFlags -> WarningFlag -> DynFlags
2451wopt_unset_fatal dfs f
2452    = dfs { fatalWarningFlags = EnumSet.delete f (fatalWarningFlags dfs) }
2453
2454-- | Test whether a 'LangExt.Extension' is set
2455xopt :: LangExt.Extension -> DynFlags -> Bool
2456xopt f dflags = f `EnumSet.member` extensionFlags dflags
2457
2458-- | Set a 'LangExt.Extension'
2459xopt_set :: DynFlags -> LangExt.Extension -> DynFlags
2460xopt_set dfs f
2461    = let onoffs = On f : extensions dfs
2462      in dfs { extensions = onoffs,
2463               extensionFlags = flattenExtensionFlags (language dfs) onoffs }
2464
2465-- | Unset a 'LangExt.Extension'
2466xopt_unset :: DynFlags -> LangExt.Extension -> DynFlags
2467xopt_unset dfs f
2468    = let onoffs = Off f : extensions dfs
2469      in dfs { extensions = onoffs,
2470               extensionFlags = flattenExtensionFlags (language dfs) onoffs }
2471
2472-- | Set or unset a 'LangExt.Extension', unless it has been explicitly
2473--   set or unset before.
2474xopt_set_unlessExplSpec
2475        :: LangExt.Extension
2476        -> (DynFlags -> LangExt.Extension -> DynFlags)
2477        -> DynFlags -> DynFlags
2478xopt_set_unlessExplSpec ext setUnset dflags =
2479    let referedExts = stripOnOff <$> extensions dflags
2480        stripOnOff (On x)  = x
2481        stripOnOff (Off x) = x
2482    in
2483        if ext `elem` referedExts then dflags else setUnset dflags ext
2484
2485lang_set :: DynFlags -> Maybe Language -> DynFlags
2486lang_set dflags lang =
2487   dflags {
2488            language = lang,
2489            extensionFlags = flattenExtensionFlags lang (extensions dflags)
2490          }
2491
2492-- | An internal helper to check whether to use unicode syntax for output.
2493--
2494-- Note: You should very likely be using 'Outputable.unicodeSyntax' instead
2495-- of this function.
2496useUnicodeSyntax :: DynFlags -> Bool
2497useUnicodeSyntax = gopt Opt_PrintUnicodeSyntax
2498
2499useStarIsType :: DynFlags -> Bool
2500useStarIsType = xopt LangExt.StarIsType
2501
2502-- | Set the Haskell language standard to use
2503setLanguage :: Language -> DynP ()
2504setLanguage l = upd (`lang_set` Just l)
2505
2506-- | Some modules have dependencies on others through the DynFlags rather than textual imports
2507dynFlagDependencies :: DynFlags -> [ModuleName]
2508dynFlagDependencies = pluginModNames
2509
2510-- | Is the -fpackage-trust mode on
2511packageTrustOn :: DynFlags -> Bool
2512packageTrustOn = gopt Opt_PackageTrust
2513
2514-- | Is Safe Haskell on in some way (including inference mode)
2515safeHaskellOn :: DynFlags -> Bool
2516safeHaskellOn dflags = safeHaskellModeEnabled dflags || safeInferOn dflags
2517
2518safeHaskellModeEnabled :: DynFlags -> Bool
2519safeHaskellModeEnabled dflags = safeHaskell dflags `elem` [Sf_Unsafe, Sf_Trustworthy
2520                                                   , Sf_Safe ]
2521
2522
2523-- | Is the Safe Haskell safe language in use
2524safeLanguageOn :: DynFlags -> Bool
2525safeLanguageOn dflags = safeHaskell dflags == Sf_Safe
2526
2527-- | Is the Safe Haskell safe inference mode active
2528safeInferOn :: DynFlags -> Bool
2529safeInferOn = safeInfer
2530
2531-- | Test if Safe Imports are on in some form
2532safeImportsOn :: DynFlags -> Bool
2533safeImportsOn dflags = safeHaskell dflags == Sf_Unsafe ||
2534                       safeHaskell dflags == Sf_Trustworthy ||
2535                       safeHaskell dflags == Sf_Safe
2536
2537-- | Set a 'Safe Haskell' flag
2538setSafeHaskell :: SafeHaskellMode -> DynP ()
2539setSafeHaskell s = updM f
2540    where f dfs = do
2541              let sf = safeHaskell dfs
2542              safeM <- combineSafeFlags sf s
2543              case s of
2544                Sf_Safe -> return $ dfs { safeHaskell = safeM, safeInfer = False }
2545                -- leave safe inferrence on in Trustworthy mode so we can warn
2546                -- if it could have been inferred safe.
2547                Sf_Trustworthy -> do
2548                  l <- getCurLoc
2549                  return $ dfs { safeHaskell = safeM, trustworthyOnLoc = l }
2550                -- leave safe inference on in Unsafe mode as well.
2551                _ -> return $ dfs { safeHaskell = safeM }
2552
2553-- | Are all direct imports required to be safe for this Safe Haskell mode?
2554-- Direct imports are when the code explicitly imports a module
2555safeDirectImpsReq :: DynFlags -> Bool
2556safeDirectImpsReq d = safeLanguageOn d
2557
2558-- | Are all implicit imports required to be safe for this Safe Haskell mode?
2559-- Implicit imports are things in the prelude. e.g System.IO when print is used.
2560safeImplicitImpsReq :: DynFlags -> Bool
2561safeImplicitImpsReq d = safeLanguageOn d
2562
2563-- | Combine two Safe Haskell modes correctly. Used for dealing with multiple flags.
2564-- This makes Safe Haskell very much a monoid but for now I prefer this as I don't
2565-- want to export this functionality from the module but do want to export the
2566-- type constructors.
2567combineSafeFlags :: SafeHaskellMode -> SafeHaskellMode -> DynP SafeHaskellMode
2568combineSafeFlags a b | a == Sf_None         = return b
2569                     | b == Sf_None         = return a
2570                     | a == Sf_Ignore || b == Sf_Ignore = return Sf_Ignore
2571                     | a == b               = return a
2572                     | otherwise            = addErr errm >> pure a
2573    where errm = "Incompatible Safe Haskell flags! ("
2574                    ++ show a ++ ", " ++ show b ++ ")"
2575
2576-- | A list of unsafe flags under Safe Haskell. Tuple elements are:
2577--     * name of the flag
2578--     * function to get srcspan that enabled the flag
2579--     * function to test if the flag is on
2580--     * function to turn the flag off
2581unsafeFlags, unsafeFlagsForInfer
2582  :: [(String, DynFlags -> SrcSpan, DynFlags -> Bool, DynFlags -> DynFlags)]
2583unsafeFlags = [ ("-XGeneralizedNewtypeDeriving", newDerivOnLoc,
2584                    xopt LangExt.GeneralizedNewtypeDeriving,
2585                    flip xopt_unset LangExt.GeneralizedNewtypeDeriving)
2586              , ("-XTemplateHaskell", thOnLoc,
2587                    xopt LangExt.TemplateHaskell,
2588                    flip xopt_unset LangExt.TemplateHaskell)
2589              ]
2590unsafeFlagsForInfer = unsafeFlags
2591
2592
2593-- | Retrieve the options corresponding to a particular @opt_*@ field in the correct order
2594getOpts :: DynFlags             -- ^ 'DynFlags' to retrieve the options from
2595        -> (DynFlags -> [a])    -- ^ Relevant record accessor: one of the @opt_*@ accessors
2596        -> [a]                  -- ^ Correctly ordered extracted options
2597getOpts dflags opts = reverse (opts dflags)
2598        -- We add to the options from the front, so we need to reverse the list
2599
2600-- | Gets the verbosity flag for the current verbosity level. This is fed to
2601-- other tools, so GHC-specific verbosity flags like @-ddump-most@ are not included
2602getVerbFlags :: DynFlags -> [String]
2603getVerbFlags dflags
2604  | verbosity dflags >= 4 = ["-v"]
2605  | otherwise             = []
2606
2607setObjectDir, setHiDir, setHieDir, setStubDir, setDumpDir, setOutputDir,
2608         setDynObjectSuf, setDynHiSuf,
2609         setDylibInstallName,
2610         setObjectSuf, setHiSuf, setHieSuf, setHcSuf, parseDynLibLoaderMode,
2611         setPgmP, addOptl, addOptc, addOptcxx, addOptP,
2612         addCmdlineFramework, addHaddockOpts, addGhciScript,
2613         setInteractivePrint
2614   :: String -> DynFlags -> DynFlags
2615setOutputFile, setDynOutputFile, setOutputHi, setDumpPrefixForce
2616   :: Maybe String -> DynFlags -> DynFlags
2617
2618setObjectDir  f d = d { objectDir  = Just f}
2619setHiDir      f d = d { hiDir      = Just f}
2620setHieDir     f d = d { hieDir     = Just f}
2621setStubDir    f d = d { stubDir    = Just f
2622                      , includePaths = addGlobalInclude (includePaths d) [f] }
2623  -- -stubdir D adds an implicit -I D, so that gcc can find the _stub.h file
2624  -- \#included from the .hc file when compiling via C (i.e. unregisterised
2625  -- builds).
2626setDumpDir    f d = d { dumpDir    = Just f}
2627setOutputDir  f = setObjectDir f
2628                . setHieDir f
2629                . setHiDir f
2630                . setStubDir f
2631                . setDumpDir f
2632setDylibInstallName  f d = d { dylibInstallName = Just f}
2633
2634setObjectSuf    f d = d { objectSuf    = f}
2635setDynObjectSuf f d = d { dynObjectSuf = f}
2636setHiSuf        f d = d { hiSuf        = f}
2637setHieSuf       f d = d { hieSuf       = f}
2638setDynHiSuf     f d = d { dynHiSuf     = f}
2639setHcSuf        f d = d { hcSuf        = f}
2640
2641setOutputFile f d = d { outputFile = f}
2642setDynOutputFile f d = d { dynOutputFile = f}
2643setOutputHi   f d = d { outputHi   = f}
2644
2645setJsonLogAction :: DynFlags -> DynFlags
2646setJsonLogAction d = d { log_action = jsonLogAction }
2647
2648thisComponentId :: DynFlags -> ComponentId
2649thisComponentId dflags =
2650  case thisComponentId_ dflags of
2651    Just cid -> cid
2652    Nothing  ->
2653      case thisUnitIdInsts_ dflags of
2654        Just _  ->
2655          throwGhcException $ CmdLineError ("Use of -instantiated-with requires -this-component-id")
2656        Nothing -> ComponentId (unitIdFS (thisPackage dflags))
2657
2658thisUnitIdInsts :: DynFlags -> [(ModuleName, Module)]
2659thisUnitIdInsts dflags =
2660    case thisUnitIdInsts_ dflags of
2661        Just insts -> insts
2662        Nothing    -> []
2663
2664thisPackage :: DynFlags -> UnitId
2665thisPackage dflags =
2666    case thisUnitIdInsts_ dflags of
2667        Nothing -> default_uid
2668        Just insts
2669          | all (\(x,y) -> mkHoleModule x == y) insts
2670          -> newUnitId (thisComponentId dflags) insts
2671          | otherwise
2672          -> default_uid
2673  where
2674    default_uid = DefiniteUnitId (DefUnitId (thisInstalledUnitId dflags))
2675
2676parseUnitIdInsts :: String -> [(ModuleName, Module)]
2677parseUnitIdInsts str = case filter ((=="").snd) (readP_to_S parse str) of
2678    [(r, "")] -> r
2679    _ -> throwGhcException $ CmdLineError ("Can't parse -instantiated-with: " ++ str)
2680  where parse = sepBy parseEntry (R.char ',')
2681        parseEntry = do
2682            n <- parseModuleName
2683            _ <- R.char '='
2684            m <- parseModuleId
2685            return (n, m)
2686
2687setUnitIdInsts :: String -> DynFlags -> DynFlags
2688setUnitIdInsts s d =
2689    d { thisUnitIdInsts_ = Just (parseUnitIdInsts s) }
2690
2691setComponentId :: String -> DynFlags -> DynFlags
2692setComponentId s d =
2693    d { thisComponentId_ = Just (ComponentId (fsLit s)) }
2694
2695addPluginModuleName :: String -> DynFlags -> DynFlags
2696addPluginModuleName name d = d { pluginModNames = (mkModuleName name) : (pluginModNames d) }
2697
2698clearPluginModuleNames :: DynFlags -> DynFlags
2699clearPluginModuleNames d =
2700    d { pluginModNames = []
2701      , pluginModNameOpts = []
2702      , cachedPlugins = [] }
2703
2704addPluginModuleNameOption :: String -> DynFlags -> DynFlags
2705addPluginModuleNameOption optflag d = d { pluginModNameOpts = (mkModuleName m, option) : (pluginModNameOpts d) }
2706  where (m, rest) = break (== ':') optflag
2707        option = case rest of
2708          [] -> "" -- should probably signal an error
2709          (_:plug_opt) -> plug_opt -- ignore the ':' from break
2710
2711addFrontendPluginOption :: String -> DynFlags -> DynFlags
2712addFrontendPluginOption s d = d { frontendPluginOpts = s : frontendPluginOpts d }
2713
2714parseDynLibLoaderMode f d =
2715 case splitAt 8 f of
2716   ("deploy", "")       -> d { dynLibLoader = Deployable }
2717   ("sysdep", "")       -> d { dynLibLoader = SystemDependent }
2718   _                    -> throwGhcException (CmdLineError ("Unknown dynlib loader: " ++ f))
2719
2720setDumpPrefixForce f d = d { dumpPrefixForce = f}
2721
2722-- XXX HACK: Prelude> words "'does not' work" ===> ["'does","not'","work"]
2723-- Config.hs should really use Option.
2724setPgmP   f = alterToolSettings (\s -> s { toolSettings_pgm_P   = (pgm, map Option args)})
2725  where (pgm:args) = words f
2726addOptl   f = alterToolSettings (\s -> s { toolSettings_opt_l   = f : toolSettings_opt_l s})
2727addOptc   f = alterToolSettings (\s -> s { toolSettings_opt_c   = f : toolSettings_opt_c s})
2728addOptcxx f = alterToolSettings (\s -> s { toolSettings_opt_cxx = f : toolSettings_opt_cxx s})
2729addOptP   f = alterToolSettings $ \s -> s
2730          { toolSettings_opt_P   = f : toolSettings_opt_P s
2731          , toolSettings_opt_P_fingerprint = fingerprintStrings (f : toolSettings_opt_P s)
2732          }
2733          -- See Note [Repeated -optP hashing]
2734  where
2735  fingerprintStrings ss = fingerprintFingerprints $ map fingerprintString ss
2736
2737
2738setDepMakefile :: FilePath -> DynFlags -> DynFlags
2739setDepMakefile f d = d { depMakefile = f }
2740
2741setDepIncludeCppDeps :: Bool -> DynFlags -> DynFlags
2742setDepIncludeCppDeps b d = d { depIncludeCppDeps = b }
2743
2744setDepIncludePkgDeps :: Bool -> DynFlags -> DynFlags
2745setDepIncludePkgDeps b d = d { depIncludePkgDeps = b }
2746
2747addDepExcludeMod :: String -> DynFlags -> DynFlags
2748addDepExcludeMod m d
2749    = d { depExcludeMods = mkModuleName m : depExcludeMods d }
2750
2751addDepSuffix :: FilePath -> DynFlags -> DynFlags
2752addDepSuffix s d = d { depSuffixes = s : depSuffixes d }
2753
2754addCmdlineFramework f d = d { cmdlineFrameworks = f : cmdlineFrameworks d}
2755
2756addGhcVersionFile :: FilePath -> DynFlags -> DynFlags
2757addGhcVersionFile f d = d { ghcVersionFile = Just f }
2758
2759addHaddockOpts f d = d { haddockOptions = Just f}
2760
2761addGhciScript f d = d { ghciScripts = f : ghciScripts d}
2762
2763setInteractivePrint f d = d { interactivePrint = Just f}
2764
2765-----------------------------------------------------------------------------
2766-- Setting the optimisation level
2767
2768updOptLevel :: Int -> DynFlags -> DynFlags
2769-- ^ Sets the 'DynFlags' to be appropriate to the optimisation level
2770updOptLevel n dfs
2771  = dfs2{ optLevel = final_n }
2772  where
2773   final_n = max 0 (min 2 n)    -- Clamp to 0 <= n <= 2
2774   dfs1 = foldr (flip gopt_unset) dfs  remove_gopts
2775   dfs2 = foldr (flip gopt_set)   dfs1 extra_gopts
2776
2777   extra_gopts  = [ f | (ns,f) <- optLevelFlags, final_n `elem` ns ]
2778   remove_gopts = [ f | (ns,f) <- optLevelFlags, final_n `notElem` ns ]
2779
2780{- **********************************************************************
2781%*                                                                      *
2782                DynFlags parser
2783%*                                                                      *
2784%********************************************************************* -}
2785
2786-- -----------------------------------------------------------------------------
2787-- Parsing the dynamic flags.
2788
2789
2790-- | Parse dynamic flags from a list of command line arguments.  Returns
2791-- the parsed 'DynFlags', the left-over arguments, and a list of warnings.
2792-- Throws a 'UsageError' if errors occurred during parsing (such as unknown
2793-- flags or missing arguments).
2794parseDynamicFlagsCmdLine :: MonadIO m => DynFlags -> [Located String]
2795                         -> m (DynFlags, [Located String], [Warn])
2796                            -- ^ Updated 'DynFlags', left-over arguments, and
2797                            -- list of warnings.
2798parseDynamicFlagsCmdLine = parseDynamicFlagsFull flagsAll True
2799
2800
2801-- | Like 'parseDynamicFlagsCmdLine' but does not allow the package flags
2802-- (-package, -hide-package, -ignore-package, -hide-all-packages, -package-db).
2803-- Used to parse flags set in a modules pragma.
2804parseDynamicFilePragma :: MonadIO m => DynFlags -> [Located String]
2805                       -> m (DynFlags, [Located String], [Warn])
2806                          -- ^ Updated 'DynFlags', left-over arguments, and
2807                          -- list of warnings.
2808parseDynamicFilePragma = parseDynamicFlagsFull flagsDynamic False
2809
2810
2811-- | Parses the dynamically set flags for GHC. This is the most general form of
2812-- the dynamic flag parser that the other methods simply wrap. It allows
2813-- saying which flags are valid flags and indicating if we are parsing
2814-- arguments from the command line or from a file pragma.
2815parseDynamicFlagsFull :: MonadIO m
2816                  => [Flag (CmdLineP DynFlags)]    -- ^ valid flags to match against
2817                  -> Bool                          -- ^ are the arguments from the command line?
2818                  -> DynFlags                      -- ^ current dynamic flags
2819                  -> [Located String]              -- ^ arguments to parse
2820                  -> m (DynFlags, [Located String], [Warn])
2821parseDynamicFlagsFull activeFlags cmdline dflags0 args = do
2822  let ((leftover, errs, warns), dflags1)
2823          = runCmdLine (processArgs activeFlags args) dflags0
2824
2825  -- See Note [Handling errors when parsing commandline flags]
2826  unless (null errs) $ liftIO $ throwGhcExceptionIO $ errorsToGhcException $
2827    map ((showPpr dflags0 . getLoc &&& unLoc) . errMsg) $ errs
2828
2829  -- check for disabled flags in safe haskell
2830  let (dflags2, sh_warns) = safeFlagCheck cmdline dflags1
2831      dflags3 = updateWays dflags2
2832      theWays = ways dflags3
2833
2834  unless (allowed_combination theWays) $ liftIO $
2835      throwGhcExceptionIO (CmdLineError ("combination not supported: " ++
2836                               intercalate "/" (map wayDesc theWays)))
2837
2838  let chooseOutput
2839        | isJust (outputFile dflags3)          -- Only iff user specified -o ...
2840        , not (isJust (dynOutputFile dflags3)) -- but not -dyno
2841        = return $ dflags3 { dynOutputFile = Just $ dynamicOutputFile dflags3 outFile }
2842        | otherwise
2843        = return dflags3
2844        where
2845          outFile = fromJust $ outputFile dflags3
2846  dflags4 <- ifGeneratingDynamicToo dflags3 chooseOutput (return dflags3)
2847
2848  let (dflags5, consistency_warnings) = makeDynFlagsConsistent dflags4
2849
2850  -- Set timer stats & heap size
2851  when (enableTimeStats dflags5) $ liftIO enableTimingStats
2852  case (ghcHeapSize dflags5) of
2853    Just x -> liftIO (setHeapSize x)
2854    _      -> return ()
2855
2856  liftIO $ setUnsafeGlobalDynFlags dflags5
2857
2858  let warns' = map (Warn Cmd.NoReason) (consistency_warnings ++ sh_warns)
2859
2860  return (dflags5, leftover, warns' ++ warns)
2861
2862-- | Write an error or warning to the 'LogOutput'.
2863putLogMsg :: DynFlags -> WarnReason -> Severity -> SrcSpan -> PprStyle
2864          -> MsgDoc -> IO ()
2865putLogMsg dflags = log_action dflags dflags
2866
2867updateWays :: DynFlags -> DynFlags
2868updateWays dflags
2869    = let theWays = sort $ nub $ ways dflags
2870      in dflags {
2871             ways        = theWays,
2872             buildTag    = mkBuildTag (filter (not . wayRTSOnly) theWays)
2873         }
2874
2875-- | Check (and potentially disable) any extensions that aren't allowed
2876-- in safe mode.
2877--
2878-- The bool is to indicate if we are parsing command line flags (false means
2879-- file pragma). This allows us to generate better warnings.
2880safeFlagCheck :: Bool -> DynFlags -> (DynFlags, [Located String])
2881safeFlagCheck _ dflags | safeLanguageOn dflags = (dflagsUnset, warns)
2882  where
2883    -- Handle illegal flags under safe language.
2884    (dflagsUnset, warns) = foldl' check_method (dflags, []) unsafeFlags
2885
2886    check_method (df, warns) (str,loc,test,fix)
2887        | test df   = (fix df, warns ++ safeFailure (loc df) str)
2888        | otherwise = (df, warns)
2889
2890    safeFailure loc str
2891       = [L loc $ str ++ " is not allowed in Safe Haskell; ignoring "
2892           ++ str]
2893
2894safeFlagCheck cmdl dflags =
2895  case (safeInferOn dflags) of
2896    True | safeFlags -> (dflags', warn)
2897    True             -> (dflags' { safeInferred = False }, warn)
2898    False            -> (dflags', warn)
2899
2900  where
2901    -- dynflags and warn for when -fpackage-trust by itself with no safe
2902    -- haskell flag
2903    (dflags', warn)
2904      | not (safeHaskellModeEnabled dflags) && not cmdl && packageTrustOn dflags
2905      = (gopt_unset dflags Opt_PackageTrust, pkgWarnMsg)
2906      | otherwise = (dflags, [])
2907
2908    pkgWarnMsg = [L (pkgTrustOnLoc dflags') $
2909                    "-fpackage-trust ignored;" ++
2910                    " must be specified with a Safe Haskell flag"]
2911
2912    -- Have we inferred Unsafe? See Note [HscMain . Safe Haskell Inference]
2913    safeFlags = all (\(_,_,t,_) -> not $ t dflags) unsafeFlagsForInfer
2914
2915
2916{- **********************************************************************
2917%*                                                                      *
2918                DynFlags specifications
2919%*                                                                      *
2920%********************************************************************* -}
2921
2922-- | All dynamic flags option strings without the deprecated ones.
2923-- These are the user facing strings for enabling and disabling options.
2924allNonDeprecatedFlags :: [String]
2925allNonDeprecatedFlags = allFlagsDeps False
2926
2927-- | All flags with possibility to filter deprecated ones
2928allFlagsDeps :: Bool -> [String]
2929allFlagsDeps keepDeprecated = [ '-':flagName flag
2930                              | (deprecated, flag) <- flagsAllDeps
2931                              , keepDeprecated || not (isDeprecated deprecated)]
2932  where isDeprecated Deprecated = True
2933        isDeprecated _ = False
2934
2935{-
2936 - Below we export user facing symbols for GHC dynamic flags for use with the
2937 - GHC API.
2938 -}
2939
2940-- All dynamic flags present in GHC.
2941flagsAll :: [Flag (CmdLineP DynFlags)]
2942flagsAll = map snd flagsAllDeps
2943
2944-- All dynamic flags present in GHC with deprecation information.
2945flagsAllDeps :: [(Deprecation, Flag (CmdLineP DynFlags))]
2946flagsAllDeps =  package_flags_deps ++ dynamic_flags_deps
2947
2948
2949-- All dynamic flags, minus package flags, present in GHC.
2950flagsDynamic :: [Flag (CmdLineP DynFlags)]
2951flagsDynamic = map snd dynamic_flags_deps
2952
2953-- ALl package flags present in GHC.
2954flagsPackage :: [Flag (CmdLineP DynFlags)]
2955flagsPackage = map snd package_flags_deps
2956
2957----------------Helpers to make flags and keep deprecation information----------
2958
2959type FlagMaker m = String -> OptKind m -> Flag m
2960type DynFlagMaker = FlagMaker (CmdLineP DynFlags)
2961data Deprecation = NotDeprecated | Deprecated deriving (Eq, Ord)
2962
2963-- Make a non-deprecated flag
2964make_ord_flag :: DynFlagMaker -> String -> OptKind (CmdLineP DynFlags)
2965              -> (Deprecation, Flag (CmdLineP DynFlags))
2966make_ord_flag fm name kind = (NotDeprecated, fm name kind)
2967
2968-- Make a deprecated flag
2969make_dep_flag :: DynFlagMaker -> String -> OptKind (CmdLineP DynFlags) -> String
2970                 -> (Deprecation, Flag (CmdLineP DynFlags))
2971make_dep_flag fm name kind message = (Deprecated,
2972                                      fm name $ add_dep_message kind message)
2973
2974add_dep_message :: OptKind (CmdLineP DynFlags) -> String
2975                -> OptKind (CmdLineP DynFlags)
2976add_dep_message (NoArg f) message = NoArg $ f >> deprecate message
2977add_dep_message (HasArg f) message = HasArg $ \s -> f s >> deprecate message
2978add_dep_message (SepArg f) message = SepArg $ \s -> f s >> deprecate message
2979add_dep_message (Prefix f) message = Prefix $ \s -> f s >> deprecate message
2980add_dep_message (OptPrefix f) message =
2981                                  OptPrefix $ \s -> f s >> deprecate message
2982add_dep_message (OptIntSuffix f) message =
2983                               OptIntSuffix $ \oi -> f oi >> deprecate message
2984add_dep_message (IntSuffix f) message =
2985                                  IntSuffix $ \i -> f i >> deprecate message
2986add_dep_message (FloatSuffix f) message =
2987                                FloatSuffix $ \fl -> f fl >> deprecate message
2988add_dep_message (PassFlag f) message =
2989                                   PassFlag $ \s -> f s >> deprecate message
2990add_dep_message (AnySuffix f) message =
2991                                  AnySuffix $ \s -> f s >> deprecate message
2992
2993----------------------- The main flags themselves ------------------------------
2994-- See Note [Updating flag description in the User's Guide]
2995-- See Note [Supporting CLI completion]
2996dynamic_flags_deps :: [(Deprecation, Flag (CmdLineP DynFlags))]
2997dynamic_flags_deps = [
2998    make_dep_flag defFlag "n" (NoArg $ return ())
2999        "The -n flag is deprecated and no longer has any effect"
3000  , make_ord_flag defFlag "cpp"      (NoArg (setExtensionFlag LangExt.Cpp))
3001  , make_ord_flag defFlag "F"        (NoArg (setGeneralFlag Opt_Pp))
3002  , (Deprecated, defFlag "#include"
3003      (HasArg (\_s ->
3004         deprecate ("-#include and INCLUDE pragmas are " ++
3005                    "deprecated: They no longer have any effect"))))
3006  , make_ord_flag defFlag "v"        (OptIntSuffix setVerbosity)
3007
3008  , make_ord_flag defGhcFlag "j"     (OptIntSuffix
3009        (\n -> case n of
3010                 Just n
3011                     | n > 0     -> upd (\d -> d { parMakeCount = Just n })
3012                     | otherwise -> addErr "Syntax: -j[n] where n > 0"
3013                 Nothing -> upd (\d -> d { parMakeCount = Nothing })))
3014                 -- When the number of parallel builds
3015                 -- is omitted, it is the same
3016                 -- as specifing that the number of
3017                 -- parallel builds is equal to the
3018                 -- result of getNumProcessors
3019  , make_ord_flag defFlag "instantiated-with"   (sepArg setUnitIdInsts)
3020  , make_ord_flag defFlag "this-component-id"   (sepArg setComponentId)
3021
3022    -- RTS options -------------------------------------------------------------
3023  , make_ord_flag defFlag "H"           (HasArg (\s -> upd (\d ->
3024          d { ghcHeapSize = Just $ fromIntegral (decodeSize s)})))
3025
3026  , make_ord_flag defFlag "Rghc-timing" (NoArg (upd (\d ->
3027                                               d { enableTimeStats = True })))
3028
3029    ------- ways ---------------------------------------------------------------
3030  , make_ord_flag defGhcFlag "prof"           (NoArg (addWay WayProf))
3031  , make_ord_flag defGhcFlag "eventlog"       (NoArg (addWay WayEventLog))
3032  , make_dep_flag defGhcFlag "smp"
3033      (NoArg $ addWay WayThreaded) "Use -threaded instead"
3034  , make_ord_flag defGhcFlag "debug"          (NoArg (addWay WayDebug))
3035  , make_ord_flag defGhcFlag "threaded"       (NoArg (addWay WayThreaded))
3036
3037  , make_ord_flag defGhcFlag "ticky"
3038      (NoArg (setGeneralFlag Opt_Ticky >> addWay WayDebug))
3039
3040    -- -ticky enables ticky-ticky code generation, and also implies -debug which
3041    -- is required to get the RTS ticky support.
3042
3043        ----- Linker --------------------------------------------------------
3044  , make_ord_flag defGhcFlag "static"         (NoArg removeWayDyn)
3045  , make_ord_flag defGhcFlag "dynamic"        (NoArg (addWay WayDyn))
3046  , make_ord_flag defGhcFlag "rdynamic" $ noArg $
3047#if defined(linux_HOST_OS)
3048                              addOptl "-rdynamic"
3049#elif defined(mingw32_HOST_OS)
3050                              addOptl "-Wl,--export-all-symbols"
3051#else
3052    -- ignored for compat w/ gcc:
3053                              id
3054#endif
3055  , make_ord_flag defGhcFlag "relative-dynlib-paths"
3056      (NoArg (setGeneralFlag Opt_RelativeDynlibPaths))
3057  , make_ord_flag defGhcFlag "copy-libs-when-linking"
3058      (NoArg (setGeneralFlag Opt_SingleLibFolder))
3059  , make_ord_flag defGhcFlag "pie"            (NoArg (setGeneralFlag Opt_PICExecutable))
3060  , make_ord_flag defGhcFlag "no-pie"         (NoArg (unSetGeneralFlag Opt_PICExecutable))
3061
3062        ------- Specific phases  --------------------------------------------
3063    -- need to appear before -pgmL to be parsed as LLVM flags.
3064  , make_ord_flag defFlag "pgmlo"
3065      $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_lo  = (f,[]) }
3066  , make_ord_flag defFlag "pgmlc"
3067      $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_lc  = (f,[]) }
3068  , make_ord_flag defFlag "pgmlm"
3069      $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_lm  = (f,[]) }
3070  , make_ord_flag defFlag "pgmi"
3071      $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_i   =  f }
3072  , make_ord_flag defFlag "pgmL"
3073      $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_L   = f }
3074  , make_ord_flag defFlag "pgmP"
3075      (hasArg setPgmP)
3076  , make_ord_flag defFlag "pgmF"
3077      $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_F   = f }
3078  , make_ord_flag defFlag "pgmc"
3079      $ hasArg $ \f -> alterToolSettings $ \s -> s
3080         { toolSettings_pgm_c   = f
3081         , -- Don't pass -no-pie with -pgmc
3082           -- (see #15319)
3083           toolSettings_ccSupportsNoPie = False
3084         }
3085  , make_ord_flag defFlag "pgmc-supports-no-pie"
3086      $ noArg $ alterToolSettings $ \s -> s { toolSettings_ccSupportsNoPie = True }
3087  , make_ord_flag defFlag "pgms"
3088      (HasArg (\_ -> addWarn "Object splitting was removed in GHC 8.8"))
3089  , make_ord_flag defFlag "pgma"
3090      $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_a   = (f,[]) }
3091  , make_ord_flag defFlag "pgml"
3092      $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_l   = (f,[]) }
3093  , make_ord_flag defFlag "pgmdll"
3094      $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_dll = (f,[]) }
3095  , make_ord_flag defFlag "pgmwindres"
3096      $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_windres = f }
3097  , make_ord_flag defFlag "pgmlibtool"
3098      $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_libtool = f }
3099  , make_ord_flag defFlag "pgmar"
3100      $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_ar = f }
3101  , make_ord_flag defFlag "pgmotool"
3102      $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_otool = f}
3103  , make_ord_flag defFlag "pgminstall_name_tool"
3104      $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_install_name_tool = f}
3105  , make_ord_flag defFlag "pgmranlib"
3106      $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_ranlib = f }
3107
3108
3109    -- need to appear before -optl/-opta to be parsed as LLVM flags.
3110  , make_ord_flag defFlag "optlm"
3111      $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_opt_lm  = f : toolSettings_opt_lm s }
3112  , make_ord_flag defFlag "optlo"
3113      $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_opt_lo  = f : toolSettings_opt_lo s }
3114  , make_ord_flag defFlag "optlc"
3115      $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_opt_lc  = f : toolSettings_opt_lc s }
3116  , make_ord_flag defFlag "opti"
3117      $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_opt_i   = f : toolSettings_opt_i s }
3118  , make_ord_flag defFlag "optL"
3119      $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_opt_L   = f : toolSettings_opt_L s }
3120  , make_ord_flag defFlag "optP"
3121      (hasArg addOptP)
3122  , make_ord_flag defFlag "optF"
3123      $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_opt_F   = f : toolSettings_opt_F s }
3124  , make_ord_flag defFlag "optc"
3125      (hasArg addOptc)
3126  , make_ord_flag defFlag "optcxx"
3127      (hasArg addOptcxx)
3128  , make_ord_flag defFlag "opta"
3129      $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_opt_a   = f : toolSettings_opt_a s }
3130  , make_ord_flag defFlag "optl"
3131      (hasArg addOptl)
3132  , make_ord_flag defFlag "optwindres"
3133      $ hasArg $ \f ->
3134        alterToolSettings $ \s -> s { toolSettings_opt_windres = f : toolSettings_opt_windres s }
3135
3136  , make_ord_flag defGhcFlag "split-objs"
3137      (NoArg $ addWarn "ignoring -split-objs")
3138
3139  , make_ord_flag defGhcFlag "split-sections"
3140      (noArgM (\dflags -> do
3141        if platformHasSubsectionsViaSymbols (targetPlatform dflags)
3142          then do addWarn $
3143                    "-split-sections is not useful on this platform " ++
3144                    "since it always uses subsections via symbols. Ignoring."
3145                  return dflags
3146          else return (gopt_set dflags Opt_SplitSections)))
3147
3148        -------- ghc -M -----------------------------------------------------
3149  , make_ord_flag defGhcFlag "dep-suffix"              (hasArg addDepSuffix)
3150  , make_ord_flag defGhcFlag "dep-makefile"            (hasArg setDepMakefile)
3151  , make_ord_flag defGhcFlag "include-cpp-deps"
3152        (noArg (setDepIncludeCppDeps True))
3153  , make_ord_flag defGhcFlag "include-pkg-deps"
3154        (noArg (setDepIncludePkgDeps True))
3155  , make_ord_flag defGhcFlag "exclude-module"          (hasArg addDepExcludeMod)
3156
3157        -------- Linking ----------------------------------------------------
3158  , make_ord_flag defGhcFlag "no-link"
3159        (noArg (\d -> d { ghcLink=NoLink }))
3160  , make_ord_flag defGhcFlag "shared"
3161        (noArg (\d -> d { ghcLink=LinkDynLib }))
3162  , make_ord_flag defGhcFlag "staticlib"
3163        (noArg (\d -> d { ghcLink=LinkStaticLib }))
3164  , make_ord_flag defGhcFlag "dynload"            (hasArg parseDynLibLoaderMode)
3165  , make_ord_flag defGhcFlag "dylib-install-name" (hasArg setDylibInstallName)
3166
3167        ------- Libraries ---------------------------------------------------
3168  , make_ord_flag defFlag "L"   (Prefix addLibraryPath)
3169  , make_ord_flag defFlag "l"   (hasArg (addLdInputs . Option . ("-l" ++)))
3170
3171        ------- Frameworks --------------------------------------------------
3172        -- -framework-path should really be -F ...
3173  , make_ord_flag defFlag "framework-path" (HasArg addFrameworkPath)
3174  , make_ord_flag defFlag "framework"      (hasArg addCmdlineFramework)
3175
3176        ------- Output Redirection ------------------------------------------
3177  , make_ord_flag defGhcFlag "odir"              (hasArg setObjectDir)
3178  , make_ord_flag defGhcFlag "o"                 (sepArg (setOutputFile . Just))
3179  , make_ord_flag defGhcFlag "dyno"
3180        (sepArg (setDynOutputFile . Just))
3181  , make_ord_flag defGhcFlag "ohi"
3182        (hasArg (setOutputHi . Just ))
3183  , make_ord_flag defGhcFlag "osuf"              (hasArg setObjectSuf)
3184  , make_ord_flag defGhcFlag "dynosuf"           (hasArg setDynObjectSuf)
3185  , make_ord_flag defGhcFlag "hcsuf"             (hasArg setHcSuf)
3186  , make_ord_flag defGhcFlag "hisuf"             (hasArg setHiSuf)
3187  , make_ord_flag defGhcFlag "hiesuf"            (hasArg setHieSuf)
3188  , make_ord_flag defGhcFlag "dynhisuf"          (hasArg setDynHiSuf)
3189  , make_ord_flag defGhcFlag "hidir"             (hasArg setHiDir)
3190  , make_ord_flag defGhcFlag "hiedir"            (hasArg setHieDir)
3191  , make_ord_flag defGhcFlag "tmpdir"            (hasArg setTmpDir)
3192  , make_ord_flag defGhcFlag "stubdir"           (hasArg setStubDir)
3193  , make_ord_flag defGhcFlag "dumpdir"           (hasArg setDumpDir)
3194  , make_ord_flag defGhcFlag "outputdir"         (hasArg setOutputDir)
3195  , make_ord_flag defGhcFlag "ddump-file-prefix"
3196        (hasArg (setDumpPrefixForce . Just))
3197
3198  , make_ord_flag defGhcFlag "dynamic-too"
3199        (NoArg (setGeneralFlag Opt_BuildDynamicToo))
3200
3201        ------- Keeping temporary files -------------------------------------
3202     -- These can be singular (think ghc -c) or plural (think ghc --make)
3203  , make_ord_flag defGhcFlag "keep-hc-file"
3204        (NoArg (setGeneralFlag Opt_KeepHcFiles))
3205  , make_ord_flag defGhcFlag "keep-hc-files"
3206        (NoArg (setGeneralFlag Opt_KeepHcFiles))
3207  , make_ord_flag defGhcFlag "keep-hscpp-file"
3208        (NoArg (setGeneralFlag Opt_KeepHscppFiles))
3209  , make_ord_flag defGhcFlag "keep-hscpp-files"
3210        (NoArg (setGeneralFlag Opt_KeepHscppFiles))
3211  , make_ord_flag defGhcFlag "keep-s-file"
3212        (NoArg (setGeneralFlag Opt_KeepSFiles))
3213  , make_ord_flag defGhcFlag "keep-s-files"
3214        (NoArg (setGeneralFlag Opt_KeepSFiles))
3215  , make_ord_flag defGhcFlag "keep-llvm-file"
3216        (NoArg $ setObjTarget HscLlvm >> setGeneralFlag Opt_KeepLlvmFiles)
3217  , make_ord_flag defGhcFlag "keep-llvm-files"
3218        (NoArg $ setObjTarget HscLlvm >> setGeneralFlag Opt_KeepLlvmFiles)
3219     -- This only makes sense as plural
3220  , make_ord_flag defGhcFlag "keep-tmp-files"
3221        (NoArg (setGeneralFlag Opt_KeepTmpFiles))
3222  , make_ord_flag defGhcFlag "keep-hi-file"
3223        (NoArg (setGeneralFlag Opt_KeepHiFiles))
3224  , make_ord_flag defGhcFlag "no-keep-hi-file"
3225        (NoArg (unSetGeneralFlag Opt_KeepHiFiles))
3226  , make_ord_flag defGhcFlag "keep-hi-files"
3227        (NoArg (setGeneralFlag Opt_KeepHiFiles))
3228  , make_ord_flag defGhcFlag "no-keep-hi-files"
3229        (NoArg (unSetGeneralFlag Opt_KeepHiFiles))
3230  , make_ord_flag defGhcFlag "keep-o-file"
3231        (NoArg (setGeneralFlag Opt_KeepOFiles))
3232  , make_ord_flag defGhcFlag "no-keep-o-file"
3233        (NoArg (unSetGeneralFlag Opt_KeepOFiles))
3234  , make_ord_flag defGhcFlag "keep-o-files"
3235        (NoArg (setGeneralFlag Opt_KeepOFiles))
3236  , make_ord_flag defGhcFlag "no-keep-o-files"
3237        (NoArg (unSetGeneralFlag Opt_KeepOFiles))
3238
3239        ------- Miscellaneous ----------------------------------------------
3240  , make_ord_flag defGhcFlag "no-auto-link-packages"
3241        (NoArg (unSetGeneralFlag Opt_AutoLinkPackages))
3242  , make_ord_flag defGhcFlag "no-hs-main"
3243        (NoArg (setGeneralFlag Opt_NoHsMain))
3244  , make_ord_flag defGhcFlag "fno-state-hack"
3245        (NoArg (setGeneralFlag Opt_G_NoStateHack))
3246  , make_ord_flag defGhcFlag "fno-opt-coercion"
3247        (NoArg (setGeneralFlag Opt_G_NoOptCoercion))
3248  , make_ord_flag defGhcFlag "with-rtsopts"
3249        (HasArg setRtsOpts)
3250  , make_ord_flag defGhcFlag "rtsopts"
3251        (NoArg (setRtsOptsEnabled RtsOptsAll))
3252  , make_ord_flag defGhcFlag "rtsopts=all"
3253        (NoArg (setRtsOptsEnabled RtsOptsAll))
3254  , make_ord_flag defGhcFlag "rtsopts=some"
3255        (NoArg (setRtsOptsEnabled RtsOptsSafeOnly))
3256  , make_ord_flag defGhcFlag "rtsopts=none"
3257        (NoArg (setRtsOptsEnabled RtsOptsNone))
3258  , make_ord_flag defGhcFlag "rtsopts=ignore"
3259        (NoArg (setRtsOptsEnabled RtsOptsIgnore))
3260  , make_ord_flag defGhcFlag "rtsopts=ignoreAll"
3261        (NoArg (setRtsOptsEnabled RtsOptsIgnoreAll))
3262  , make_ord_flag defGhcFlag "no-rtsopts"
3263        (NoArg (setRtsOptsEnabled RtsOptsNone))
3264  , make_ord_flag defGhcFlag "no-rtsopts-suggestions"
3265      (noArg (\d -> d {rtsOptsSuggestions = False}))
3266  , make_ord_flag defGhcFlag "dhex-word-literals"
3267        (NoArg (setGeneralFlag Opt_HexWordLiterals))
3268
3269  , make_ord_flag defGhcFlag "ghcversion-file"      (hasArg addGhcVersionFile)
3270  , make_ord_flag defGhcFlag "main-is"              (SepArg setMainIs)
3271  , make_ord_flag defGhcFlag "haddock"              (NoArg (setGeneralFlag Opt_Haddock))
3272  , make_ord_flag defGhcFlag "haddock-opts"         (hasArg addHaddockOpts)
3273  , make_ord_flag defGhcFlag "hpcdir"               (SepArg setOptHpcDir)
3274  , make_ord_flag defGhciFlag "ghci-script"         (hasArg addGhciScript)
3275  , make_ord_flag defGhciFlag "interactive-print"   (hasArg setInteractivePrint)
3276  , make_ord_flag defGhcFlag "ticky-allocd"
3277        (NoArg (setGeneralFlag Opt_Ticky_Allocd))
3278  , make_ord_flag defGhcFlag "ticky-LNE"
3279        (NoArg (setGeneralFlag Opt_Ticky_LNE))
3280  , make_ord_flag defGhcFlag "ticky-dyn-thunk"
3281        (NoArg (setGeneralFlag Opt_Ticky_Dyn_Thunk))
3282        ------- recompilation checker --------------------------------------
3283  , make_dep_flag defGhcFlag "recomp"
3284        (NoArg $ unSetGeneralFlag Opt_ForceRecomp)
3285             "Use -fno-force-recomp instead"
3286  , make_dep_flag defGhcFlag "no-recomp"
3287        (NoArg $ setGeneralFlag Opt_ForceRecomp) "Use -fforce-recomp instead"
3288  , make_ord_flag defFlag "fmax-errors"
3289      (intSuffix (\n d -> d { maxErrors = Just (max 1 n) }))
3290  , make_ord_flag defFlag "fno-max-errors"
3291      (noArg (\d -> d { maxErrors = Nothing }))
3292  , make_ord_flag defFlag "freverse-errors"
3293        (noArg (\d -> d {reverseErrors = True} ))
3294  , make_ord_flag defFlag "fno-reverse-errors"
3295        (noArg (\d -> d {reverseErrors = False} ))
3296
3297        ------ HsCpp opts ---------------------------------------------------
3298  , make_ord_flag defFlag "D"              (AnySuffix (upd . addOptP))
3299  , make_ord_flag defFlag "U"              (AnySuffix (upd . addOptP))
3300
3301        ------- Include/Import Paths ----------------------------------------
3302  , make_ord_flag defFlag "I"              (Prefix    addIncludePath)
3303  , make_ord_flag defFlag "i"              (OptPrefix addImportPath)
3304
3305        ------ Output style options -----------------------------------------
3306  , make_ord_flag defFlag "dppr-user-length" (intSuffix (\n d ->
3307                                                       d { pprUserLength = n }))
3308  , make_ord_flag defFlag "dppr-cols"        (intSuffix (\n d ->
3309                                                             d { pprCols = n }))
3310  , make_ord_flag defFlag "fdiagnostics-color=auto"
3311      (NoArg (upd (\d -> d { useColor = Auto })))
3312  , make_ord_flag defFlag "fdiagnostics-color=always"
3313      (NoArg (upd (\d -> d { useColor = Always })))
3314  , make_ord_flag defFlag "fdiagnostics-color=never"
3315      (NoArg (upd (\d -> d { useColor = Never })))
3316
3317  -- Suppress all that is suppressable in core dumps.
3318  -- Except for uniques, as some simplifier phases introduce new variables that
3319  -- have otherwise identical names.
3320  , make_ord_flag defGhcFlag "dsuppress-all"
3321      (NoArg $ do setGeneralFlag Opt_SuppressCoercions
3322                  setGeneralFlag Opt_SuppressVarKinds
3323                  setGeneralFlag Opt_SuppressModulePrefixes
3324                  setGeneralFlag Opt_SuppressTypeApplications
3325                  setGeneralFlag Opt_SuppressIdInfo
3326                  setGeneralFlag Opt_SuppressTicks
3327                  setGeneralFlag Opt_SuppressStgExts
3328                  setGeneralFlag Opt_SuppressTypeSignatures
3329                  setGeneralFlag Opt_SuppressTimestamps)
3330
3331        ------ Debugging ----------------------------------------------------
3332  , make_ord_flag defGhcFlag "dstg-stats"
3333        (NoArg (setGeneralFlag Opt_StgStats))
3334
3335  , make_ord_flag defGhcFlag "ddump-cmm"
3336        (setDumpFlag Opt_D_dump_cmm)
3337  , make_ord_flag defGhcFlag "ddump-cmm-from-stg"
3338        (setDumpFlag Opt_D_dump_cmm_from_stg)
3339  , make_ord_flag defGhcFlag "ddump-cmm-raw"
3340        (setDumpFlag Opt_D_dump_cmm_raw)
3341  , make_ord_flag defGhcFlag "ddump-cmm-verbose"
3342        (setDumpFlag Opt_D_dump_cmm_verbose)
3343  , make_ord_flag defGhcFlag "ddump-cmm-verbose-by-proc"
3344        (setDumpFlag Opt_D_dump_cmm_verbose_by_proc)
3345  , make_ord_flag defGhcFlag "ddump-cmm-cfg"
3346        (setDumpFlag Opt_D_dump_cmm_cfg)
3347  , make_ord_flag defGhcFlag "ddump-cmm-cbe"
3348        (setDumpFlag Opt_D_dump_cmm_cbe)
3349  , make_ord_flag defGhcFlag "ddump-cmm-switch"
3350        (setDumpFlag Opt_D_dump_cmm_switch)
3351  , make_ord_flag defGhcFlag "ddump-cmm-proc"
3352        (setDumpFlag Opt_D_dump_cmm_proc)
3353  , make_ord_flag defGhcFlag "ddump-cmm-sp"
3354        (setDumpFlag Opt_D_dump_cmm_sp)
3355  , make_ord_flag defGhcFlag "ddump-cmm-sink"
3356        (setDumpFlag Opt_D_dump_cmm_sink)
3357  , make_ord_flag defGhcFlag "ddump-cmm-caf"
3358        (setDumpFlag Opt_D_dump_cmm_caf)
3359  , make_ord_flag defGhcFlag "ddump-cmm-procmap"
3360        (setDumpFlag Opt_D_dump_cmm_procmap)
3361  , make_ord_flag defGhcFlag "ddump-cmm-split"
3362        (setDumpFlag Opt_D_dump_cmm_split)
3363  , make_ord_flag defGhcFlag "ddump-cmm-info"
3364        (setDumpFlag Opt_D_dump_cmm_info)
3365  , make_ord_flag defGhcFlag "ddump-cmm-cps"
3366        (setDumpFlag Opt_D_dump_cmm_cps)
3367  , make_ord_flag defGhcFlag "ddump-cfg-weights"
3368        (setDumpFlag Opt_D_dump_cfg_weights)
3369  , make_ord_flag defGhcFlag "ddump-core-stats"
3370        (setDumpFlag Opt_D_dump_core_stats)
3371  , make_ord_flag defGhcFlag "ddump-asm"
3372        (setDumpFlag Opt_D_dump_asm)
3373  , make_ord_flag defGhcFlag "ddump-asm-native"
3374        (setDumpFlag Opt_D_dump_asm_native)
3375  , make_ord_flag defGhcFlag "ddump-asm-liveness"
3376        (setDumpFlag Opt_D_dump_asm_liveness)
3377  , make_ord_flag defGhcFlag "ddump-asm-regalloc"
3378        (setDumpFlag Opt_D_dump_asm_regalloc)
3379  , make_ord_flag defGhcFlag "ddump-asm-conflicts"
3380        (setDumpFlag Opt_D_dump_asm_conflicts)
3381  , make_ord_flag defGhcFlag "ddump-asm-regalloc-stages"
3382        (setDumpFlag Opt_D_dump_asm_regalloc_stages)
3383  , make_ord_flag defGhcFlag "ddump-asm-stats"
3384        (setDumpFlag Opt_D_dump_asm_stats)
3385  , make_ord_flag defGhcFlag "ddump-asm-expanded"
3386        (setDumpFlag Opt_D_dump_asm_expanded)
3387  , make_ord_flag defGhcFlag "ddump-llvm"
3388        (NoArg $ setObjTarget HscLlvm >> setDumpFlag' Opt_D_dump_llvm)
3389  , make_ord_flag defGhcFlag "ddump-deriv"
3390        (setDumpFlag Opt_D_dump_deriv)
3391  , make_ord_flag defGhcFlag "ddump-ds"
3392        (setDumpFlag Opt_D_dump_ds)
3393  , make_ord_flag defGhcFlag "ddump-ds-preopt"
3394        (setDumpFlag Opt_D_dump_ds_preopt)
3395  , make_ord_flag defGhcFlag "ddump-foreign"
3396        (setDumpFlag Opt_D_dump_foreign)
3397  , make_ord_flag defGhcFlag "ddump-inlinings"
3398        (setDumpFlag Opt_D_dump_inlinings)
3399  , make_ord_flag defGhcFlag "ddump-rule-firings"
3400        (setDumpFlag Opt_D_dump_rule_firings)
3401  , make_ord_flag defGhcFlag "ddump-rule-rewrites"
3402        (setDumpFlag Opt_D_dump_rule_rewrites)
3403  , make_ord_flag defGhcFlag "ddump-simpl-trace"
3404        (setDumpFlag Opt_D_dump_simpl_trace)
3405  , make_ord_flag defGhcFlag "ddump-occur-anal"
3406        (setDumpFlag Opt_D_dump_occur_anal)
3407  , make_ord_flag defGhcFlag "ddump-parsed"
3408        (setDumpFlag Opt_D_dump_parsed)
3409  , make_ord_flag defGhcFlag "ddump-parsed-ast"
3410        (setDumpFlag Opt_D_dump_parsed_ast)
3411  , make_ord_flag defGhcFlag "ddump-rn"
3412        (setDumpFlag Opt_D_dump_rn)
3413  , make_ord_flag defGhcFlag "ddump-rn-ast"
3414        (setDumpFlag Opt_D_dump_rn_ast)
3415  , make_ord_flag defGhcFlag "ddump-simpl"
3416        (setDumpFlag Opt_D_dump_simpl)
3417  , make_ord_flag defGhcFlag "ddump-simpl-iterations"
3418      (setDumpFlag Opt_D_dump_simpl_iterations)
3419  , make_ord_flag defGhcFlag "ddump-spec"
3420        (setDumpFlag Opt_D_dump_spec)
3421  , make_ord_flag defGhcFlag "ddump-prep"
3422        (setDumpFlag Opt_D_dump_prep)
3423  , make_ord_flag defGhcFlag "ddump-stg"
3424        (setDumpFlag Opt_D_dump_stg)
3425  , make_ord_flag defGhcFlag "ddump-stg-unarised"
3426        (setDumpFlag Opt_D_dump_stg_unarised)
3427  , make_ord_flag defGhcFlag "ddump-stg-final"
3428        (setDumpFlag Opt_D_dump_stg_final)
3429  , make_ord_flag defGhcFlag "ddump-call-arity"
3430        (setDumpFlag Opt_D_dump_call_arity)
3431  , make_ord_flag defGhcFlag "ddump-exitify"
3432        (setDumpFlag Opt_D_dump_exitify)
3433  , make_ord_flag defGhcFlag "ddump-stranal"
3434        (setDumpFlag Opt_D_dump_stranal)
3435  , make_ord_flag defGhcFlag "ddump-str-signatures"
3436        (setDumpFlag Opt_D_dump_str_signatures)
3437  , make_ord_flag defGhcFlag "ddump-tc"
3438        (setDumpFlag Opt_D_dump_tc)
3439  , make_ord_flag defGhcFlag "ddump-tc-ast"
3440        (setDumpFlag Opt_D_dump_tc_ast)
3441  , make_ord_flag defGhcFlag "ddump-types"
3442        (setDumpFlag Opt_D_dump_types)
3443  , make_ord_flag defGhcFlag "ddump-rules"
3444        (setDumpFlag Opt_D_dump_rules)
3445  , make_ord_flag defGhcFlag "ddump-cse"
3446        (setDumpFlag Opt_D_dump_cse)
3447  , make_ord_flag defGhcFlag "ddump-worker-wrapper"
3448        (setDumpFlag Opt_D_dump_worker_wrapper)
3449  , make_ord_flag defGhcFlag "ddump-rn-trace"
3450        (setDumpFlag Opt_D_dump_rn_trace)
3451  , make_ord_flag defGhcFlag "ddump-if-trace"
3452        (setDumpFlag Opt_D_dump_if_trace)
3453  , make_ord_flag defGhcFlag "ddump-cs-trace"
3454        (setDumpFlag Opt_D_dump_cs_trace)
3455  , make_ord_flag defGhcFlag "ddump-tc-trace"
3456        (NoArg (do setDumpFlag' Opt_D_dump_tc_trace
3457                   setDumpFlag' Opt_D_dump_cs_trace))
3458  , make_ord_flag defGhcFlag "ddump-ec-trace"
3459        (setDumpFlag Opt_D_dump_ec_trace)
3460  , make_ord_flag defGhcFlag "ddump-vt-trace"
3461        (setDumpFlag Opt_D_dump_vt_trace)
3462  , make_ord_flag defGhcFlag "ddump-splices"
3463        (setDumpFlag Opt_D_dump_splices)
3464  , make_ord_flag defGhcFlag "dth-dec-file"
3465        (setDumpFlag Opt_D_th_dec_file)
3466
3467  , make_ord_flag defGhcFlag "ddump-rn-stats"
3468        (setDumpFlag Opt_D_dump_rn_stats)
3469  , make_ord_flag defGhcFlag "ddump-opt-cmm"
3470        (setDumpFlag Opt_D_dump_opt_cmm)
3471  , make_ord_flag defGhcFlag "ddump-simpl-stats"
3472        (setDumpFlag Opt_D_dump_simpl_stats)
3473  , make_ord_flag defGhcFlag "ddump-bcos"
3474        (setDumpFlag Opt_D_dump_BCOs)
3475  , make_ord_flag defGhcFlag "dsource-stats"
3476        (setDumpFlag Opt_D_source_stats)
3477  , make_ord_flag defGhcFlag "dverbose-core2core"
3478        (NoArg $ setVerbosity (Just 2) >> setVerboseCore2Core)
3479  , make_ord_flag defGhcFlag "dverbose-stg2stg"
3480        (setDumpFlag Opt_D_verbose_stg2stg)
3481  , make_ord_flag defGhcFlag "ddump-hi"
3482        (setDumpFlag Opt_D_dump_hi)
3483  , make_ord_flag defGhcFlag "ddump-minimal-imports"
3484        (NoArg (setGeneralFlag Opt_D_dump_minimal_imports))
3485  , make_ord_flag defGhcFlag "ddump-hpc"
3486        (setDumpFlag Opt_D_dump_ticked) -- back compat
3487  , make_ord_flag defGhcFlag "ddump-ticked"
3488        (setDumpFlag Opt_D_dump_ticked)
3489  , make_ord_flag defGhcFlag "ddump-mod-cycles"
3490        (setDumpFlag Opt_D_dump_mod_cycles)
3491  , make_ord_flag defGhcFlag "ddump-mod-map"
3492        (setDumpFlag Opt_D_dump_mod_map)
3493  , make_ord_flag defGhcFlag "ddump-timings"
3494        (setDumpFlag Opt_D_dump_timings)
3495  , make_ord_flag defGhcFlag "ddump-view-pattern-commoning"
3496        (setDumpFlag Opt_D_dump_view_pattern_commoning)
3497  , make_ord_flag defGhcFlag "ddump-to-file"
3498        (NoArg (setGeneralFlag Opt_DumpToFile))
3499  , make_ord_flag defGhcFlag "ddump-hi-diffs"
3500        (setDumpFlag Opt_D_dump_hi_diffs)
3501  , make_ord_flag defGhcFlag "ddump-rtti"
3502        (setDumpFlag Opt_D_dump_rtti)
3503  , make_ord_flag defGhcFlag "dcore-lint"
3504        (NoArg (setGeneralFlag Opt_DoCoreLinting))
3505  , make_ord_flag defGhcFlag "dstg-lint"
3506        (NoArg (setGeneralFlag Opt_DoStgLinting))
3507  , make_ord_flag defGhcFlag "dcmm-lint"
3508        (NoArg (setGeneralFlag Opt_DoCmmLinting))
3509  , make_ord_flag defGhcFlag "dasm-lint"
3510        (NoArg (setGeneralFlag Opt_DoAsmLinting))
3511  , make_ord_flag defGhcFlag "dannot-lint"
3512        (NoArg (setGeneralFlag Opt_DoAnnotationLinting))
3513  , make_ord_flag defGhcFlag "dshow-passes"
3514        (NoArg $ forceRecompile >> (setVerbosity $ Just 2))
3515  , make_ord_flag defGhcFlag "dfaststring-stats"
3516        (NoArg (setGeneralFlag Opt_D_faststring_stats))
3517  , make_ord_flag defGhcFlag "dno-llvm-mangler"
3518        (NoArg (setGeneralFlag Opt_NoLlvmMangler)) -- hidden flag
3519  , make_ord_flag defGhcFlag "fast-llvm"
3520        (NoArg (setGeneralFlag Opt_FastLlvm)) -- hidden flag
3521  , make_ord_flag defGhcFlag "dno-typeable-binds"
3522        (NoArg (setGeneralFlag Opt_NoTypeableBinds))
3523  , make_ord_flag defGhcFlag "ddump-debug"
3524        (setDumpFlag Opt_D_dump_debug)
3525  , make_ord_flag defGhcFlag "ddump-json"
3526        (noArg (flip dopt_set Opt_D_dump_json . setJsonLogAction ) )
3527  , make_ord_flag defGhcFlag "dppr-debug"
3528        (setDumpFlag Opt_D_ppr_debug)
3529  , make_ord_flag defGhcFlag "ddebug-output"
3530        (noArg (flip dopt_unset Opt_D_no_debug_output))
3531  , make_ord_flag defGhcFlag "dno-debug-output"
3532        (setDumpFlag Opt_D_no_debug_output)
3533
3534        ------ Machine dependent (-m<blah>) stuff ---------------------------
3535
3536  , make_ord_flag defGhcFlag "msse"         (noArg (\d ->
3537                                                  d { sseVersion = Just SSE1 }))
3538  , make_ord_flag defGhcFlag "msse2"        (noArg (\d ->
3539                                                  d { sseVersion = Just SSE2 }))
3540  , make_ord_flag defGhcFlag "msse3"        (noArg (\d ->
3541                                                  d { sseVersion = Just SSE3 }))
3542  , make_ord_flag defGhcFlag "msse4"        (noArg (\d ->
3543                                                  d { sseVersion = Just SSE4 }))
3544  , make_ord_flag defGhcFlag "msse4.2"      (noArg (\d ->
3545                                                 d { sseVersion = Just SSE42 }))
3546  , make_ord_flag defGhcFlag "mbmi"         (noArg (\d ->
3547                                                 d { bmiVersion = Just BMI1 }))
3548  , make_ord_flag defGhcFlag "mbmi2"        (noArg (\d ->
3549                                                 d { bmiVersion = Just BMI2 }))
3550  , make_ord_flag defGhcFlag "mavx"         (noArg (\d -> d { avx = True }))
3551  , make_ord_flag defGhcFlag "mavx2"        (noArg (\d -> d { avx2 = True }))
3552  , make_ord_flag defGhcFlag "mavx512cd"    (noArg (\d ->
3553                                                         d { avx512cd = True }))
3554  , make_ord_flag defGhcFlag "mavx512er"    (noArg (\d ->
3555                                                         d { avx512er = True }))
3556  , make_ord_flag defGhcFlag "mavx512f"     (noArg (\d -> d { avx512f = True }))
3557  , make_ord_flag defGhcFlag "mavx512pf"    (noArg (\d ->
3558                                                         d { avx512pf = True }))
3559
3560     ------ Warning opts -------------------------------------------------
3561  , make_ord_flag defFlag "W"       (NoArg (mapM_ setWarningFlag minusWOpts))
3562  , make_ord_flag defFlag "Werror"
3563               (NoArg (do { setGeneralFlag Opt_WarnIsError
3564                          ; mapM_ setFatalWarningFlag minusWeverythingOpts   }))
3565  , make_ord_flag defFlag "Wwarn"
3566               (NoArg (do { unSetGeneralFlag Opt_WarnIsError
3567                          ; mapM_ unSetFatalWarningFlag minusWeverythingOpts }))
3568                          -- Opt_WarnIsError is still needed to pass -Werror
3569                          -- to CPP; see runCpp in SysTools
3570  , make_dep_flag defFlag "Wnot"    (NoArg (upd (\d ->
3571                                              d {warningFlags = EnumSet.empty})))
3572                                             "Use -w or -Wno-everything instead"
3573  , make_ord_flag defFlag "w"       (NoArg (upd (\d ->
3574                                              d {warningFlags = EnumSet.empty})))
3575
3576     -- New-style uniform warning sets
3577     --
3578     -- Note that -Weverything > -Wall > -Wextra > -Wdefault > -Wno-everything
3579  , make_ord_flag defFlag "Weverything"    (NoArg (mapM_
3580                                           setWarningFlag minusWeverythingOpts))
3581  , make_ord_flag defFlag "Wno-everything"
3582                           (NoArg (upd (\d -> d {warningFlags = EnumSet.empty})))
3583
3584  , make_ord_flag defFlag "Wall"           (NoArg (mapM_
3585                                                  setWarningFlag minusWallOpts))
3586  , make_ord_flag defFlag "Wno-all"        (NoArg (mapM_
3587                                                unSetWarningFlag minusWallOpts))
3588
3589  , make_ord_flag defFlag "Wextra"         (NoArg (mapM_
3590                                                     setWarningFlag minusWOpts))
3591  , make_ord_flag defFlag "Wno-extra"      (NoArg (mapM_
3592                                                   unSetWarningFlag minusWOpts))
3593
3594  , make_ord_flag defFlag "Wdefault"       (NoArg (mapM_
3595                                               setWarningFlag standardWarnings))
3596  , make_ord_flag defFlag "Wno-default"    (NoArg (mapM_
3597                                             unSetWarningFlag standardWarnings))
3598
3599  , make_ord_flag defFlag "Wcompat"        (NoArg (mapM_
3600                                               setWarningFlag minusWcompatOpts))
3601  , make_ord_flag defFlag "Wno-compat"     (NoArg (mapM_
3602                                             unSetWarningFlag minusWcompatOpts))
3603
3604        ------ Plugin flags ------------------------------------------------
3605  , make_ord_flag defGhcFlag "fplugin-opt" (hasArg addPluginModuleNameOption)
3606  , make_ord_flag defGhcFlag "fplugin-trustworthy"
3607      (NoArg (setGeneralFlag Opt_PluginTrustworthy))
3608  , make_ord_flag defGhcFlag "fplugin"     (hasArg addPluginModuleName)
3609  , make_ord_flag defGhcFlag "fclear-plugins" (noArg clearPluginModuleNames)
3610  , make_ord_flag defGhcFlag "ffrontend-opt" (hasArg addFrontendPluginOption)
3611
3612        ------ Optimisation flags ------------------------------------------
3613  , make_dep_flag defGhcFlag "Onot"   (noArgM $ setOptLevel 0 )
3614                                                            "Use -O0 instead"
3615  , make_ord_flag defGhcFlag "O"      (optIntSuffixM (\mb_n ->
3616                                                setOptLevel (mb_n `orElse` 1)))
3617                -- If the number is missing, use 1
3618
3619  , make_ord_flag defFlag "fbinary-blob-threshold"
3620      (intSuffix (\n d -> d { binBlobThreshold = fromIntegral n }))
3621
3622  , make_ord_flag defFlag "fmax-relevant-binds"
3623      (intSuffix (\n d -> d { maxRelevantBinds = Just n }))
3624  , make_ord_flag defFlag "fno-max-relevant-binds"
3625      (noArg (\d -> d { maxRelevantBinds = Nothing }))
3626
3627  , make_ord_flag defFlag "fmax-valid-hole-fits"
3628      (intSuffix (\n d -> d { maxValidHoleFits = Just n }))
3629  , make_ord_flag defFlag "fno-max-valid-hole-fits"
3630      (noArg (\d -> d { maxValidHoleFits = Nothing }))
3631  , make_ord_flag defFlag "fmax-refinement-hole-fits"
3632      (intSuffix (\n d -> d { maxRefHoleFits = Just n }))
3633  , make_ord_flag defFlag "fno-max-refinement-hole-fits"
3634      (noArg (\d -> d { maxRefHoleFits = Nothing }))
3635  , make_ord_flag defFlag "frefinement-level-hole-fits"
3636      (intSuffix (\n d -> d { refLevelHoleFits = Just n }))
3637  , make_ord_flag defFlag "fno-refinement-level-hole-fits"
3638      (noArg (\d -> d { refLevelHoleFits = Nothing }))
3639
3640  , make_dep_flag defGhcFlag "fllvm-pass-vectors-in-regs"
3641            (noArg id)
3642            "vectors registers are now passed in registers by default."
3643  , make_ord_flag defFlag "fmax-uncovered-patterns"
3644      (intSuffix (\n d -> d { maxUncoveredPatterns = n }))
3645  , make_ord_flag defFlag "fmax-pmcheck-models"
3646      (intSuffix (\n d -> d { maxPmCheckModels = n }))
3647  , make_ord_flag defFlag "fsimplifier-phases"
3648      (intSuffix (\n d -> d { simplPhases = n }))
3649  , make_ord_flag defFlag "fmax-simplifier-iterations"
3650      (intSuffix (\n d -> d { maxSimplIterations = n }))
3651  , (Deprecated, defFlag "fmax-pmcheck-iterations"
3652      (intSuffixM (\_ d ->
3653       do { deprecate $ "use -fmax-pmcheck-models instead"
3654          ; return d })))
3655  , make_ord_flag defFlag "fsimpl-tick-factor"
3656      (intSuffix (\n d -> d { simplTickFactor = n }))
3657  , make_ord_flag defFlag "fspec-constr-threshold"
3658      (intSuffix (\n d -> d { specConstrThreshold = Just n }))
3659  , make_ord_flag defFlag "fno-spec-constr-threshold"
3660      (noArg (\d -> d { specConstrThreshold = Nothing }))
3661  , make_ord_flag defFlag "fspec-constr-count"
3662      (intSuffix (\n d -> d { specConstrCount = Just n }))
3663  , make_ord_flag defFlag "fno-spec-constr-count"
3664      (noArg (\d -> d { specConstrCount = Nothing }))
3665  , make_ord_flag defFlag "fspec-constr-recursive"
3666      (intSuffix (\n d -> d { specConstrRecursive = n }))
3667  , make_ord_flag defFlag "fliberate-case-threshold"
3668      (intSuffix (\n d -> d { liberateCaseThreshold = Just n }))
3669  , make_ord_flag defFlag "fno-liberate-case-threshold"
3670      (noArg (\d -> d { liberateCaseThreshold = Nothing }))
3671  , make_ord_flag defFlag "drule-check"
3672      (sepArg (\s d -> d { ruleCheck = Just s }))
3673  , make_ord_flag defFlag "dinline-check"
3674      (sepArg (\s d -> d { inlineCheck = Just s }))
3675  , make_ord_flag defFlag "freduction-depth"
3676      (intSuffix (\n d -> d { reductionDepth = treatZeroAsInf n }))
3677  , make_ord_flag defFlag "fconstraint-solver-iterations"
3678      (intSuffix (\n d -> d { solverIterations = treatZeroAsInf n }))
3679  , (Deprecated, defFlag "fcontext-stack"
3680      (intSuffixM (\n d ->
3681       do { deprecate $ "use -freduction-depth=" ++ show n ++ " instead"
3682          ; return $ d { reductionDepth = treatZeroAsInf n } })))
3683  , (Deprecated, defFlag "ftype-function-depth"
3684      (intSuffixM (\n d ->
3685       do { deprecate $ "use -freduction-depth=" ++ show n ++ " instead"
3686          ; return $ d { reductionDepth = treatZeroAsInf n } })))
3687  , make_ord_flag defFlag "fstrictness-before"
3688      (intSuffix (\n d -> d { strictnessBefore = n : strictnessBefore d }))
3689  , make_ord_flag defFlag "ffloat-lam-args"
3690      (intSuffix (\n d -> d { floatLamArgs = Just n }))
3691  , make_ord_flag defFlag "ffloat-all-lams"
3692      (noArg (\d -> d { floatLamArgs = Nothing }))
3693  , make_ord_flag defFlag "fstg-lift-lams-rec-args"
3694      (intSuffix (\n d -> d { liftLamsRecArgs = Just n }))
3695  , make_ord_flag defFlag "fstg-lift-lams-rec-args-any"
3696      (noArg (\d -> d { liftLamsRecArgs = Nothing }))
3697  , make_ord_flag defFlag "fstg-lift-lams-non-rec-args"
3698      (intSuffix (\n d -> d { liftLamsRecArgs = Just n }))
3699  , make_ord_flag defFlag "fstg-lift-lams-non-rec-args-any"
3700      (noArg (\d -> d { liftLamsRecArgs = Nothing }))
3701  , make_ord_flag defFlag "fstg-lift-lams-known"
3702      (noArg (\d -> d { liftLamsKnown = True }))
3703  , make_ord_flag defFlag "fno-stg-lift-lams-known"
3704      (noArg (\d -> d { liftLamsKnown = False }))
3705  , make_ord_flag defFlag "fproc-alignment"
3706      (intSuffix (\n d -> d { cmmProcAlignment = Just n }))
3707  , make_ord_flag defFlag "fblock-layout-weights"
3708        (HasArg (\s ->
3709            upd (\d -> d { cfgWeightInfo =
3710                parseCfgWeights s (cfgWeightInfo d)})))
3711  , make_ord_flag defFlag "fhistory-size"
3712      (intSuffix (\n d -> d { historySize = n }))
3713  , make_ord_flag defFlag "funfolding-creation-threshold"
3714      (intSuffix   (\n d -> d {ufCreationThreshold = n}))
3715  , make_ord_flag defFlag "funfolding-use-threshold"
3716      (intSuffix   (\n d -> d {ufUseThreshold = n}))
3717  , make_ord_flag defFlag "funfolding-fun-discount"
3718      (intSuffix   (\n d -> d {ufFunAppDiscount = n}))
3719  , make_ord_flag defFlag "funfolding-dict-discount"
3720      (intSuffix   (\n d -> d {ufDictDiscount = n}))
3721  , make_ord_flag defFlag "funfolding-keeness-factor"
3722      (floatSuffix (\n d -> d {ufKeenessFactor = n}))
3723  , make_ord_flag defFlag "fmax-worker-args"
3724      (intSuffix (\n d -> d {maxWorkerArgs = n}))
3725  , make_ord_flag defGhciFlag "fghci-hist-size"
3726      (intSuffix (\n d -> d {ghciHistSize = n}))
3727  , make_ord_flag defGhcFlag "fmax-inline-alloc-size"
3728      (intSuffix (\n d -> d { maxInlineAllocSize = n }))
3729  , make_ord_flag defGhcFlag "fmax-inline-memcpy-insns"
3730      (intSuffix (\n d -> d { maxInlineMemcpyInsns = n }))
3731  , make_ord_flag defGhcFlag "fmax-inline-memset-insns"
3732      (intSuffix (\n d -> d { maxInlineMemsetInsns = n }))
3733  , make_ord_flag defGhcFlag "dinitial-unique"
3734      (intSuffix (\n d -> d { initialUnique = n }))
3735  , make_ord_flag defGhcFlag "dunique-increment"
3736      (intSuffix (\n d -> d { uniqueIncrement = n }))
3737
3738        ------ Profiling ----------------------------------------------------
3739
3740        -- OLD profiling flags
3741  , make_dep_flag defGhcFlag "auto-all"
3742                    (noArg (\d -> d { profAuto = ProfAutoAll } ))
3743                    "Use -fprof-auto instead"
3744  , make_dep_flag defGhcFlag "no-auto-all"
3745                    (noArg (\d -> d { profAuto = NoProfAuto } ))
3746                    "Use -fno-prof-auto instead"
3747  , make_dep_flag defGhcFlag "auto"
3748                    (noArg (\d -> d { profAuto = ProfAutoExports } ))
3749                    "Use -fprof-auto-exported instead"
3750  , make_dep_flag defGhcFlag "no-auto"
3751            (noArg (\d -> d { profAuto = NoProfAuto } ))
3752                    "Use -fno-prof-auto instead"
3753  , make_dep_flag defGhcFlag "caf-all"
3754            (NoArg (setGeneralFlag Opt_AutoSccsOnIndividualCafs))
3755                    "Use -fprof-cafs instead"
3756  , make_dep_flag defGhcFlag "no-caf-all"
3757            (NoArg (unSetGeneralFlag Opt_AutoSccsOnIndividualCafs))
3758                    "Use -fno-prof-cafs instead"
3759
3760        -- NEW profiling flags
3761  , make_ord_flag defGhcFlag "fprof-auto"
3762      (noArg (\d -> d { profAuto = ProfAutoAll } ))
3763  , make_ord_flag defGhcFlag "fprof-auto-top"
3764      (noArg (\d -> d { profAuto = ProfAutoTop } ))
3765  , make_ord_flag defGhcFlag "fprof-auto-exported"
3766      (noArg (\d -> d { profAuto = ProfAutoExports } ))
3767  , make_ord_flag defGhcFlag "fprof-auto-calls"
3768      (noArg (\d -> d { profAuto = ProfAutoCalls } ))
3769  , make_ord_flag defGhcFlag "fno-prof-auto"
3770      (noArg (\d -> d { profAuto = NoProfAuto } ))
3771
3772        ------ Compiler flags -----------------------------------------------
3773
3774  , make_ord_flag defGhcFlag "fasm"             (NoArg (setObjTarget HscAsm))
3775  , make_ord_flag defGhcFlag "fvia-c"           (NoArg
3776         (deprecate $ "The -fvia-c flag does nothing; " ++
3777                      "it will be removed in a future GHC release"))
3778  , make_ord_flag defGhcFlag "fvia-C"           (NoArg
3779         (deprecate $ "The -fvia-C flag does nothing; " ++
3780                      "it will be removed in a future GHC release"))
3781  , make_ord_flag defGhcFlag "fllvm"            (NoArg (setObjTarget HscLlvm))
3782
3783  , make_ord_flag defFlag "fno-code"         (NoArg ((upd $ \d ->
3784                  d { ghcLink=NoLink }) >> setTarget HscNothing))
3785  , make_ord_flag defFlag "fbyte-code"       (NoArg ((upd $ \d ->
3786      -- Enabling Opt_ByteCodeIfUnboxed is a workaround for #18955.
3787      -- See the comments for resetOptByteCodeIfUnboxed for more details.
3788      gopt_set d Opt_ByteCodeIfUnboxed) >> setTarget HscInterpreted))
3789  , make_ord_flag defFlag "fobject-code"     $ NoArg $ do
3790      dflags <- liftEwM getCmdLineState
3791      setTarget $ defaultObjectTarget dflags
3792
3793  , make_dep_flag defFlag "fglasgow-exts"
3794      (NoArg enableGlasgowExts) "Use individual extensions instead"
3795  , make_dep_flag defFlag "fno-glasgow-exts"
3796      (NoArg disableGlasgowExts) "Use individual extensions instead"
3797  , make_ord_flag defFlag "Wunused-binds" (NoArg enableUnusedBinds)
3798  , make_ord_flag defFlag "Wno-unused-binds" (NoArg disableUnusedBinds)
3799  , make_ord_flag defHiddenFlag "fwarn-unused-binds" (NoArg enableUnusedBinds)
3800  , make_ord_flag defHiddenFlag "fno-warn-unused-binds" (NoArg
3801                                                            disableUnusedBinds)
3802
3803        ------ Safe Haskell flags -------------------------------------------
3804  , make_ord_flag defFlag "fpackage-trust"   (NoArg setPackageTrust)
3805  , make_ord_flag defFlag "fno-safe-infer"   (noArg (\d ->
3806                                                    d { safeInfer = False }))
3807  , make_ord_flag defFlag "fno-safe-haskell" (NoArg (setSafeHaskell Sf_Ignore))
3808
3809        ------ position independent flags  ----------------------------------
3810  , make_ord_flag defGhcFlag "fPIC"          (NoArg (setGeneralFlag Opt_PIC))
3811  , make_ord_flag defGhcFlag "fno-PIC"       (NoArg (unSetGeneralFlag Opt_PIC))
3812  , make_ord_flag defGhcFlag "fPIE"          (NoArg (setGeneralFlag Opt_PIC))
3813  , make_ord_flag defGhcFlag "fno-PIE"       (NoArg (unSetGeneralFlag Opt_PIC))
3814
3815         ------ Debugging flags ----------------------------------------------
3816  , make_ord_flag defGhcFlag "g"             (OptIntSuffix setDebugLevel)
3817 ]
3818 ++ map (mkFlag turnOn  ""          setGeneralFlag    ) negatableFlagsDeps
3819 ++ map (mkFlag turnOff "no-"       unSetGeneralFlag  ) negatableFlagsDeps
3820 ++ map (mkFlag turnOn  "d"         setGeneralFlag    ) dFlagsDeps
3821 ++ map (mkFlag turnOff "dno-"      unSetGeneralFlag  ) dFlagsDeps
3822 ++ map (mkFlag turnOn  "f"         setGeneralFlag    ) fFlagsDeps
3823 ++ map (mkFlag turnOff "fno-"      unSetGeneralFlag  ) fFlagsDeps
3824 ++ map (mkFlag turnOn  "W"         setWarningFlag    ) wWarningFlagsDeps
3825 ++ map (mkFlag turnOff "Wno-"      unSetWarningFlag  ) wWarningFlagsDeps
3826 ++ map (mkFlag turnOn  "Werror="   setWErrorFlag )     wWarningFlagsDeps
3827 ++ map (mkFlag turnOn  "Wwarn="     unSetFatalWarningFlag )
3828                                                        wWarningFlagsDeps
3829 ++ map (mkFlag turnOn  "Wno-error=" unSetFatalWarningFlag )
3830                                                        wWarningFlagsDeps
3831 ++ map (mkFlag turnOn  "fwarn-"    setWarningFlag   . hideFlag)
3832    wWarningFlagsDeps
3833 ++ map (mkFlag turnOff "fno-warn-" unSetWarningFlag . hideFlag)
3834    wWarningFlagsDeps
3835 ++ [ (NotDeprecated, unrecognisedWarning "W"),
3836      (Deprecated,    unrecognisedWarning "fwarn-"),
3837      (Deprecated,    unrecognisedWarning "fno-warn-") ]
3838 ++ [ make_ord_flag defFlag "Werror=compat"
3839        (NoArg (mapM_ setWErrorFlag minusWcompatOpts))
3840    , make_ord_flag defFlag "Wno-error=compat"
3841        (NoArg (mapM_ unSetFatalWarningFlag minusWcompatOpts))
3842    , make_ord_flag defFlag "Wwarn=compat"
3843        (NoArg (mapM_ unSetFatalWarningFlag minusWcompatOpts)) ]
3844 ++ map (mkFlag turnOn  "f"         setExtensionFlag  ) fLangFlagsDeps
3845 ++ map (mkFlag turnOff "fno-"      unSetExtensionFlag) fLangFlagsDeps
3846 ++ map (mkFlag turnOn  "X"         setExtensionFlag  ) xFlagsDeps
3847 ++ map (mkFlag turnOff "XNo"       unSetExtensionFlag) xFlagsDeps
3848 ++ map (mkFlag turnOn  "X"         setLanguage       ) languageFlagsDeps
3849 ++ map (mkFlag turnOn  "X"         setSafeHaskell    ) safeHaskellFlagsDeps
3850 ++ [ make_dep_flag defFlag "XGenerics"
3851        (NoArg $ return ())
3852                  ("it does nothing; look into -XDefaultSignatures " ++
3853                   "and -XDeriveGeneric for generic programming support.")
3854    , make_dep_flag defFlag "XNoGenerics"
3855        (NoArg $ return ())
3856               ("it does nothing; look into -XDefaultSignatures and " ++
3857                  "-XDeriveGeneric for generic programming support.") ]
3858
3859-- | This is where we handle unrecognised warning flags. We only issue a warning
3860-- if -Wunrecognised-warning-flags is set. See #11429 for context.
3861unrecognisedWarning :: String -> Flag (CmdLineP DynFlags)
3862unrecognisedWarning prefix = defHiddenFlag prefix (Prefix action)
3863  where
3864    action :: String -> EwM (CmdLineP DynFlags) ()
3865    action flag = do
3866      f <- wopt Opt_WarnUnrecognisedWarningFlags <$> liftEwM getCmdLineState
3867      when f $ addFlagWarn Cmd.ReasonUnrecognisedFlag $
3868        "unrecognised warning flag: -" ++ prefix ++ flag
3869
3870-- See Note [Supporting CLI completion]
3871package_flags_deps :: [(Deprecation, Flag (CmdLineP DynFlags))]
3872package_flags_deps = [
3873        ------- Packages ----------------------------------------------------
3874    make_ord_flag defFlag "package-db"
3875      (HasArg (addPkgConfRef . PkgConfFile))
3876  , make_ord_flag defFlag "clear-package-db"      (NoArg clearPkgConf)
3877  , make_ord_flag defFlag "no-global-package-db"  (NoArg removeGlobalPkgConf)
3878  , make_ord_flag defFlag "no-user-package-db"    (NoArg removeUserPkgConf)
3879  , make_ord_flag defFlag "global-package-db"
3880      (NoArg (addPkgConfRef GlobalPkgConf))
3881  , make_ord_flag defFlag "user-package-db"
3882      (NoArg (addPkgConfRef UserPkgConf))
3883    -- backwards compat with GHC<=7.4 :
3884  , make_dep_flag defFlag "package-conf"
3885      (HasArg $ addPkgConfRef . PkgConfFile) "Use -package-db instead"
3886  , make_dep_flag defFlag "no-user-package-conf"
3887      (NoArg removeUserPkgConf)              "Use -no-user-package-db instead"
3888  , make_ord_flag defGhcFlag "package-name"       (HasArg $ \name -> do
3889                                      upd (setUnitId name))
3890                                      -- TODO: Since we JUST deprecated
3891                                      -- -this-package-key, let's keep this
3892                                      -- undeprecated for another cycle.
3893                                      -- Deprecate this eventually.
3894                                      -- deprecate "Use -this-unit-id instead")
3895  , make_dep_flag defGhcFlag "this-package-key"   (HasArg $ upd . setUnitId)
3896                                                  "Use -this-unit-id instead"
3897  , make_ord_flag defGhcFlag "this-unit-id"       (hasArg setUnitId)
3898  , make_ord_flag defFlag "package"               (HasArg exposePackage)
3899  , make_ord_flag defFlag "plugin-package-id"     (HasArg exposePluginPackageId)
3900  , make_ord_flag defFlag "plugin-package"        (HasArg exposePluginPackage)
3901  , make_ord_flag defFlag "package-id"            (HasArg exposePackageId)
3902  , make_ord_flag defFlag "hide-package"          (HasArg hidePackage)
3903  , make_ord_flag defFlag "hide-all-packages"
3904      (NoArg (setGeneralFlag Opt_HideAllPackages))
3905  , make_ord_flag defFlag "hide-all-plugin-packages"
3906      (NoArg (setGeneralFlag Opt_HideAllPluginPackages))
3907  , make_ord_flag defFlag "package-env"           (HasArg setPackageEnv)
3908  , make_ord_flag defFlag "ignore-package"        (HasArg ignorePackage)
3909  , make_dep_flag defFlag "syslib" (HasArg exposePackage) "Use -package instead"
3910  , make_ord_flag defFlag "distrust-all-packages"
3911      (NoArg (setGeneralFlag Opt_DistrustAllPackages))
3912  , make_ord_flag defFlag "trust"                 (HasArg trustPackage)
3913  , make_ord_flag defFlag "distrust"              (HasArg distrustPackage)
3914  ]
3915  where
3916    setPackageEnv env = upd $ \s -> s { packageEnv = Just env }
3917
3918-- | Make a list of flags for shell completion.
3919-- Filter all available flags into two groups, for interactive GHC vs all other.
3920flagsForCompletion :: Bool -> [String]
3921flagsForCompletion isInteractive
3922    = [ '-':flagName flag
3923      | flag <- flagsAll
3924      , modeFilter (flagGhcMode flag)
3925      ]
3926    where
3927      modeFilter AllModes = True
3928      modeFilter OnlyGhci = isInteractive
3929      modeFilter OnlyGhc = not isInteractive
3930      modeFilter HiddenFlag = False
3931
3932type TurnOnFlag = Bool   -- True  <=> we are turning the flag on
3933                         -- False <=> we are turning the flag off
3934turnOn  :: TurnOnFlag; turnOn  = True
3935turnOff :: TurnOnFlag; turnOff = False
3936
3937data FlagSpec flag
3938   = FlagSpec
3939       { flagSpecName :: String   -- ^ Flag in string form
3940       , flagSpecFlag :: flag     -- ^ Flag in internal form
3941       , flagSpecAction :: (TurnOnFlag -> DynP ())
3942           -- ^ Extra action to run when the flag is found
3943           -- Typically, emit a warning or error
3944       , flagSpecGhcMode :: GhcFlagMode
3945           -- ^ In which ghc mode the flag has effect
3946       }
3947
3948-- | Define a new flag.
3949flagSpec :: String -> flag -> (Deprecation, FlagSpec flag)
3950flagSpec name flag = flagSpec' name flag nop
3951
3952-- | Define a new flag with an effect.
3953flagSpec' :: String -> flag -> (TurnOnFlag -> DynP ())
3954          -> (Deprecation, FlagSpec flag)
3955flagSpec' name flag act = (NotDeprecated, FlagSpec name flag act AllModes)
3956
3957-- | Define a new deprecated flag with an effect.
3958depFlagSpecOp :: String -> flag -> (TurnOnFlag -> DynP ()) -> String
3959            -> (Deprecation, FlagSpec flag)
3960depFlagSpecOp name flag act dep =
3961    (Deprecated, snd (flagSpec' name flag (\f -> act f >> deprecate dep)))
3962
3963-- | Define a new deprecated flag.
3964depFlagSpec :: String -> flag -> String
3965            -> (Deprecation, FlagSpec flag)
3966depFlagSpec name flag dep = depFlagSpecOp name flag nop dep
3967
3968-- | Define a new deprecated flag with an effect where the deprecation message
3969-- depends on the flag value
3970depFlagSpecOp' :: String
3971             -> flag
3972             -> (TurnOnFlag -> DynP ())
3973             -> (TurnOnFlag -> String)
3974             -> (Deprecation, FlagSpec flag)
3975depFlagSpecOp' name flag act dep =
3976    (Deprecated, FlagSpec name flag (\f -> act f >> (deprecate $ dep f))
3977                                                                       AllModes)
3978
3979-- | Define a new deprecated flag where the deprecation message
3980-- depends on the flag value
3981depFlagSpec' :: String
3982             -> flag
3983             -> (TurnOnFlag -> String)
3984             -> (Deprecation, FlagSpec flag)
3985depFlagSpec' name flag dep = depFlagSpecOp' name flag nop dep
3986
3987
3988-- | Define a new deprecated flag where the deprecation message
3989-- is shown depending on the flag value
3990depFlagSpecCond :: String
3991                -> flag
3992                -> (TurnOnFlag -> Bool)
3993                -> String
3994                -> (Deprecation, FlagSpec flag)
3995depFlagSpecCond name flag cond dep =
3996    (Deprecated, FlagSpec name flag (\f -> when (cond f) $ deprecate dep)
3997                                                                       AllModes)
3998
3999-- | Define a new flag for GHCi.
4000flagGhciSpec :: String -> flag -> (Deprecation, FlagSpec flag)
4001flagGhciSpec name flag = flagGhciSpec' name flag nop
4002
4003-- | Define a new flag for GHCi with an effect.
4004flagGhciSpec' :: String -> flag -> (TurnOnFlag -> DynP ())
4005              -> (Deprecation, FlagSpec flag)
4006flagGhciSpec' name flag act = (NotDeprecated, FlagSpec name flag act OnlyGhci)
4007
4008-- | Define a new flag invisible to CLI completion.
4009flagHiddenSpec :: String -> flag -> (Deprecation, FlagSpec flag)
4010flagHiddenSpec name flag = flagHiddenSpec' name flag nop
4011
4012-- | Define a new flag invisible to CLI completion with an effect.
4013flagHiddenSpec' :: String -> flag -> (TurnOnFlag -> DynP ())
4014                -> (Deprecation, FlagSpec flag)
4015flagHiddenSpec' name flag act = (NotDeprecated, FlagSpec name flag act
4016                                                                     HiddenFlag)
4017
4018-- | Hide a 'FlagSpec' from being displayed in @--show-options@.
4019--
4020-- This is for example useful for flags that are obsolete, but should not
4021-- (yet) be deprecated for compatibility reasons.
4022hideFlag :: (Deprecation, FlagSpec a) -> (Deprecation, FlagSpec a)
4023hideFlag (dep, fs) = (dep, fs { flagSpecGhcMode = HiddenFlag })
4024
4025mkFlag :: TurnOnFlag            -- ^ True <=> it should be turned on
4026       -> String                -- ^ The flag prefix
4027       -> (flag -> DynP ())     -- ^ What to do when the flag is found
4028       -> (Deprecation, FlagSpec flag)  -- ^ Specification of
4029                                        -- this particular flag
4030       -> (Deprecation, Flag (CmdLineP DynFlags))
4031mkFlag turn_on flagPrefix f (dep, (FlagSpec name flag extra_action mode))
4032    = (dep,
4033       Flag (flagPrefix ++ name) (NoArg (f flag >> extra_action turn_on)) mode)
4034
4035deprecatedForExtension :: String -> TurnOnFlag -> String
4036deprecatedForExtension lang turn_on
4037    = "use -X" ++ flag ++
4038      " or pragma {-# LANGUAGE " ++ flag ++ " #-} instead"
4039    where
4040      flag | turn_on   = lang
4041           | otherwise = "No" ++ lang
4042
4043useInstead :: String -> String -> TurnOnFlag -> String
4044useInstead prefix flag turn_on
4045  = "Use " ++ prefix ++ no ++ flag ++ " instead"
4046  where
4047    no = if turn_on then "" else "no-"
4048
4049nop :: TurnOnFlag -> DynP ()
4050nop _ = return ()
4051
4052-- | Find the 'FlagSpec' for a 'WarningFlag'.
4053flagSpecOf :: WarningFlag -> Maybe (FlagSpec WarningFlag)
4054flagSpecOf flag = listToMaybe $ filter check wWarningFlags
4055  where
4056    check fs = flagSpecFlag fs == flag
4057
4058-- | These @-W\<blah\>@ flags can all be reversed with @-Wno-\<blah\>@
4059wWarningFlags :: [FlagSpec WarningFlag]
4060wWarningFlags = map snd (sortBy (comparing fst) wWarningFlagsDeps)
4061
4062wWarningFlagsDeps :: [(Deprecation, FlagSpec WarningFlag)]
4063wWarningFlagsDeps = [
4064-- See Note [Updating flag description in the User's Guide]
4065-- See Note [Supporting CLI completion]
4066-- Please keep the list of flags below sorted alphabetically
4067  flagSpec "alternative-layout-rule-transitional"
4068                                      Opt_WarnAlternativeLayoutRuleTransitional,
4069  depFlagSpec "auto-orphans"             Opt_WarnAutoOrphans
4070    "it has no effect",
4071  flagSpec "cpp-undef"                   Opt_WarnCPPUndef,
4072  flagSpec "unbanged-strict-patterns"    Opt_WarnUnbangedStrictPatterns,
4073  flagSpec "deferred-type-errors"        Opt_WarnDeferredTypeErrors,
4074  flagSpec "deferred-out-of-scope-variables"
4075                                         Opt_WarnDeferredOutOfScopeVariables,
4076  flagSpec "deprecations"                Opt_WarnWarningsDeprecations,
4077  flagSpec "deprecated-flags"            Opt_WarnDeprecatedFlags,
4078  flagSpec "deriving-defaults"           Opt_WarnDerivingDefaults,
4079  flagSpec "deriving-typeable"           Opt_WarnDerivingTypeable,
4080  flagSpec "dodgy-exports"               Opt_WarnDodgyExports,
4081  flagSpec "dodgy-foreign-imports"       Opt_WarnDodgyForeignImports,
4082  flagSpec "dodgy-imports"               Opt_WarnDodgyImports,
4083  flagSpec "empty-enumerations"          Opt_WarnEmptyEnumerations,
4084  depFlagSpec "duplicate-constraints"    Opt_WarnDuplicateConstraints
4085    "it is subsumed by -Wredundant-constraints",
4086  flagSpec "redundant-constraints"       Opt_WarnRedundantConstraints,
4087  flagSpec "duplicate-exports"           Opt_WarnDuplicateExports,
4088  depFlagSpec "hi-shadowing"                Opt_WarnHiShadows
4089    "it is not used, and was never implemented",
4090  flagSpec "inaccessible-code"           Opt_WarnInaccessibleCode,
4091  flagSpec "implicit-prelude"            Opt_WarnImplicitPrelude,
4092  depFlagSpec "implicit-kind-vars"       Opt_WarnImplicitKindVars
4093    "it is now an error",
4094  flagSpec "incomplete-patterns"         Opt_WarnIncompletePatterns,
4095  flagSpec "incomplete-record-updates"   Opt_WarnIncompletePatternsRecUpd,
4096  flagSpec "incomplete-uni-patterns"     Opt_WarnIncompleteUniPatterns,
4097  flagSpec "inline-rule-shadowing"       Opt_WarnInlineRuleShadowing,
4098  flagSpec "identities"                  Opt_WarnIdentities,
4099  flagSpec "missing-fields"              Opt_WarnMissingFields,
4100  flagSpec "missing-import-lists"        Opt_WarnMissingImportList,
4101  flagSpec "missing-export-lists"        Opt_WarnMissingExportList,
4102  depFlagSpec "missing-local-sigs"       Opt_WarnMissingLocalSignatures
4103    "it is replaced by -Wmissing-local-signatures",
4104  flagSpec "missing-local-signatures"    Opt_WarnMissingLocalSignatures,
4105  flagSpec "missing-methods"             Opt_WarnMissingMethods,
4106  flagSpec "missing-monadfail-instances" Opt_WarnMissingMonadFailInstances,
4107  flagSpec "semigroup"                   Opt_WarnSemigroup,
4108  flagSpec "missing-signatures"          Opt_WarnMissingSignatures,
4109  depFlagSpec "missing-exported-sigs"    Opt_WarnMissingExportedSignatures
4110    "it is replaced by -Wmissing-exported-signatures",
4111  flagSpec "missing-exported-signatures" Opt_WarnMissingExportedSignatures,
4112  flagSpec "monomorphism-restriction"    Opt_WarnMonomorphism,
4113  flagSpec "name-shadowing"              Opt_WarnNameShadowing,
4114  flagSpec "noncanonical-monad-instances"
4115                                         Opt_WarnNonCanonicalMonadInstances,
4116  depFlagSpec "noncanonical-monadfail-instances"
4117                                         Opt_WarnNonCanonicalMonadInstances
4118    "fail is no longer a method of Monad",
4119  flagSpec "noncanonical-monoid-instances"
4120                                         Opt_WarnNonCanonicalMonoidInstances,
4121  flagSpec "orphans"                     Opt_WarnOrphans,
4122  flagSpec "overflowed-literals"         Opt_WarnOverflowedLiterals,
4123  flagSpec "overlapping-patterns"        Opt_WarnOverlappingPatterns,
4124  flagSpec "missed-specialisations"      Opt_WarnMissedSpecs,
4125  flagSpec "missed-specializations"      Opt_WarnMissedSpecs,
4126  flagSpec "all-missed-specialisations"  Opt_WarnAllMissedSpecs,
4127  flagSpec "all-missed-specializations"  Opt_WarnAllMissedSpecs,
4128  flagSpec' "safe"                       Opt_WarnSafe setWarnSafe,
4129  flagSpec "trustworthy-safe"            Opt_WarnTrustworthySafe,
4130  flagSpec "inferred-safe-imports"       Opt_WarnInferredSafeImports,
4131  flagSpec "missing-safe-haskell-mode"   Opt_WarnMissingSafeHaskellMode,
4132  flagSpec "tabs"                        Opt_WarnTabs,
4133  flagSpec "type-defaults"               Opt_WarnTypeDefaults,
4134  flagSpec "typed-holes"                 Opt_WarnTypedHoles,
4135  flagSpec "partial-type-signatures"     Opt_WarnPartialTypeSignatures,
4136  flagSpec "unrecognised-pragmas"        Opt_WarnUnrecognisedPragmas,
4137  flagSpec' "unsafe"                     Opt_WarnUnsafe setWarnUnsafe,
4138  flagSpec "unsupported-calling-conventions"
4139                                         Opt_WarnUnsupportedCallingConventions,
4140  flagSpec "unsupported-llvm-version"    Opt_WarnUnsupportedLlvmVersion,
4141  flagSpec "missed-extra-shared-lib"     Opt_WarnMissedExtraSharedLib,
4142  flagSpec "unticked-promoted-constructors"
4143                                         Opt_WarnUntickedPromotedConstructors,
4144  flagSpec "unused-do-bind"              Opt_WarnUnusedDoBind,
4145  flagSpec "unused-foralls"              Opt_WarnUnusedForalls,
4146  flagSpec "unused-imports"              Opt_WarnUnusedImports,
4147  flagSpec "unused-local-binds"          Opt_WarnUnusedLocalBinds,
4148  flagSpec "unused-matches"              Opt_WarnUnusedMatches,
4149  flagSpec "unused-pattern-binds"        Opt_WarnUnusedPatternBinds,
4150  flagSpec "unused-top-binds"            Opt_WarnUnusedTopBinds,
4151  flagSpec "unused-type-patterns"        Opt_WarnUnusedTypePatterns,
4152  flagSpec "unused-record-wildcards"     Opt_WarnUnusedRecordWildcards,
4153  flagSpec "redundant-record-wildcards"  Opt_WarnRedundantRecordWildcards,
4154  flagSpec "warnings-deprecations"       Opt_WarnWarningsDeprecations,
4155  flagSpec "wrong-do-bind"               Opt_WarnWrongDoBind,
4156  flagSpec "missing-pattern-synonym-signatures"
4157                                    Opt_WarnMissingPatternSynonymSignatures,
4158  flagSpec "missing-deriving-strategies" Opt_WarnMissingDerivingStrategies,
4159  flagSpec "simplifiable-class-constraints" Opt_WarnSimplifiableClassConstraints,
4160  flagSpec "missing-home-modules"        Opt_WarnMissingHomeModules,
4161  flagSpec "unrecognised-warning-flags"  Opt_WarnUnrecognisedWarningFlags,
4162  flagSpec "star-binder"                 Opt_WarnStarBinder,
4163  flagSpec "star-is-type"                Opt_WarnStarIsType,
4164  flagSpec "missing-space-after-bang"    Opt_WarnSpaceAfterBang,
4165  flagSpec "partial-fields"              Opt_WarnPartialFields,
4166  flagSpec "prepositive-qualified-module"
4167                                         Opt_WarnPrepositiveQualifiedModule,
4168  flagSpec "unused-packages"             Opt_WarnUnusedPackages,
4169  flagSpec "compat-unqualified-imports"  Opt_WarnCompatUnqualifiedImports
4170 ]
4171
4172-- | These @-\<blah\>@ flags can all be reversed with @-no-\<blah\>@
4173negatableFlagsDeps :: [(Deprecation, FlagSpec GeneralFlag)]
4174negatableFlagsDeps = [
4175  flagGhciSpec "ignore-dot-ghci"         Opt_IgnoreDotGhci ]
4176
4177-- | These @-d\<blah\>@ flags can all be reversed with @-dno-\<blah\>@
4178dFlagsDeps :: [(Deprecation, FlagSpec GeneralFlag)]
4179dFlagsDeps = [
4180-- See Note [Updating flag description in the User's Guide]
4181-- See Note [Supporting CLI completion]
4182-- Please keep the list of flags below sorted alphabetically
4183  flagSpec "ppr-case-as-let"            Opt_PprCaseAsLet,
4184  depFlagSpec' "ppr-ticks"              Opt_PprShowTicks
4185     (\turn_on -> useInstead "-d" "suppress-ticks" (not turn_on)),
4186  flagSpec "suppress-ticks"             Opt_SuppressTicks,
4187  depFlagSpec' "suppress-stg-free-vars" Opt_SuppressStgExts
4188     (useInstead "-d" "suppress-stg-exts"),
4189  flagSpec "suppress-stg-exts"          Opt_SuppressStgExts,
4190  flagSpec "suppress-coercions"         Opt_SuppressCoercions,
4191  flagSpec "suppress-idinfo"            Opt_SuppressIdInfo,
4192  flagSpec "suppress-unfoldings"        Opt_SuppressUnfoldings,
4193  flagSpec "suppress-module-prefixes"   Opt_SuppressModulePrefixes,
4194  flagSpec "suppress-timestamps"        Opt_SuppressTimestamps,
4195  flagSpec "suppress-type-applications" Opt_SuppressTypeApplications,
4196  flagSpec "suppress-type-signatures"   Opt_SuppressTypeSignatures,
4197  flagSpec "suppress-uniques"           Opt_SuppressUniques,
4198  flagSpec "suppress-var-kinds"         Opt_SuppressVarKinds
4199  ]
4200
4201-- | These @-f\<blah\>@ flags can all be reversed with @-fno-\<blah\>@
4202fFlags :: [FlagSpec GeneralFlag]
4203fFlags = map snd fFlagsDeps
4204
4205fFlagsDeps :: [(Deprecation, FlagSpec GeneralFlag)]
4206fFlagsDeps = [
4207-- See Note [Updating flag description in the User's Guide]
4208-- See Note [Supporting CLI completion]
4209-- Please keep the list of flags below sorted alphabetically
4210  flagSpec "asm-shortcutting"                 Opt_AsmShortcutting,
4211  flagGhciSpec "break-on-error"               Opt_BreakOnError,
4212  flagGhciSpec "break-on-exception"           Opt_BreakOnException,
4213  flagSpec "building-cabal-package"           Opt_BuildingCabalPackage,
4214  flagSpec "call-arity"                       Opt_CallArity,
4215  flagSpec "exitification"                    Opt_Exitification,
4216  flagSpec "case-merge"                       Opt_CaseMerge,
4217  flagSpec "case-folding"                     Opt_CaseFolding,
4218  flagSpec "cmm-elim-common-blocks"           Opt_CmmElimCommonBlocks,
4219  flagSpec "cmm-sink"                         Opt_CmmSink,
4220  flagSpec "cse"                              Opt_CSE,
4221  flagSpec "stg-cse"                          Opt_StgCSE,
4222  flagSpec "stg-lift-lams"                    Opt_StgLiftLams,
4223  flagSpec "cpr-anal"                         Opt_CprAnal,
4224  flagSpec "defer-diagnostics"                Opt_DeferDiagnostics,
4225  flagSpec "defer-type-errors"                Opt_DeferTypeErrors,
4226  flagSpec "defer-typed-holes"                Opt_DeferTypedHoles,
4227  flagSpec "defer-out-of-scope-variables"     Opt_DeferOutOfScopeVariables,
4228  flagSpec "diagnostics-show-caret"           Opt_DiagnosticsShowCaret,
4229  flagSpec "dicts-cheap"                      Opt_DictsCheap,
4230  flagSpec "dicts-strict"                     Opt_DictsStrict,
4231  flagSpec "dmd-tx-dict-sel"                  Opt_DmdTxDictSel,
4232  flagSpec "do-eta-reduction"                 Opt_DoEtaReduction,
4233  flagSpec "do-lambda-eta-expansion"          Opt_DoLambdaEtaExpansion,
4234  flagSpec "eager-blackholing"                Opt_EagerBlackHoling,
4235  flagSpec "embed-manifest"                   Opt_EmbedManifest,
4236  flagSpec "enable-rewrite-rules"             Opt_EnableRewriteRules,
4237  flagSpec "enable-th-splice-warnings"        Opt_EnableThSpliceWarnings,
4238  flagSpec "error-spans"                      Opt_ErrorSpans,
4239  flagSpec "excess-precision"                 Opt_ExcessPrecision,
4240  flagSpec "expose-all-unfoldings"            Opt_ExposeAllUnfoldings,
4241  flagSpec "external-dynamic-refs"            Opt_ExternalDynamicRefs,
4242  flagSpec "external-interpreter"             Opt_ExternalInterpreter,
4243  flagSpec "flat-cache"                       Opt_FlatCache,
4244  flagSpec "float-in"                         Opt_FloatIn,
4245  flagSpec "force-recomp"                     Opt_ForceRecomp,
4246  flagSpec "ignore-optim-changes"             Opt_IgnoreOptimChanges,
4247  flagSpec "ignore-hpc-changes"               Opt_IgnoreHpcChanges,
4248  flagSpec "full-laziness"                    Opt_FullLaziness,
4249  flagSpec "fun-to-thunk"                     Opt_FunToThunk,
4250  flagSpec "gen-manifest"                     Opt_GenManifest,
4251  flagSpec "ghci-history"                     Opt_GhciHistory,
4252  flagSpec "ghci-leak-check"                  Opt_GhciLeakCheck,
4253  flagSpec "validate-ide-info"                Opt_ValidateHie,
4254  flagGhciSpec "local-ghci-history"           Opt_LocalGhciHistory,
4255  flagGhciSpec "no-it"                        Opt_NoIt,
4256  flagSpec "ghci-sandbox"                     Opt_GhciSandbox,
4257  flagSpec "helpful-errors"                   Opt_HelpfulErrors,
4258  flagSpec "hpc"                              Opt_Hpc,
4259  flagSpec "ignore-asserts"                   Opt_IgnoreAsserts,
4260  flagSpec "ignore-interface-pragmas"         Opt_IgnoreInterfacePragmas,
4261  flagGhciSpec "implicit-import-qualified"    Opt_ImplicitImportQualified,
4262  flagSpec "irrefutable-tuples"               Opt_IrrefutableTuples,
4263  flagSpec "keep-going"                       Opt_KeepGoing,
4264  flagSpec "kill-absence"                     Opt_KillAbsence,
4265  flagSpec "kill-one-shot"                    Opt_KillOneShot,
4266  flagSpec "late-dmd-anal"                    Opt_LateDmdAnal,
4267  flagSpec "late-specialise"                  Opt_LateSpecialise,
4268  flagSpec "liberate-case"                    Opt_LiberateCase,
4269  flagHiddenSpec "llvm-tbaa"                  Opt_LlvmTBAA,
4270  flagHiddenSpec "llvm-fill-undef-with-garbage" Opt_LlvmFillUndefWithGarbage,
4271  flagSpec "loopification"                    Opt_Loopification,
4272  flagSpec "block-layout-cfg"                 Opt_CfgBlocklayout,
4273  flagSpec "block-layout-weightless"          Opt_WeightlessBlocklayout,
4274  flagSpec "omit-interface-pragmas"           Opt_OmitInterfacePragmas,
4275  flagSpec "omit-yields"                      Opt_OmitYields,
4276  flagSpec "optimal-applicative-do"           Opt_OptimalApplicativeDo,
4277  flagSpec "pedantic-bottoms"                 Opt_PedanticBottoms,
4278  flagSpec "pre-inlining"                     Opt_SimplPreInlining,
4279  flagGhciSpec "print-bind-contents"          Opt_PrintBindContents,
4280  flagGhciSpec "print-bind-result"            Opt_PrintBindResult,
4281  flagGhciSpec "print-evld-with-show"         Opt_PrintEvldWithShow,
4282  flagSpec "print-explicit-foralls"           Opt_PrintExplicitForalls,
4283  flagSpec "print-explicit-kinds"             Opt_PrintExplicitKinds,
4284  flagSpec "print-explicit-coercions"         Opt_PrintExplicitCoercions,
4285  flagSpec "print-explicit-runtime-reps"      Opt_PrintExplicitRuntimeReps,
4286  flagSpec "print-equality-relations"         Opt_PrintEqualityRelations,
4287  flagSpec "print-axiom-incomps"              Opt_PrintAxiomIncomps,
4288  flagSpec "print-unicode-syntax"             Opt_PrintUnicodeSyntax,
4289  flagSpec "print-expanded-synonyms"          Opt_PrintExpandedSynonyms,
4290  flagSpec "print-potential-instances"        Opt_PrintPotentialInstances,
4291  flagSpec "print-typechecker-elaboration"    Opt_PrintTypecheckerElaboration,
4292  flagSpec "prof-cafs"                        Opt_AutoSccsOnIndividualCafs,
4293  flagSpec "prof-count-entries"               Opt_ProfCountEntries,
4294  flagSpec "regs-graph"                       Opt_RegsGraph,
4295  flagSpec "regs-iterative"                   Opt_RegsIterative,
4296  depFlagSpec' "rewrite-rules"                Opt_EnableRewriteRules
4297   (useInstead "-f" "enable-rewrite-rules"),
4298  flagSpec "shared-implib"                    Opt_SharedImplib,
4299  flagSpec "spec-constr"                      Opt_SpecConstr,
4300  flagSpec "spec-constr-keen"                 Opt_SpecConstrKeen,
4301  flagSpec "specialise"                       Opt_Specialise,
4302  flagSpec "specialize"                       Opt_Specialise,
4303  flagSpec "specialise-aggressively"          Opt_SpecialiseAggressively,
4304  flagSpec "specialize-aggressively"          Opt_SpecialiseAggressively,
4305  flagSpec "cross-module-specialise"          Opt_CrossModuleSpecialise,
4306  flagSpec "cross-module-specialize"          Opt_CrossModuleSpecialise,
4307  flagSpec "static-argument-transformation"   Opt_StaticArgumentTransformation,
4308  flagSpec "strictness"                       Opt_Strictness,
4309  flagSpec "use-rpaths"                       Opt_RPath,
4310  flagSpec "write-interface"                  Opt_WriteInterface,
4311  flagSpec "write-ide-info"                   Opt_WriteHie,
4312  flagSpec "unbox-small-strict-fields"        Opt_UnboxSmallStrictFields,
4313  flagSpec "unbox-strict-fields"              Opt_UnboxStrictFields,
4314  flagSpec "version-macros"                   Opt_VersionMacros,
4315  flagSpec "worker-wrapper"                   Opt_WorkerWrapper,
4316  flagSpec "solve-constant-dicts"             Opt_SolveConstantDicts,
4317  flagSpec "catch-bottoms"                    Opt_CatchBottoms,
4318  flagSpec "alignment-sanitisation"           Opt_AlignmentSanitisation,
4319  flagSpec "num-constant-folding"             Opt_NumConstantFolding,
4320  flagSpec "show-warning-groups"              Opt_ShowWarnGroups,
4321  flagSpec "hide-source-paths"                Opt_HideSourcePaths,
4322  flagSpec "show-loaded-modules"              Opt_ShowLoadedModules,
4323  flagSpec "whole-archive-hs-libs"            Opt_WholeArchiveHsLibs,
4324  flagSpec "keep-cafs"                        Opt_KeepCAFs
4325  ]
4326  ++ fHoleFlags
4327
4328-- | These @-f\<blah\>@ flags have to do with the typed-hole error message or
4329-- the valid hole fits in that message. See Note [Valid hole fits include ...]
4330-- in the TcHoleErrors module. These flags can all be reversed with
4331-- @-fno-\<blah\>@
4332fHoleFlags :: [(Deprecation, FlagSpec GeneralFlag)]
4333fHoleFlags = [
4334  flagSpec "show-hole-constraints"            Opt_ShowHoleConstraints,
4335  depFlagSpec' "show-valid-substitutions"     Opt_ShowValidHoleFits
4336   (useInstead "-f" "show-valid-hole-fits"),
4337  flagSpec "show-valid-hole-fits"             Opt_ShowValidHoleFits,
4338  -- Sorting settings
4339  flagSpec "sort-valid-hole-fits"             Opt_SortValidHoleFits,
4340  flagSpec "sort-by-size-hole-fits"           Opt_SortBySizeHoleFits,
4341  flagSpec "sort-by-subsumption-hole-fits"    Opt_SortBySubsumHoleFits,
4342  flagSpec "abstract-refinement-hole-fits"    Opt_AbstractRefHoleFits,
4343  -- Output format settings
4344  flagSpec "show-hole-matches-of-hole-fits"   Opt_ShowMatchesOfHoleFits,
4345  flagSpec "show-provenance-of-hole-fits"     Opt_ShowProvOfHoleFits,
4346  flagSpec "show-type-of-hole-fits"           Opt_ShowTypeOfHoleFits,
4347  flagSpec "show-type-app-of-hole-fits"       Opt_ShowTypeAppOfHoleFits,
4348  flagSpec "show-type-app-vars-of-hole-fits"  Opt_ShowTypeAppVarsOfHoleFits,
4349  flagSpec "show-docs-of-hole-fits"           Opt_ShowDocsOfHoleFits,
4350  flagSpec "unclutter-valid-hole-fits"        Opt_UnclutterValidHoleFits
4351  ]
4352
4353-- | These @-f\<blah\>@ flags can all be reversed with @-fno-\<blah\>@
4354fLangFlags :: [FlagSpec LangExt.Extension]
4355fLangFlags = map snd fLangFlagsDeps
4356
4357fLangFlagsDeps :: [(Deprecation, FlagSpec LangExt.Extension)]
4358fLangFlagsDeps = [
4359-- See Note [Updating flag description in the User's Guide]
4360-- See Note [Supporting CLI completion]
4361  depFlagSpecOp' "th"                           LangExt.TemplateHaskell
4362    checkTemplateHaskellOk
4363    (deprecatedForExtension "TemplateHaskell"),
4364  depFlagSpec' "fi"                             LangExt.ForeignFunctionInterface
4365    (deprecatedForExtension "ForeignFunctionInterface"),
4366  depFlagSpec' "ffi"                            LangExt.ForeignFunctionInterface
4367    (deprecatedForExtension "ForeignFunctionInterface"),
4368  depFlagSpec' "arrows"                         LangExt.Arrows
4369    (deprecatedForExtension "Arrows"),
4370  depFlagSpec' "implicit-prelude"               LangExt.ImplicitPrelude
4371    (deprecatedForExtension "ImplicitPrelude"),
4372  depFlagSpec' "bang-patterns"                  LangExt.BangPatterns
4373    (deprecatedForExtension "BangPatterns"),
4374  depFlagSpec' "monomorphism-restriction"       LangExt.MonomorphismRestriction
4375    (deprecatedForExtension "MonomorphismRestriction"),
4376  depFlagSpec' "mono-pat-binds"                 LangExt.MonoPatBinds
4377    (deprecatedForExtension "MonoPatBinds"),
4378  depFlagSpec' "extended-default-rules"         LangExt.ExtendedDefaultRules
4379    (deprecatedForExtension "ExtendedDefaultRules"),
4380  depFlagSpec' "implicit-params"                LangExt.ImplicitParams
4381    (deprecatedForExtension "ImplicitParams"),
4382  depFlagSpec' "scoped-type-variables"          LangExt.ScopedTypeVariables
4383    (deprecatedForExtension "ScopedTypeVariables"),
4384  depFlagSpec' "allow-overlapping-instances"    LangExt.OverlappingInstances
4385    (deprecatedForExtension "OverlappingInstances"),
4386  depFlagSpec' "allow-undecidable-instances"    LangExt.UndecidableInstances
4387    (deprecatedForExtension "UndecidableInstances"),
4388  depFlagSpec' "allow-incoherent-instances"     LangExt.IncoherentInstances
4389    (deprecatedForExtension "IncoherentInstances")
4390  ]
4391
4392supportedLanguages :: [String]
4393supportedLanguages = map (flagSpecName . snd) languageFlagsDeps
4394
4395supportedLanguageOverlays :: [String]
4396supportedLanguageOverlays = map (flagSpecName . snd) safeHaskellFlagsDeps
4397
4398supportedExtensions :: PlatformMini -> [String]
4399supportedExtensions targetPlatformMini = concatMap toFlagSpecNamePair xFlags
4400  where
4401    toFlagSpecNamePair flg
4402      -- IMPORTANT! Make sure that `ghc --supported-extensions` omits
4403      -- "TemplateHaskell"/"QuasiQuotes" when it's known not to work out of the
4404      -- box. See also GHC #11102 and #16331 for more details about
4405      -- the rationale
4406      | isAIX, flagSpecFlag flg == LangExt.TemplateHaskell  = [noName]
4407      | isAIX, flagSpecFlag flg == LangExt.QuasiQuotes      = [noName]
4408      | otherwise = [name, noName]
4409      where
4410        isAIX = platformMini_os targetPlatformMini == OSAIX
4411        noName = "No" ++ name
4412        name = flagSpecName flg
4413
4414supportedLanguagesAndExtensions :: PlatformMini -> [String]
4415supportedLanguagesAndExtensions targetPlatformMini =
4416    supportedLanguages ++ supportedLanguageOverlays ++ supportedExtensions targetPlatformMini
4417
4418-- | These -X<blah> flags cannot be reversed with -XNo<blah>
4419languageFlagsDeps :: [(Deprecation, FlagSpec Language)]
4420languageFlagsDeps = [
4421  flagSpec "Haskell98"   Haskell98,
4422  flagSpec "Haskell2010" Haskell2010
4423  ]
4424
4425-- | These -X<blah> flags cannot be reversed with -XNo<blah>
4426-- They are used to place hard requirements on what GHC Haskell language
4427-- features can be used.
4428safeHaskellFlagsDeps :: [(Deprecation, FlagSpec SafeHaskellMode)]
4429safeHaskellFlagsDeps = [mkF Sf_Unsafe, mkF Sf_Trustworthy, mkF Sf_Safe]
4430    where mkF flag = flagSpec (show flag) flag
4431
4432-- | These -X<blah> flags can all be reversed with -XNo<blah>
4433xFlags :: [FlagSpec LangExt.Extension]
4434xFlags = map snd xFlagsDeps
4435
4436xFlagsDeps :: [(Deprecation, FlagSpec LangExt.Extension)]
4437xFlagsDeps = [
4438-- See Note [Updating flag description in the User's Guide]
4439-- See Note [Supporting CLI completion]
4440-- See Note [Adding a language extension]
4441-- Please keep the list of flags below sorted alphabetically
4442  flagSpec "AllowAmbiguousTypes"              LangExt.AllowAmbiguousTypes,
4443  flagSpec "AlternativeLayoutRule"            LangExt.AlternativeLayoutRule,
4444  flagSpec "AlternativeLayoutRuleTransitional"
4445                                              LangExt.AlternativeLayoutRuleTransitional,
4446  flagSpec "Arrows"                           LangExt.Arrows,
4447  depFlagSpecCond "AutoDeriveTypeable"        LangExt.AutoDeriveTypeable
4448    id
4449         ("Typeable instances are created automatically " ++
4450                     "for all types since GHC 8.2."),
4451  flagSpec "BangPatterns"                     LangExt.BangPatterns,
4452  flagSpec "BinaryLiterals"                   LangExt.BinaryLiterals,
4453  flagSpec "CApiFFI"                          LangExt.CApiFFI,
4454  flagSpec "CPP"                              LangExt.Cpp,
4455  flagSpec "CUSKs"                            LangExt.CUSKs,
4456  flagSpec "ConstrainedClassMethods"          LangExt.ConstrainedClassMethods,
4457  flagSpec "ConstraintKinds"                  LangExt.ConstraintKinds,
4458  flagSpec "DataKinds"                        LangExt.DataKinds,
4459  depFlagSpecCond "DatatypeContexts"          LangExt.DatatypeContexts
4460    id
4461         ("It was widely considered a misfeature, " ++
4462                     "and has been removed from the Haskell language."),
4463  flagSpec "DefaultSignatures"                LangExt.DefaultSignatures,
4464  flagSpec "DeriveAnyClass"                   LangExt.DeriveAnyClass,
4465  flagSpec "DeriveDataTypeable"               LangExt.DeriveDataTypeable,
4466  flagSpec "DeriveFoldable"                   LangExt.DeriveFoldable,
4467  flagSpec "DeriveFunctor"                    LangExt.DeriveFunctor,
4468  flagSpec "DeriveGeneric"                    LangExt.DeriveGeneric,
4469  flagSpec "DeriveLift"                       LangExt.DeriveLift,
4470  flagSpec "DeriveTraversable"                LangExt.DeriveTraversable,
4471  flagSpec "DerivingStrategies"               LangExt.DerivingStrategies,
4472  flagSpec "DerivingVia"                      LangExt.DerivingVia,
4473  flagSpec "DisambiguateRecordFields"         LangExt.DisambiguateRecordFields,
4474  flagSpec "DoAndIfThenElse"                  LangExt.DoAndIfThenElse,
4475  flagSpec "BlockArguments"                   LangExt.BlockArguments,
4476  depFlagSpec' "DoRec"                        LangExt.RecursiveDo
4477    (deprecatedForExtension "RecursiveDo"),
4478  flagSpec "DuplicateRecordFields"            LangExt.DuplicateRecordFields,
4479  flagSpec "EmptyCase"                        LangExt.EmptyCase,
4480  flagSpec "EmptyDataDecls"                   LangExt.EmptyDataDecls,
4481  flagSpec "EmptyDataDeriving"                LangExt.EmptyDataDeriving,
4482  flagSpec "ExistentialQuantification"        LangExt.ExistentialQuantification,
4483  flagSpec "ExplicitForAll"                   LangExt.ExplicitForAll,
4484  flagSpec "ExplicitNamespaces"               LangExt.ExplicitNamespaces,
4485  flagSpec "ExtendedDefaultRules"             LangExt.ExtendedDefaultRules,
4486  flagSpec "FlexibleContexts"                 LangExt.FlexibleContexts,
4487  flagSpec "FlexibleInstances"                LangExt.FlexibleInstances,
4488  flagSpec "ForeignFunctionInterface"         LangExt.ForeignFunctionInterface,
4489  flagSpec "FunctionalDependencies"           LangExt.FunctionalDependencies,
4490  flagSpec "GADTSyntax"                       LangExt.GADTSyntax,
4491  flagSpec "GADTs"                            LangExt.GADTs,
4492  flagSpec "GHCForeignImportPrim"             LangExt.GHCForeignImportPrim,
4493  flagSpec' "GeneralizedNewtypeDeriving"      LangExt.GeneralizedNewtypeDeriving
4494                                              setGenDeriving,
4495  flagSpec' "GeneralisedNewtypeDeriving"      LangExt.GeneralizedNewtypeDeriving
4496                                              setGenDeriving,
4497  flagSpec "ImplicitParams"                   LangExt.ImplicitParams,
4498  flagSpec "ImplicitPrelude"                  LangExt.ImplicitPrelude,
4499  flagSpec "ImportQualifiedPost"              LangExt.ImportQualifiedPost,
4500  flagSpec "ImpredicativeTypes"               LangExt.ImpredicativeTypes,
4501  flagSpec' "IncoherentInstances"             LangExt.IncoherentInstances
4502                                              setIncoherentInsts,
4503  flagSpec "TypeFamilyDependencies"           LangExt.TypeFamilyDependencies,
4504  flagSpec "InstanceSigs"                     LangExt.InstanceSigs,
4505  flagSpec "ApplicativeDo"                    LangExt.ApplicativeDo,
4506  flagSpec "InterruptibleFFI"                 LangExt.InterruptibleFFI,
4507  flagSpec "JavaScriptFFI"                    LangExt.JavaScriptFFI,
4508  flagSpec "KindSignatures"                   LangExt.KindSignatures,
4509  flagSpec "LambdaCase"                       LangExt.LambdaCase,
4510  flagSpec "LiberalTypeSynonyms"              LangExt.LiberalTypeSynonyms,
4511  flagSpec "MagicHash"                        LangExt.MagicHash,
4512  flagSpec "MonadComprehensions"              LangExt.MonadComprehensions,
4513  depFlagSpec "MonadFailDesugaring"           LangExt.MonadFailDesugaring
4514    "MonadFailDesugaring is now the default behavior",
4515  flagSpec "MonoLocalBinds"                   LangExt.MonoLocalBinds,
4516  depFlagSpecCond "MonoPatBinds"              LangExt.MonoPatBinds
4517    id
4518         "Experimental feature now removed; has no effect",
4519  flagSpec "MonomorphismRestriction"          LangExt.MonomorphismRestriction,
4520  flagSpec "MultiParamTypeClasses"            LangExt.MultiParamTypeClasses,
4521  flagSpec "MultiWayIf"                       LangExt.MultiWayIf,
4522  flagSpec "NumericUnderscores"               LangExt.NumericUnderscores,
4523  flagSpec "NPlusKPatterns"                   LangExt.NPlusKPatterns,
4524  flagSpec "NamedFieldPuns"                   LangExt.RecordPuns,
4525  flagSpec "NamedWildCards"                   LangExt.NamedWildCards,
4526  flagSpec "NegativeLiterals"                 LangExt.NegativeLiterals,
4527  flagSpec "HexFloatLiterals"                 LangExt.HexFloatLiterals,
4528  flagSpec "NondecreasingIndentation"         LangExt.NondecreasingIndentation,
4529  depFlagSpec' "NullaryTypeClasses"           LangExt.NullaryTypeClasses
4530    (deprecatedForExtension "MultiParamTypeClasses"),
4531  flagSpec "NumDecimals"                      LangExt.NumDecimals,
4532  depFlagSpecOp "OverlappingInstances"        LangExt.OverlappingInstances
4533    setOverlappingInsts
4534    "instead use per-instance pragmas OVERLAPPING/OVERLAPPABLE/OVERLAPS",
4535  flagSpec "OverloadedLabels"                 LangExt.OverloadedLabels,
4536  flagSpec "OverloadedLists"                  LangExt.OverloadedLists,
4537  flagSpec "OverloadedStrings"                LangExt.OverloadedStrings,
4538  flagSpec "PackageImports"                   LangExt.PackageImports,
4539  flagSpec "ParallelArrays"                   LangExt.ParallelArrays,
4540  flagSpec "ParallelListComp"                 LangExt.ParallelListComp,
4541  flagSpec "PartialTypeSignatures"            LangExt.PartialTypeSignatures,
4542  flagSpec "PatternGuards"                    LangExt.PatternGuards,
4543  depFlagSpec' "PatternSignatures"            LangExt.ScopedTypeVariables
4544    (deprecatedForExtension "ScopedTypeVariables"),
4545  flagSpec "PatternSynonyms"                  LangExt.PatternSynonyms,
4546  flagSpec "PolyKinds"                        LangExt.PolyKinds,
4547  flagSpec "PolymorphicComponents"            LangExt.RankNTypes,
4548  flagSpec "QuantifiedConstraints"            LangExt.QuantifiedConstraints,
4549  flagSpec "PostfixOperators"                 LangExt.PostfixOperators,
4550  flagSpec "QuasiQuotes"                      LangExt.QuasiQuotes,
4551  flagSpec "Rank2Types"                       LangExt.RankNTypes,
4552  flagSpec "RankNTypes"                       LangExt.RankNTypes,
4553  flagSpec "RebindableSyntax"                 LangExt.RebindableSyntax,
4554  depFlagSpec' "RecordPuns"                   LangExt.RecordPuns
4555    (deprecatedForExtension "NamedFieldPuns"),
4556  flagSpec "RecordWildCards"                  LangExt.RecordWildCards,
4557  flagSpec "RecursiveDo"                      LangExt.RecursiveDo,
4558  flagSpec "RelaxedLayout"                    LangExt.RelaxedLayout,
4559  depFlagSpecCond "RelaxedPolyRec"            LangExt.RelaxedPolyRec
4560    not
4561         "You can't turn off RelaxedPolyRec any more",
4562  flagSpec "RoleAnnotations"                  LangExt.RoleAnnotations,
4563  flagSpec "ScopedTypeVariables"              LangExt.ScopedTypeVariables,
4564  flagSpec "StandaloneDeriving"               LangExt.StandaloneDeriving,
4565  flagSpec "StarIsType"                       LangExt.StarIsType,
4566  flagSpec "StaticPointers"                   LangExt.StaticPointers,
4567  flagSpec "Strict"                           LangExt.Strict,
4568  flagSpec "StrictData"                       LangExt.StrictData,
4569  flagSpec' "TemplateHaskell"                 LangExt.TemplateHaskell
4570                                              checkTemplateHaskellOk,
4571  flagSpec "TemplateHaskellQuotes"            LangExt.TemplateHaskellQuotes,
4572  flagSpec "StandaloneKindSignatures"         LangExt.StandaloneKindSignatures,
4573  flagSpec "TraditionalRecordSyntax"          LangExt.TraditionalRecordSyntax,
4574  flagSpec "TransformListComp"                LangExt.TransformListComp,
4575  flagSpec "TupleSections"                    LangExt.TupleSections,
4576  flagSpec "TypeApplications"                 LangExt.TypeApplications,
4577  flagSpec "TypeInType"                       LangExt.TypeInType,
4578  flagSpec "TypeFamilies"                     LangExt.TypeFamilies,
4579  flagSpec "TypeOperators"                    LangExt.TypeOperators,
4580  flagSpec "TypeSynonymInstances"             LangExt.TypeSynonymInstances,
4581  flagSpec "UnboxedTuples"                    LangExt.UnboxedTuples,
4582  flagSpec "UnboxedSums"                      LangExt.UnboxedSums,
4583  flagSpec "UndecidableInstances"             LangExt.UndecidableInstances,
4584  flagSpec "UndecidableSuperClasses"          LangExt.UndecidableSuperClasses,
4585  flagSpec "UnicodeSyntax"                    LangExt.UnicodeSyntax,
4586  flagSpec "UnliftedFFITypes"                 LangExt.UnliftedFFITypes,
4587  flagSpec "UnliftedNewtypes"                 LangExt.UnliftedNewtypes,
4588  flagSpec "ViewPatterns"                     LangExt.ViewPatterns
4589  ]
4590
4591defaultFlags :: Settings -> [GeneralFlag]
4592defaultFlags settings
4593-- See Note [Updating flag description in the User's Guide]
4594  = [ Opt_AutoLinkPackages,
4595      Opt_DiagnosticsShowCaret,
4596      Opt_EmbedManifest,
4597      Opt_FlatCache,
4598      Opt_GenManifest,
4599      Opt_GhciHistory,
4600      Opt_GhciSandbox,
4601      Opt_HelpfulErrors,
4602      Opt_KeepHiFiles,
4603      Opt_KeepOFiles,
4604      Opt_OmitYields,
4605      Opt_PrintBindContents,
4606      Opt_ProfCountEntries,
4607      Opt_SharedImplib,
4608      Opt_SimplPreInlining,
4609      Opt_VersionMacros,
4610      Opt_RPath
4611    ]
4612
4613    ++ [f | (ns,f) <- optLevelFlags, 0 `elem` ns]
4614             -- The default -O0 options
4615
4616    ++ default_PIC platform
4617
4618    ++ concatMap (wayGeneralFlags platform) (defaultWays settings)
4619    ++ validHoleFitDefaults
4620
4621    where platform = sTargetPlatform settings
4622
4623-- | These are the default settings for the display and sorting of valid hole
4624--  fits in typed-hole error messages. See Note [Valid hole fits include ...]
4625 -- in the TcHoleErrors module.
4626validHoleFitDefaults :: [GeneralFlag]
4627validHoleFitDefaults
4628  =  [ Opt_ShowTypeAppOfHoleFits
4629     , Opt_ShowTypeOfHoleFits
4630     , Opt_ShowProvOfHoleFits
4631     , Opt_ShowMatchesOfHoleFits
4632     , Opt_ShowValidHoleFits
4633     , Opt_SortValidHoleFits
4634     , Opt_SortBySizeHoleFits
4635     , Opt_ShowHoleConstraints ]
4636
4637
4638validHoleFitsImpliedGFlags :: [(GeneralFlag, TurnOnFlag, GeneralFlag)]
4639validHoleFitsImpliedGFlags
4640  = [ (Opt_UnclutterValidHoleFits, turnOff, Opt_ShowTypeAppOfHoleFits)
4641    , (Opt_UnclutterValidHoleFits, turnOff, Opt_ShowTypeAppVarsOfHoleFits)
4642    , (Opt_UnclutterValidHoleFits, turnOff, Opt_ShowDocsOfHoleFits)
4643    , (Opt_ShowTypeAppVarsOfHoleFits, turnOff, Opt_ShowTypeAppOfHoleFits)
4644    , (Opt_UnclutterValidHoleFits, turnOff, Opt_ShowProvOfHoleFits) ]
4645
4646default_PIC :: Platform -> [GeneralFlag]
4647default_PIC platform =
4648  case (platformOS platform, platformArch platform) of
4649    -- Darwin always requires PIC.  Especially on more recent macOS releases
4650    -- there will be a 4GB __ZEROPAGE that prevents us from using 32bit addresses
4651    -- while we could work around this on x86_64 (like WINE does), we won't be
4652    -- able on aarch64, where this is enforced.
4653    (OSDarwin,  ArchX86_64) -> [Opt_PIC]
4654    -- For AArch64, we need to always have PIC enabled.  The relocation model
4655    -- on AArch64 does not permit arbitrary relocations.  Under ASLR, we can't
4656    -- control much how far apart symbols are in memory for our in-memory static
4657    -- linker;  and thus need to ensure we get sufficiently capable relocations.
4658    -- This requires PIC on AArch64, and ExternalDynamicRefs on Linux on top
4659    -- of that.  Subsequently we expect all code on aarch64/linux (and macOS) to
4660    -- be built with -fPIC.
4661    -- See #15275, #18892
4662    (OSDarwin,  ArchAArch64) -> [Opt_PIC]
4663    (OSLinux,   ArchAArch64) -> [Opt_PIC, Opt_ExternalDynamicRefs]
4664    (OSLinux,   ArchARM {})  -> [Opt_PIC, Opt_ExternalDynamicRefs]
4665    (OSOpenBSD, ArchX86_64)  -> [Opt_PIC] -- Due to PIE support in
4666                                          -- OpenBSD since 5.3 release
4667                                          -- (1 May 2013) we need to
4668                                          -- always generate PIC. See
4669                                          -- #10597 for more
4670                                          -- information.
4671    _                        -> []
4672
4673-- General flags that are switched on/off when other general flags are switched
4674-- on
4675impliedGFlags :: [(GeneralFlag, TurnOnFlag, GeneralFlag)]
4676impliedGFlags = [(Opt_DeferTypeErrors, turnOn, Opt_DeferTypedHoles)
4677                ,(Opt_DeferTypeErrors, turnOn, Opt_DeferOutOfScopeVariables)
4678                ,(Opt_Strictness, turnOn, Opt_WorkerWrapper)
4679                ] ++ validHoleFitsImpliedGFlags
4680
4681-- General flags that are switched on/off when other general flags are switched
4682-- off
4683impliedOffGFlags :: [(GeneralFlag, TurnOnFlag, GeneralFlag)]
4684impliedOffGFlags = [(Opt_Strictness, turnOff, Opt_WorkerWrapper)]
4685
4686impliedXFlags :: [(LangExt.Extension, TurnOnFlag, LangExt.Extension)]
4687impliedXFlags
4688-- See Note [Updating flag description in the User's Guide]
4689  = [ (LangExt.RankNTypes,                turnOn, LangExt.ExplicitForAll)
4690    , (LangExt.QuantifiedConstraints,     turnOn, LangExt.ExplicitForAll)
4691    , (LangExt.ScopedTypeVariables,       turnOn, LangExt.ExplicitForAll)
4692    , (LangExt.LiberalTypeSynonyms,       turnOn, LangExt.ExplicitForAll)
4693    , (LangExt.ExistentialQuantification, turnOn, LangExt.ExplicitForAll)
4694    , (LangExt.FlexibleInstances,         turnOn, LangExt.TypeSynonymInstances)
4695    , (LangExt.FunctionalDependencies,    turnOn, LangExt.MultiParamTypeClasses)
4696    , (LangExt.MultiParamTypeClasses,     turnOn, LangExt.ConstrainedClassMethods)  -- c.f. #7854
4697    , (LangExt.TypeFamilyDependencies,    turnOn, LangExt.TypeFamilies)
4698
4699    , (LangExt.RebindableSyntax, turnOff, LangExt.ImplicitPrelude)      -- NB: turn off!
4700
4701    , (LangExt.DerivingVia, turnOn, LangExt.DerivingStrategies)
4702
4703    , (LangExt.GADTs,            turnOn, LangExt.GADTSyntax)
4704    , (LangExt.GADTs,            turnOn, LangExt.MonoLocalBinds)
4705    , (LangExt.TypeFamilies,     turnOn, LangExt.MonoLocalBinds)
4706
4707    , (LangExt.TypeFamilies,     turnOn, LangExt.KindSignatures)  -- Type families use kind signatures
4708    , (LangExt.PolyKinds,        turnOn, LangExt.KindSignatures)  -- Ditto polymorphic kinds
4709
4710    -- TypeInType is now just a synonym for a couple of other extensions.
4711    , (LangExt.TypeInType,       turnOn, LangExt.DataKinds)
4712    , (LangExt.TypeInType,       turnOn, LangExt.PolyKinds)
4713    , (LangExt.TypeInType,       turnOn, LangExt.KindSignatures)
4714
4715    -- Standalone kind signatures are a replacement for CUSKs.
4716    , (LangExt.StandaloneKindSignatures, turnOff, LangExt.CUSKs)
4717
4718    -- AutoDeriveTypeable is not very useful without DeriveDataTypeable
4719    , (LangExt.AutoDeriveTypeable, turnOn, LangExt.DeriveDataTypeable)
4720
4721    -- We turn this on so that we can export associated type
4722    -- type synonyms in subordinates (e.g. MyClass(type AssocType))
4723    , (LangExt.TypeFamilies,     turnOn, LangExt.ExplicitNamespaces)
4724    , (LangExt.TypeOperators, turnOn, LangExt.ExplicitNamespaces)
4725
4726    , (LangExt.ImpredicativeTypes,  turnOn, LangExt.RankNTypes)
4727
4728        -- Record wild-cards implies field disambiguation
4729        -- Otherwise if you write (C {..}) you may well get
4730        -- stuff like " 'a' not in scope ", which is a bit silly
4731        -- if the compiler has just filled in field 'a' of constructor 'C'
4732    , (LangExt.RecordWildCards,     turnOn, LangExt.DisambiguateRecordFields)
4733
4734    , (LangExt.ParallelArrays, turnOn, LangExt.ParallelListComp)
4735
4736    , (LangExt.JavaScriptFFI, turnOn, LangExt.InterruptibleFFI)
4737
4738    , (LangExt.DeriveTraversable, turnOn, LangExt.DeriveFunctor)
4739    , (LangExt.DeriveTraversable, turnOn, LangExt.DeriveFoldable)
4740
4741    -- Duplicate record fields require field disambiguation
4742    , (LangExt.DuplicateRecordFields, turnOn, LangExt.DisambiguateRecordFields)
4743
4744    , (LangExt.TemplateHaskell, turnOn, LangExt.TemplateHaskellQuotes)
4745    , (LangExt.Strict, turnOn, LangExt.StrictData)
4746  ]
4747
4748-- Note [When is StarIsType enabled]
4749-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
4750-- The StarIsType extension determines whether to treat '*' as a regular type
4751-- operator or as a synonym for 'Data.Kind.Type'. Many existing pre-TypeInType
4752-- programs expect '*' to be synonymous with 'Type', so by default StarIsType is
4753-- enabled.
4754--
4755-- Programs that use TypeOperators might expect to repurpose '*' for
4756-- multiplication or another binary operation, but making TypeOperators imply
4757-- NoStarIsType caused too much breakage on Hackage.
4758--
4759
4760-- Note [Documenting optimisation flags]
4761-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
4762--
4763-- If you change the list of flags enabled for particular optimisation levels
4764-- please remember to update the User's Guide. The relevant file is:
4765--
4766--   docs/users_guide/using-optimisation.rst
4767--
4768-- Make sure to note whether a flag is implied by -O0, -O or -O2.
4769
4770optLevelFlags :: [([Int], GeneralFlag)]
4771optLevelFlags -- see Note [Documenting optimisation flags]
4772  = [ ([0,1,2], Opt_DoLambdaEtaExpansion)
4773    , ([0,1,2], Opt_DoEtaReduction)       -- See Note [Eta-reduction in -O0]
4774    , ([0,1,2], Opt_DmdTxDictSel)
4775    , ([0,1,2], Opt_LlvmTBAA)
4776
4777    , ([0],     Opt_IgnoreInterfacePragmas)
4778    , ([0],     Opt_OmitInterfacePragmas)
4779
4780    , ([1,2],   Opt_CallArity)
4781    , ([1,2],   Opt_Exitification)
4782    , ([1,2],   Opt_CaseMerge)
4783    , ([1,2],   Opt_CaseFolding)
4784    , ([1,2],   Opt_CmmElimCommonBlocks)
4785    , ([2],     Opt_AsmShortcutting)
4786    , ([1,2],   Opt_CmmSink)
4787    , ([1,2],   Opt_CSE)
4788    , ([1,2],   Opt_StgCSE)
4789    , ([2],     Opt_StgLiftLams)
4790    , ([1,2],   Opt_EnableRewriteRules)  -- Off for -O0; see Note [Scoping for Builtin rules]
4791                                         --              in PrelRules
4792    , ([1,2],   Opt_FloatIn)
4793    , ([1,2],   Opt_FullLaziness)
4794    , ([1,2],   Opt_IgnoreAsserts)
4795    , ([1,2],   Opt_Loopification)
4796    , ([1,2],   Opt_CfgBlocklayout)      -- Experimental
4797
4798    , ([1,2],   Opt_Specialise)
4799    , ([1,2],   Opt_CrossModuleSpecialise)
4800    , ([1,2],   Opt_Strictness)
4801    , ([1,2],   Opt_UnboxSmallStrictFields)
4802    , ([1,2],   Opt_CprAnal)
4803    , ([1,2],   Opt_WorkerWrapper)
4804    , ([1,2],   Opt_SolveConstantDicts)
4805    , ([1,2],   Opt_NumConstantFolding)
4806
4807    , ([2],     Opt_LiberateCase)
4808    , ([2],     Opt_SpecConstr)
4809--  , ([2],     Opt_RegsGraph)
4810--   RegsGraph suffers performance regression. See #7679
4811--  , ([2],     Opt_StaticArgumentTransformation)
4812--   Static Argument Transformation needs investigation. See #9374
4813    ]
4814
4815{- Note [Eta-reduction in -O0]
4816~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
4817#11562 showed an example which tripped an ASSERT in CoreToStg; a
4818function was marked as MayHaveCafRefs when in fact it obviously
4819didn't.  Reason was:
4820 * Eta reduction wasn't happening in the simplifier, but it was
4821   happening in CorePrep, on
4822        $fBla = MkDict (/\a. K a)
4823 * Result: rhsIsStatic told TidyPgm that $fBla might have CAF refs
4824   but the eta-reduced version (MkDict K) obviously doesn't
4825Simple solution: just let the simplifier do eta-reduction even in -O0.
4826After all, CorePrep does it unconditionally!  Not a big deal, but
4827removes an assertion failure. -}
4828
4829
4830-- -----------------------------------------------------------------------------
4831-- Standard sets of warning options
4832
4833-- Note [Documenting warning flags]
4834-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
4835--
4836-- If you change the list of warning enabled by default
4837-- please remember to update the User's Guide. The relevant file is:
4838--
4839--  docs/users_guide/using-warnings.rst
4840
4841-- | Warning groups.
4842--
4843-- As all warnings are in the Weverything set, it is ignored when
4844-- displaying to the user which group a warning is in.
4845warningGroups :: [(String, [WarningFlag])]
4846warningGroups =
4847    [ ("compat",       minusWcompatOpts)
4848    , ("unused-binds", unusedBindsFlags)
4849    , ("default",      standardWarnings)
4850    , ("extra",        minusWOpts)
4851    , ("all",          minusWallOpts)
4852    , ("everything",   minusWeverythingOpts)
4853    ]
4854
4855-- | Warning group hierarchies, where there is an explicit inclusion
4856-- relation.
4857--
4858-- Each inner list is a hierarchy of warning groups, ordered from
4859-- smallest to largest, where each group is a superset of the one
4860-- before it.
4861--
4862-- Separating this from 'warningGroups' allows for multiple
4863-- hierarchies with no inherent relation to be defined.
4864--
4865-- The special-case Weverything group is not included.
4866warningHierarchies :: [[String]]
4867warningHierarchies = hierarchies ++ map (:[]) rest
4868  where
4869    hierarchies = [["default", "extra", "all"]]
4870    rest = filter (`notElem` "everything" : concat hierarchies) $
4871           map fst warningGroups
4872
4873-- | Find the smallest group in every hierarchy which a warning
4874-- belongs to, excluding Weverything.
4875smallestGroups :: WarningFlag -> [String]
4876smallestGroups flag = mapMaybe go warningHierarchies where
4877    -- Because each hierarchy is arranged from smallest to largest,
4878    -- the first group we find in a hierarchy which contains the flag
4879    -- is the smallest.
4880    go (group:rest) = fromMaybe (go rest) $ do
4881        flags <- lookup group warningGroups
4882        guard (flag `elem` flags)
4883        pure (Just group)
4884    go [] = Nothing
4885
4886-- | Warnings enabled unless specified otherwise
4887standardWarnings :: [WarningFlag]
4888standardWarnings -- see Note [Documenting warning flags]
4889    = [ Opt_WarnOverlappingPatterns,
4890        Opt_WarnWarningsDeprecations,
4891        Opt_WarnDeprecatedFlags,
4892        Opt_WarnDeferredTypeErrors,
4893        Opt_WarnTypedHoles,
4894        Opt_WarnDeferredOutOfScopeVariables,
4895        Opt_WarnPartialTypeSignatures,
4896        Opt_WarnUnrecognisedPragmas,
4897        Opt_WarnDuplicateExports,
4898        Opt_WarnDerivingDefaults,
4899        Opt_WarnOverflowedLiterals,
4900        Opt_WarnEmptyEnumerations,
4901        Opt_WarnMissingFields,
4902        Opt_WarnMissingMethods,
4903        Opt_WarnWrongDoBind,
4904        Opt_WarnUnsupportedCallingConventions,
4905        Opt_WarnDodgyForeignImports,
4906        Opt_WarnInlineRuleShadowing,
4907        Opt_WarnAlternativeLayoutRuleTransitional,
4908        Opt_WarnUnsupportedLlvmVersion,
4909        Opt_WarnMissedExtraSharedLib,
4910        Opt_WarnTabs,
4911        Opt_WarnUnrecognisedWarningFlags,
4912        Opt_WarnSimplifiableClassConstraints,
4913        Opt_WarnStarBinder,
4914        Opt_WarnInaccessibleCode,
4915        Opt_WarnSpaceAfterBang
4916      ]
4917
4918-- | Things you get with -W
4919minusWOpts :: [WarningFlag]
4920minusWOpts
4921    = standardWarnings ++
4922      [ Opt_WarnUnusedTopBinds,
4923        Opt_WarnUnusedLocalBinds,
4924        Opt_WarnUnusedPatternBinds,
4925        Opt_WarnUnusedMatches,
4926        Opt_WarnUnusedForalls,
4927        Opt_WarnUnusedImports,
4928        Opt_WarnIncompletePatterns,
4929        Opt_WarnDodgyExports,
4930        Opt_WarnDodgyImports,
4931        Opt_WarnUnbangedStrictPatterns
4932      ]
4933
4934-- | Things you get with -Wall
4935minusWallOpts :: [WarningFlag]
4936minusWallOpts
4937    = minusWOpts ++
4938      [ Opt_WarnTypeDefaults,
4939        Opt_WarnNameShadowing,
4940        Opt_WarnMissingSignatures,
4941        Opt_WarnHiShadows,
4942        Opt_WarnOrphans,
4943        Opt_WarnUnusedDoBind,
4944        Opt_WarnTrustworthySafe,
4945        Opt_WarnUntickedPromotedConstructors,
4946        Opt_WarnMissingPatternSynonymSignatures,
4947        Opt_WarnUnusedRecordWildcards,
4948        Opt_WarnRedundantRecordWildcards
4949      ]
4950
4951-- | Things you get with -Weverything, i.e. *all* known warnings flags
4952minusWeverythingOpts :: [WarningFlag]
4953minusWeverythingOpts = [ toEnum 0 .. ]
4954
4955-- | Things you get with -Wcompat.
4956--
4957-- This is intended to group together warnings that will be enabled by default
4958-- at some point in the future, so that library authors eager to make their
4959-- code future compatible to fix issues before they even generate warnings.
4960minusWcompatOpts :: [WarningFlag]
4961minusWcompatOpts
4962    = [ Opt_WarnMissingMonadFailInstances
4963      , Opt_WarnSemigroup
4964      , Opt_WarnNonCanonicalMonoidInstances
4965      , Opt_WarnStarIsType
4966      , Opt_WarnCompatUnqualifiedImports
4967      ]
4968
4969enableUnusedBinds :: DynP ()
4970enableUnusedBinds = mapM_ setWarningFlag unusedBindsFlags
4971
4972disableUnusedBinds :: DynP ()
4973disableUnusedBinds = mapM_ unSetWarningFlag unusedBindsFlags
4974
4975-- Things you get with -Wunused-binds
4976unusedBindsFlags :: [WarningFlag]
4977unusedBindsFlags = [ Opt_WarnUnusedTopBinds
4978                   , Opt_WarnUnusedLocalBinds
4979                   , Opt_WarnUnusedPatternBinds
4980                   ]
4981
4982enableGlasgowExts :: DynP ()
4983enableGlasgowExts = do setGeneralFlag Opt_PrintExplicitForalls
4984                       mapM_ setExtensionFlag glasgowExtsFlags
4985
4986disableGlasgowExts :: DynP ()
4987disableGlasgowExts = do unSetGeneralFlag Opt_PrintExplicitForalls
4988                        mapM_ unSetExtensionFlag glasgowExtsFlags
4989
4990-- Please keep what_glasgow_exts_does.rst up to date with this list
4991glasgowExtsFlags :: [LangExt.Extension]
4992glasgowExtsFlags = [
4993             LangExt.ConstrainedClassMethods
4994           , LangExt.DeriveDataTypeable
4995           , LangExt.DeriveFoldable
4996           , LangExt.DeriveFunctor
4997           , LangExt.DeriveGeneric
4998           , LangExt.DeriveTraversable
4999           , LangExt.EmptyDataDecls
5000           , LangExt.ExistentialQuantification
5001           , LangExt.ExplicitNamespaces
5002           , LangExt.FlexibleContexts
5003           , LangExt.FlexibleInstances
5004           , LangExt.ForeignFunctionInterface
5005           , LangExt.FunctionalDependencies
5006           , LangExt.GeneralizedNewtypeDeriving
5007           , LangExt.ImplicitParams
5008           , LangExt.KindSignatures
5009           , LangExt.LiberalTypeSynonyms
5010           , LangExt.MagicHash
5011           , LangExt.MultiParamTypeClasses
5012           , LangExt.ParallelListComp
5013           , LangExt.PatternGuards
5014           , LangExt.PostfixOperators
5015           , LangExt.RankNTypes
5016           , LangExt.RecursiveDo
5017           , LangExt.ScopedTypeVariables
5018           , LangExt.StandaloneDeriving
5019           , LangExt.TypeOperators
5020           , LangExt.TypeSynonymInstances
5021           , LangExt.UnboxedTuples
5022           , LangExt.UnicodeSyntax
5023           , LangExt.UnliftedFFITypes ]
5024
5025foreign import ccall unsafe "rts_isProfiled" rtsIsProfiledIO :: IO CInt
5026
5027-- | Was the runtime system built with profiling enabled?
5028rtsIsProfiled :: Bool
5029rtsIsProfiled = unsafeDupablePerformIO rtsIsProfiledIO /= 0
5030
5031-- Consult the RTS to find whether GHC itself has been built with
5032-- dynamic linking.  This can't be statically known at compile-time,
5033-- because we build both the static and dynamic versions together with
5034-- -dynamic-too.
5035foreign import ccall unsafe "rts_isDynamic" rtsIsDynamicIO :: IO CInt
5036
5037dynamicGhc :: Bool
5038dynamicGhc = unsafeDupablePerformIO rtsIsDynamicIO /= 0
5039
5040setWarnSafe :: Bool -> DynP ()
5041setWarnSafe True  = getCurLoc >>= \l -> upd (\d -> d { warnSafeOnLoc = l })
5042setWarnSafe False = return ()
5043
5044setWarnUnsafe :: Bool -> DynP ()
5045setWarnUnsafe True  = getCurLoc >>= \l -> upd (\d -> d { warnUnsafeOnLoc = l })
5046setWarnUnsafe False = return ()
5047
5048setPackageTrust :: DynP ()
5049setPackageTrust = do
5050    setGeneralFlag Opt_PackageTrust
5051    l <- getCurLoc
5052    upd $ \d -> d { pkgTrustOnLoc = l }
5053
5054setGenDeriving :: TurnOnFlag -> DynP ()
5055setGenDeriving True  = getCurLoc >>= \l -> upd (\d -> d { newDerivOnLoc = l })
5056setGenDeriving False = return ()
5057
5058setOverlappingInsts :: TurnOnFlag -> DynP ()
5059setOverlappingInsts False = return ()
5060setOverlappingInsts True = do
5061  l <- getCurLoc
5062  upd (\d -> d { overlapInstLoc = l })
5063
5064setIncoherentInsts :: TurnOnFlag -> DynP ()
5065setIncoherentInsts False = return ()
5066setIncoherentInsts True = do
5067  l <- getCurLoc
5068  upd (\d -> d { incoherentOnLoc = l })
5069
5070checkTemplateHaskellOk :: TurnOnFlag -> DynP ()
5071checkTemplateHaskellOk _turn_on
5072  = getCurLoc >>= \l -> upd (\d -> d { thOnLoc = l })
5073
5074{- **********************************************************************
5075%*                                                                      *
5076                DynFlags constructors
5077%*                                                                      *
5078%********************************************************************* -}
5079
5080type DynP = EwM (CmdLineP DynFlags)
5081
5082upd :: (DynFlags -> DynFlags) -> DynP ()
5083upd f = liftEwM (do dflags <- getCmdLineState
5084                    putCmdLineState $! f dflags)
5085
5086updM :: (DynFlags -> DynP DynFlags) -> DynP ()
5087updM f = do dflags <- liftEwM getCmdLineState
5088            dflags' <- f dflags
5089            liftEwM $ putCmdLineState $! dflags'
5090
5091--------------- Constructor functions for OptKind -----------------
5092noArg :: (DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
5093noArg fn = NoArg (upd fn)
5094
5095noArgM :: (DynFlags -> DynP DynFlags) -> OptKind (CmdLineP DynFlags)
5096noArgM fn = NoArg (updM fn)
5097
5098hasArg :: (String -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
5099hasArg fn = HasArg (upd . fn)
5100
5101sepArg :: (String -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
5102sepArg fn = SepArg (upd . fn)
5103
5104intSuffix :: (Int -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
5105intSuffix fn = IntSuffix (\n -> upd (fn n))
5106
5107intSuffixM :: (Int -> DynFlags -> DynP DynFlags) -> OptKind (CmdLineP DynFlags)
5108intSuffixM fn = IntSuffix (\n -> updM (fn n))
5109
5110floatSuffix :: (Float -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
5111floatSuffix fn = FloatSuffix (\n -> upd (fn n))
5112
5113optIntSuffixM :: (Maybe Int -> DynFlags -> DynP DynFlags)
5114              -> OptKind (CmdLineP DynFlags)
5115optIntSuffixM fn = OptIntSuffix (\mi -> updM (fn mi))
5116
5117setDumpFlag :: DumpFlag -> OptKind (CmdLineP DynFlags)
5118setDumpFlag dump_flag = NoArg (setDumpFlag' dump_flag)
5119
5120--------------------------
5121addWay :: Way -> DynP ()
5122addWay w = upd (addWay' w)
5123
5124addWay' :: Way -> DynFlags -> DynFlags
5125addWay' w dflags0 = let platform = targetPlatform dflags0
5126                        dflags1 = dflags0 { ways = w : ways dflags0 }
5127                        dflags2 = foldr setGeneralFlag' dflags1
5128                                        (wayGeneralFlags platform w)
5129                        dflags3 = foldr unSetGeneralFlag' dflags2
5130                                        (wayUnsetGeneralFlags platform w)
5131                    in dflags3
5132
5133removeWayDyn :: DynP ()
5134removeWayDyn = upd (\dfs -> dfs { ways = filter (WayDyn /=) (ways dfs) })
5135
5136--------------------------
5137setGeneralFlag, unSetGeneralFlag :: GeneralFlag -> DynP ()
5138setGeneralFlag   f = upd (setGeneralFlag' f)
5139unSetGeneralFlag f = upd (unSetGeneralFlag' f)
5140
5141setGeneralFlag' :: GeneralFlag -> DynFlags -> DynFlags
5142setGeneralFlag' f dflags = foldr ($) (gopt_set dflags f) deps
5143  where
5144    deps = [ if turn_on then setGeneralFlag'   d
5145                        else unSetGeneralFlag' d
5146           | (f', turn_on, d) <- impliedGFlags, f' == f ]
5147        -- When you set f, set the ones it implies
5148        -- NB: use setGeneralFlag recursively, in case the implied flags
5149        --     implies further flags
5150
5151unSetGeneralFlag' :: GeneralFlag -> DynFlags -> DynFlags
5152unSetGeneralFlag' f dflags = foldr ($) (gopt_unset dflags f) deps
5153  where
5154    deps = [ if turn_on then setGeneralFlag' d
5155                        else unSetGeneralFlag' d
5156           | (f', turn_on, d) <- impliedOffGFlags, f' == f ]
5157   -- In general, when you un-set f, we don't un-set the things it implies.
5158   -- There are however some exceptions, e.g., -fno-strictness implies
5159   -- -fno-worker-wrapper.
5160   --
5161   -- NB: use unSetGeneralFlag' recursively, in case the implied off flags
5162   --     imply further flags.
5163
5164--------------------------
5165setWarningFlag, unSetWarningFlag :: WarningFlag -> DynP ()
5166setWarningFlag   f = upd (\dfs -> wopt_set dfs f)
5167unSetWarningFlag f = upd (\dfs -> wopt_unset dfs f)
5168
5169setFatalWarningFlag, unSetFatalWarningFlag :: WarningFlag -> DynP ()
5170setFatalWarningFlag   f = upd (\dfs -> wopt_set_fatal dfs f)
5171unSetFatalWarningFlag f = upd (\dfs -> wopt_unset_fatal dfs f)
5172
5173setWErrorFlag :: WarningFlag -> DynP ()
5174setWErrorFlag flag =
5175  do { setWarningFlag flag
5176     ; setFatalWarningFlag flag }
5177
5178--------------------------
5179setExtensionFlag, unSetExtensionFlag :: LangExt.Extension -> DynP ()
5180setExtensionFlag f = upd (setExtensionFlag' f)
5181unSetExtensionFlag f = upd (unSetExtensionFlag' f)
5182
5183setExtensionFlag', unSetExtensionFlag' :: LangExt.Extension -> DynFlags -> DynFlags
5184setExtensionFlag' f dflags = foldr ($) (xopt_set dflags f) deps
5185  where
5186    deps = [ if turn_on then setExtensionFlag'   d
5187                        else unSetExtensionFlag' d
5188           | (f', turn_on, d) <- impliedXFlags, f' == f ]
5189        -- When you set f, set the ones it implies
5190        -- NB: use setExtensionFlag recursively, in case the implied flags
5191        --     implies further flags
5192
5193unSetExtensionFlag' f dflags = xopt_unset dflags f
5194   -- When you un-set f, however, we don't un-set the things it implies
5195   --      (except for -fno-glasgow-exts, which is treated specially)
5196
5197--------------------------
5198alterFileSettings :: (FileSettings -> FileSettings) -> DynFlags -> DynFlags
5199alterFileSettings f dynFlags = dynFlags { fileSettings = f (fileSettings dynFlags) }
5200
5201alterToolSettings :: (ToolSettings -> ToolSettings) -> DynFlags -> DynFlags
5202alterToolSettings f dynFlags = dynFlags { toolSettings = f (toolSettings dynFlags) }
5203
5204--------------------------
5205setDumpFlag' :: DumpFlag -> DynP ()
5206setDumpFlag' dump_flag
5207  = do upd (\dfs -> dopt_set dfs dump_flag)
5208       when want_recomp forceRecompile
5209    where -- Certain dumpy-things are really interested in what's going
5210          -- on during recompilation checking, so in those cases we
5211          -- don't want to turn it off.
5212          want_recomp = dump_flag `notElem` [Opt_D_dump_if_trace,
5213                                             Opt_D_dump_hi_diffs,
5214                                             Opt_D_no_debug_output]
5215
5216forceRecompile :: DynP ()
5217-- Whenver we -ddump, force recompilation (by switching off the
5218-- recompilation checker), else you don't see the dump! However,
5219-- don't switch it off in --make mode, else *everything* gets
5220-- recompiled which probably isn't what you want
5221forceRecompile = do dfs <- liftEwM getCmdLineState
5222                    when (force_recomp dfs) (setGeneralFlag Opt_ForceRecomp)
5223        where
5224          force_recomp dfs = isOneShot (ghcMode dfs)
5225
5226
5227setVerboseCore2Core :: DynP ()
5228setVerboseCore2Core = setDumpFlag' Opt_D_verbose_core2core
5229
5230setVerbosity :: Maybe Int -> DynP ()
5231setVerbosity mb_n = upd (\dfs -> dfs{ verbosity = mb_n `orElse` 3 })
5232
5233setDebugLevel :: Maybe Int -> DynP ()
5234setDebugLevel mb_n = upd (\dfs -> dfs{ debugLevel = mb_n `orElse` 2 })
5235
5236data PkgConfRef
5237  = GlobalPkgConf
5238  | UserPkgConf
5239  | PkgConfFile FilePath
5240  deriving Eq
5241
5242addPkgConfRef :: PkgConfRef -> DynP ()
5243addPkgConfRef p = upd $ \s ->
5244  s { packageDBFlags = PackageDB p : packageDBFlags s }
5245
5246removeUserPkgConf :: DynP ()
5247removeUserPkgConf = upd $ \s ->
5248  s { packageDBFlags = NoUserPackageDB : packageDBFlags s }
5249
5250removeGlobalPkgConf :: DynP ()
5251removeGlobalPkgConf = upd $ \s ->
5252 s { packageDBFlags = NoGlobalPackageDB : packageDBFlags s }
5253
5254clearPkgConf :: DynP ()
5255clearPkgConf = upd $ \s ->
5256  s { packageDBFlags = ClearPackageDBs : packageDBFlags s }
5257
5258parsePackageFlag :: String                 -- the flag
5259                 -> ReadP PackageArg       -- type of argument
5260                 -> String                 -- string to parse
5261                 -> PackageFlag
5262parsePackageFlag flag arg_parse str
5263 = case filter ((=="").snd) (readP_to_S parse str) of
5264    [(r, "")] -> r
5265    _ -> throwGhcException $ CmdLineError ("Can't parse package flag: " ++ str)
5266  where doc = flag ++ " " ++ str
5267        parse = do
5268            pkg_arg <- tok arg_parse
5269            let mk_expose = ExposePackage doc pkg_arg
5270            ( do _ <- tok $ string "with"
5271                 fmap (mk_expose . ModRenaming True) parseRns
5272             <++ fmap (mk_expose . ModRenaming False) parseRns
5273             <++ return (mk_expose (ModRenaming True [])))
5274        parseRns = do _ <- tok $ R.char '('
5275                      rns <- tok $ sepBy parseItem (tok $ R.char ',')
5276                      _ <- tok $ R.char ')'
5277                      return rns
5278        parseItem = do
5279            orig <- tok $ parseModuleName
5280            (do _ <- tok $ string "as"
5281                new <- tok $ parseModuleName
5282                return (orig, new)
5283              +++
5284             return (orig, orig))
5285        tok m = m >>= \x -> skipSpaces >> return x
5286
5287exposePackage, exposePackageId, hidePackage,
5288        exposePluginPackage, exposePluginPackageId,
5289        ignorePackage,
5290        trustPackage, distrustPackage :: String -> DynP ()
5291exposePackage p = upd (exposePackage' p)
5292exposePackageId p =
5293  upd (\s -> s{ packageFlags =
5294    parsePackageFlag "-package-id" parseUnitIdArg p : packageFlags s })
5295exposePluginPackage p =
5296  upd (\s -> s{ pluginPackageFlags =
5297    parsePackageFlag "-plugin-package" parsePackageArg p : pluginPackageFlags s })
5298exposePluginPackageId p =
5299  upd (\s -> s{ pluginPackageFlags =
5300    parsePackageFlag "-plugin-package-id" parseUnitIdArg p : pluginPackageFlags s })
5301hidePackage p =
5302  upd (\s -> s{ packageFlags = HidePackage p : packageFlags s })
5303ignorePackage p =
5304  upd (\s -> s{ ignorePackageFlags = IgnorePackage p : ignorePackageFlags s })
5305
5306trustPackage p = exposePackage p >> -- both trust and distrust also expose a package
5307  upd (\s -> s{ trustFlags = TrustPackage p : trustFlags s })
5308distrustPackage p = exposePackage p >>
5309  upd (\s -> s{ trustFlags = DistrustPackage p : trustFlags s })
5310
5311exposePackage' :: String -> DynFlags -> DynFlags
5312exposePackage' p dflags
5313    = dflags { packageFlags =
5314            parsePackageFlag "-package" parsePackageArg p : packageFlags dflags }
5315
5316parsePackageArg :: ReadP PackageArg
5317parsePackageArg =
5318    fmap PackageArg (munch1 (\c -> isAlphaNum c || c `elem` ":-_."))
5319
5320parseUnitIdArg :: ReadP PackageArg
5321parseUnitIdArg =
5322    fmap UnitIdArg parseUnitId
5323
5324setUnitId :: String -> DynFlags -> DynFlags
5325setUnitId p d = d { thisInstalledUnitId = stringToInstalledUnitId p }
5326
5327-- | Given a 'ModuleName' of a signature in the home library, find
5328-- out how it is instantiated.  E.g., the canonical form of
5329-- A in @p[A=q[]:A]@ is @q[]:A@.
5330canonicalizeHomeModule :: DynFlags -> ModuleName -> Module
5331canonicalizeHomeModule dflags mod_name =
5332    case lookup mod_name (thisUnitIdInsts dflags) of
5333        Nothing  -> mkModule (thisPackage dflags) mod_name
5334        Just mod -> mod
5335
5336canonicalizeModuleIfHome :: DynFlags -> Module -> Module
5337canonicalizeModuleIfHome dflags mod
5338    = if thisPackage dflags == moduleUnitId mod
5339                      then canonicalizeHomeModule dflags (moduleName mod)
5340                      else mod
5341
5342-- If we're linking a binary, then only targets that produce object
5343-- code are allowed (requests for other target types are ignored).
5344setTarget :: HscTarget -> DynP ()
5345setTarget l = upd $ \ dfs ->
5346  if ghcLink dfs /= LinkBinary || isObjectTarget l
5347  then dfs{ hscTarget = l }
5348  else dfs
5349
5350-- Changes the target only if we're compiling object code.  This is
5351-- used by -fasm and -fllvm, which switch from one to the other, but
5352-- not from bytecode to object-code.  The idea is that -fasm/-fllvm
5353-- can be safely used in an OPTIONS_GHC pragma.
5354setObjTarget :: HscTarget -> DynP ()
5355setObjTarget l = updM set
5356  where
5357   set dflags
5358     | isObjectTarget (hscTarget dflags)
5359       = return $ dflags { hscTarget = l }
5360     | otherwise = return dflags
5361
5362setOptLevel :: Int -> DynFlags -> DynP DynFlags
5363setOptLevel n dflags = return (updOptLevel n dflags)
5364
5365checkOptLevel :: Int -> DynFlags -> Either String DynFlags
5366checkOptLevel n dflags
5367   | hscTarget dflags == HscInterpreted && n > 0
5368     = Left "-O conflicts with --interactive; -O ignored."
5369   | otherwise
5370     = Right dflags
5371
5372setMainIs :: String -> DynP ()
5373setMainIs arg
5374  | not (null main_fn) && isLower (head main_fn)
5375     -- The arg looked like "Foo.Bar.baz"
5376  = upd $ \d -> d { mainFunIs = Just main_fn,
5377                   mainModIs = mkModule mainUnitId (mkModuleName main_mod) }
5378
5379  | isUpper (head arg)  -- The arg looked like "Foo" or "Foo.Bar"
5380  = upd $ \d -> d { mainModIs = mkModule mainUnitId (mkModuleName arg) }
5381
5382  | otherwise                   -- The arg looked like "baz"
5383  = upd $ \d -> d { mainFunIs = Just arg }
5384  where
5385    (main_mod, main_fn) = splitLongestPrefix arg (== '.')
5386
5387addLdInputs :: Option -> DynFlags -> DynFlags
5388addLdInputs p dflags = dflags{ldInputs = ldInputs dflags ++ [p]}
5389
5390-- -----------------------------------------------------------------------------
5391-- Load dynflags from environment files.
5392
5393setFlagsFromEnvFile :: FilePath -> String -> DynP ()
5394setFlagsFromEnvFile envfile content = do
5395  setGeneralFlag Opt_HideAllPackages
5396  parseEnvFile envfile content
5397
5398parseEnvFile :: FilePath -> String -> DynP ()
5399parseEnvFile envfile = mapM_ parseEntry . lines
5400  where
5401    parseEntry str = case words str of
5402      ("package-db": _)     -> addPkgConfRef (PkgConfFile (envdir </> db))
5403        -- relative package dbs are interpreted relative to the env file
5404        where envdir = takeDirectory envfile
5405              db     = drop 11 str
5406      ["clear-package-db"]  -> clearPkgConf
5407      ["global-package-db"] -> addPkgConfRef GlobalPkgConf
5408      ["user-package-db"]   -> addPkgConfRef UserPkgConf
5409      ["package-id", pkgid] -> exposePackageId pkgid
5410      (('-':'-':_):_)       -> return () -- comments
5411      -- and the original syntax introduced in 7.10:
5412      [pkgid]               -> exposePackageId pkgid
5413      []                    -> return ()
5414      _                     -> throwGhcException $ CmdLineError $
5415                                    "Can't parse environment file entry: "
5416                                 ++ envfile ++ ": " ++ str
5417
5418
5419-----------------------------------------------------------------------------
5420-- Paths & Libraries
5421
5422addImportPath, addLibraryPath, addIncludePath, addFrameworkPath :: FilePath -> DynP ()
5423
5424-- -i on its own deletes the import paths
5425addImportPath "" = upd (\s -> s{importPaths = []})
5426addImportPath p  = upd (\s -> s{importPaths = importPaths s ++ splitPathList p})
5427
5428addLibraryPath p =
5429  upd (\s -> s{libraryPaths = libraryPaths s ++ splitPathList p})
5430
5431addIncludePath p =
5432  upd (\s -> s{includePaths =
5433                  addGlobalInclude (includePaths s) (splitPathList p)})
5434
5435addFrameworkPath p =
5436  upd (\s -> s{frameworkPaths = frameworkPaths s ++ splitPathList p})
5437
5438#if !defined(mingw32_HOST_OS)
5439split_marker :: Char
5440split_marker = ':'   -- not configurable (ToDo)
5441#endif
5442
5443splitPathList :: String -> [String]
5444splitPathList s = filter notNull (splitUp s)
5445                -- empty paths are ignored: there might be a trailing
5446                -- ':' in the initial list, for example.  Empty paths can
5447                -- cause confusion when they are translated into -I options
5448                -- for passing to gcc.
5449  where
5450#if !defined(mingw32_HOST_OS)
5451    splitUp xs = split split_marker xs
5452#else
5453     -- Windows: 'hybrid' support for DOS-style paths in directory lists.
5454     --
5455     -- That is, if "foo:bar:baz" is used, this interpreted as
5456     -- consisting of three entries, 'foo', 'bar', 'baz'.
5457     -- However, with "c:/foo:c:\\foo;x:/bar", this is interpreted
5458     -- as 3 elts, "c:/foo", "c:\\foo", "x:/bar"
5459     --
5460     -- Notice that no attempt is made to fully replace the 'standard'
5461     -- split marker ':' with the Windows / DOS one, ';'. The reason being
5462     -- that this will cause too much breakage for users & ':' will
5463     -- work fine even with DOS paths, if you're not insisting on being silly.
5464     -- So, use either.
5465    splitUp []             = []
5466    splitUp (x:':':div:xs) | div `elem` dir_markers
5467                           = ((x:':':div:p): splitUp rs)
5468                           where
5469                              (p,rs) = findNextPath xs
5470          -- we used to check for existence of the path here, but that
5471          -- required the IO monad to be threaded through the command-line
5472          -- parser which is quite inconvenient.  The
5473    splitUp xs = cons p (splitUp rs)
5474               where
5475                 (p,rs) = findNextPath xs
5476
5477                 cons "" xs = xs
5478                 cons x  xs = x:xs
5479
5480    -- will be called either when we've consumed nought or the
5481    -- "<Drive>:/" part of a DOS path, so splitting is just a Q of
5482    -- finding the next split marker.
5483    findNextPath xs =
5484        case break (`elem` split_markers) xs of
5485           (p, _:ds) -> (p, ds)
5486           (p, xs)   -> (p, xs)
5487
5488    split_markers :: [Char]
5489    split_markers = [':', ';']
5490
5491    dir_markers :: [Char]
5492    dir_markers = ['/', '\\']
5493#endif
5494
5495-- -----------------------------------------------------------------------------
5496-- tmpDir, where we store temporary files.
5497
5498setTmpDir :: FilePath -> DynFlags -> DynFlags
5499setTmpDir dir = alterFileSettings $ \s -> s { fileSettings_tmpDir = normalise dir }
5500  -- we used to fix /cygdrive/c/.. on Windows, but this doesn't
5501  -- seem necessary now --SDM 7/2/2008
5502
5503-----------------------------------------------------------------------------
5504-- RTS opts
5505
5506setRtsOpts :: String -> DynP ()
5507setRtsOpts arg  = upd $ \ d -> d {rtsOpts = Just arg}
5508
5509setRtsOptsEnabled :: RtsOptsEnabled -> DynP ()
5510setRtsOptsEnabled arg  = upd $ \ d -> d {rtsOptsEnabled = arg}
5511
5512-----------------------------------------------------------------------------
5513-- Hpc stuff
5514
5515setOptHpcDir :: String -> DynP ()
5516setOptHpcDir arg  = upd $ \ d -> d {hpcDir = arg}
5517
5518-----------------------------------------------------------------------------
5519-- Via-C compilation stuff
5520
5521-- There are some options that we need to pass to gcc when compiling
5522-- Haskell code via C, but are only supported by recent versions of
5523-- gcc.  The configure script decides which of these options we need,
5524-- and puts them in the "settings" file in $topdir. The advantage of
5525-- having these in a separate file is that the file can be created at
5526-- install-time depending on the available gcc version, and even
5527-- re-generated later if gcc is upgraded.
5528--
5529-- The options below are not dependent on the version of gcc, only the
5530-- platform.
5531
5532picCCOpts :: DynFlags -> [String]
5533picCCOpts dflags = pieOpts ++ picOpts
5534  where
5535    picOpts =
5536      case platformOS (targetPlatform dflags) of
5537      OSDarwin
5538          -- Apple prefers to do things the other way round.
5539          -- PIC is on by default.
5540          -- -mdynamic-no-pic:
5541          --     Turn off PIC code generation.
5542          -- -fno-common:
5543          --     Don't generate "common" symbols - these are unwanted
5544          --     in dynamic libraries.
5545
5546       | gopt Opt_PIC dflags -> ["-fno-common", "-U__PIC__", "-D__PIC__"]
5547       | otherwise           -> ["-mdynamic-no-pic"]
5548      OSMinGW32 -- no -fPIC for Windows
5549       | gopt Opt_PIC dflags -> ["-U__PIC__", "-D__PIC__"]
5550       | otherwise           -> []
5551      _
5552      -- we need -fPIC for C files when we are compiling with -dynamic,
5553      -- otherwise things like stub.c files don't get compiled
5554      -- correctly.  They need to reference data in the Haskell
5555      -- objects, but can't without -fPIC.  See
5556      -- https://gitlab.haskell.org/ghc/ghc/wikis/commentary/position-independent-code
5557       | gopt Opt_PIC dflags || WayDyn `elem` ways dflags ->
5558          ["-fPIC", "-U__PIC__", "-D__PIC__"]
5559      -- gcc may be configured to have PIC on by default, let's be
5560      -- explicit here, see #15847
5561       | otherwise -> ["-fno-PIC"]
5562
5563    pieOpts
5564      | gopt Opt_PICExecutable dflags       = ["-pie"]
5565        -- See Note [No PIE when linking]
5566      | toolSettings_ccSupportsNoPie (toolSettings dflags) = ["-no-pie"]
5567      | otherwise                           = []
5568
5569
5570{-
5571Note [No PIE while linking]
5572~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
5573As of 2016 some Linux distributions (e.g. Debian) have started enabling -pie by
5574default in their gcc builds. This is incompatible with -r as it implies that we
5575are producing an executable. Consequently, we must manually pass -no-pie to gcc
5576when joining object files or linking dynamic libraries. Unless, of course, the
5577user has explicitly requested a PIE executable with -pie. See #12759.
5578-}
5579
5580picPOpts :: DynFlags -> [String]
5581picPOpts dflags
5582 | gopt Opt_PIC dflags = ["-U__PIC__", "-D__PIC__"]
5583 | otherwise           = []
5584
5585-- -----------------------------------------------------------------------------
5586-- Compiler Info
5587
5588compilerInfo :: DynFlags -> [(String, String)]
5589compilerInfo dflags
5590    = -- We always make "Project name" be first to keep parsing in
5591      -- other languages simple, i.e. when looking for other fields,
5592      -- you don't have to worry whether there is a leading '[' or not
5593      ("Project name",                 cProjectName)
5594      -- Next come the settings, so anything else can be overridden
5595      -- in the settings file (as "lookup" uses the first match for the
5596      -- key)
5597    : map (fmap $ expandDirectories (topDir dflags) (toolDir dflags))
5598          (rawSettings dflags)
5599   ++ [("Project version",             projectVersion dflags),
5600       ("Project Git commit id",       cProjectGitCommitId),
5601       ("Booter version",              cBooterVersion),
5602       ("Stage",                       cStage),
5603       ("Build platform",              cBuildPlatformString),
5604       ("Host platform",               cHostPlatformString),
5605       ("Target platform",             platformMisc_targetPlatformString $ platformMisc dflags),
5606       ("Have interpreter",            showBool $ platformMisc_ghcWithInterpreter $ platformMisc dflags),
5607       ("Object splitting supported",  showBool False),
5608       ("Have native code generator",  showBool $ platformMisc_ghcWithNativeCodeGen $ platformMisc dflags),
5609       -- Whether or not we support @-dynamic-too@
5610       ("Support dynamic-too",         showBool $ not isWindows),
5611       -- Whether or not we support the @-j@ flag with @--make@.
5612       ("Support parallel --make",     "YES"),
5613       -- Whether or not we support "Foo from foo-0.1-XXX:Foo" syntax in
5614       -- installed package info.
5615       ("Support reexported-modules",  "YES"),
5616       -- Whether or not we support extended @-package foo (Foo)@ syntax.
5617       ("Support thinning and renaming package flags", "YES"),
5618       -- Whether or not we support Backpack.
5619       ("Support Backpack", "YES"),
5620       -- If true, we require that the 'id' field in installed package info
5621       -- match what is passed to the @-this-unit-id@ flag for modules
5622       -- built in it
5623       ("Requires unified installed package IDs", "YES"),
5624       -- Whether or not we support the @-this-package-key@ flag.  Prefer
5625       -- "Uses unit IDs" over it.
5626       ("Uses package keys",           "YES"),
5627       -- Whether or not we support the @-this-unit-id@ flag
5628       ("Uses unit IDs",               "YES"),
5629       -- Whether or not GHC compiles libraries as dynamic by default
5630       ("Dynamic by default",          showBool $ dYNAMIC_BY_DEFAULT dflags),
5631       -- Whether or not GHC was compiled using -dynamic
5632       ("GHC Dynamic",                 showBool dynamicGhc),
5633       -- Whether or not GHC was compiled using -prof
5634       ("GHC Profiled",                showBool rtsIsProfiled),
5635       ("Debug on",                    showBool debugIsOn),
5636       ("LibDir",                      topDir dflags),
5637       -- The path of the global package database used by GHC
5638       ("Global Package DB",           systemPackageConfig dflags)
5639      ]
5640  where
5641    showBool True  = "YES"
5642    showBool False = "NO"
5643    isWindows = platformOS (targetPlatform dflags) == OSMinGW32
5644    expandDirectories :: FilePath -> Maybe FilePath -> String -> String
5645    expandDirectories topd mtoold = expandToolDir mtoold . expandTopDir topd
5646
5647-- Produced by deriveConstants
5648#include "GHCConstantsHaskellWrappers.hs"
5649
5650bLOCK_SIZE_W :: DynFlags -> Int
5651bLOCK_SIZE_W dflags = bLOCK_SIZE dflags `quot` wORD_SIZE dflags
5652
5653wORD_SIZE_IN_BITS :: DynFlags -> Int
5654wORD_SIZE_IN_BITS dflags = wORD_SIZE dflags * 8
5655
5656wordAlignment :: DynFlags -> Alignment
5657wordAlignment dflags = alignmentOf (wORD_SIZE dflags)
5658
5659tAG_MASK :: DynFlags -> Int
5660tAG_MASK dflags = (1 `shiftL` tAG_BITS dflags) - 1
5661
5662mAX_PTR_TAG :: DynFlags -> Int
5663mAX_PTR_TAG = tAG_MASK
5664
5665-- Might be worth caching these in targetPlatform?
5666tARGET_MIN_INT, tARGET_MAX_INT, tARGET_MAX_WORD :: DynFlags -> Integer
5667tARGET_MIN_INT dflags
5668    = case platformWordSize (targetPlatform dflags) of
5669      PW4 -> toInteger (minBound :: Int32)
5670      PW8 -> toInteger (minBound :: Int64)
5671tARGET_MAX_INT dflags
5672    = case platformWordSize (targetPlatform dflags) of
5673      PW4 -> toInteger (maxBound :: Int32)
5674      PW8 -> toInteger (maxBound :: Int64)
5675tARGET_MAX_WORD dflags
5676    = case platformWordSize (targetPlatform dflags) of
5677      PW4 -> toInteger (maxBound :: Word32)
5678      PW8 -> toInteger (maxBound :: Word64)
5679
5680
5681{- -----------------------------------------------------------------------------
5682Note [DynFlags consistency]
5683~~~~~~~~~~~~~~~~~~~~~~~~~~~~
5684
5685There are a number of number of DynFlags configurations which either
5686do not make sense or lead to unimplemented or buggy codepaths in the
5687compiler. makeDynFlagsConsistent is responsible for verifying the validity
5688of a set of DynFlags, fixing any issues, and reporting them back to the
5689caller.
5690
5691GHCi and -O
5692---------------
5693
5694When using optimization, the compiler can introduce several things
5695(such as unboxed tuples) into the intermediate code, which GHCi later
5696chokes on since the bytecode interpreter can't handle this (and while
5697this is arguably a bug these aren't handled, there are no plans to fix
5698it.)
5699
5700While the driver pipeline always checks for this particular erroneous
5701combination when parsing flags, we also need to check when we update
5702the flags; this is because API clients may parse flags but update the
5703DynFlags afterwords, before finally running code inside a session (see
5704T10052 and #10052).
5705-}
5706
5707-- | Resolve any internal inconsistencies in a set of 'DynFlags'.
5708-- Returns the consistent 'DynFlags' as well as a list of warnings
5709-- to report to the user.
5710makeDynFlagsConsistent :: DynFlags -> (DynFlags, [Located String])
5711-- Whenever makeDynFlagsConsistent does anything, it starts over, to
5712-- ensure that a later change doesn't invalidate an earlier check.
5713-- Be careful not to introduce potential loops!
5714makeDynFlagsConsistent dflags
5715 -- Disable -dynamic-too on Windows (#8228, #7134, #5987)
5716 | os == OSMinGW32 && gopt Opt_BuildDynamicToo dflags
5717    = let dflags' = gopt_unset dflags Opt_BuildDynamicToo
5718          warn    = "-dynamic-too is not supported on Windows"
5719      in loop dflags' warn
5720 | hscTarget dflags == HscC &&
5721   not (platformUnregisterised (targetPlatform dflags))
5722    = if platformMisc_ghcWithNativeCodeGen $ platformMisc dflags
5723      then let dflags' = dflags { hscTarget = HscAsm }
5724               warn = "Compiler not unregisterised, so using native code generator rather than compiling via C"
5725           in loop dflags' warn
5726      else let dflags' = dflags { hscTarget = HscLlvm }
5727               warn = "Compiler not unregisterised, so using LLVM rather than compiling via C"
5728           in loop dflags' warn
5729 | gopt Opt_Hpc dflags && hscTarget dflags == HscInterpreted
5730    = let dflags' = gopt_unset dflags Opt_Hpc
5731          warn = "Hpc can't be used with byte-code interpreter. Ignoring -fhpc."
5732      in loop dflags' warn
5733 | hscTarget dflags `elem` [HscAsm, HscLlvm] &&
5734   platformUnregisterised (targetPlatform dflags)
5735    = loop (dflags { hscTarget = HscC })
5736           "Compiler unregisterised, so compiling via C"
5737 | hscTarget dflags == HscAsm &&
5738   not (platformMisc_ghcWithNativeCodeGen $ platformMisc dflags)
5739      = let dflags' = dflags { hscTarget = HscLlvm }
5740            warn = "No native code generator, so using LLVM"
5741        in loop dflags' warn
5742 | not (osElfTarget os) && gopt Opt_PIE dflags
5743    = loop (gopt_unset dflags Opt_PIE)
5744           "Position-independent only supported on ELF platforms"
5745 | os == OSDarwin &&
5746   arch == ArchX86_64 &&
5747   not (gopt Opt_PIC dflags)
5748    = loop (gopt_set dflags Opt_PIC)
5749           "Enabling -fPIC as it is always on for this platform"
5750 | Left err <- checkOptLevel (optLevel dflags) dflags
5751    = loop (updOptLevel 0 dflags) err
5752
5753 | LinkInMemory <- ghcLink dflags
5754 , not (gopt Opt_ExternalInterpreter dflags)
5755 , rtsIsProfiled
5756 , isObjectTarget (hscTarget dflags)
5757 , WayProf `notElem` ways dflags
5758    = loop dflags{ways = WayProf : ways dflags}
5759         "Enabling -prof, because -fobject-code is enabled and GHCi is profiled"
5760
5761 | otherwise = (dflags, [])
5762    where loc = mkGeneralSrcSpan (fsLit "when making flags consistent")
5763          loop updated_dflags warning
5764              = case makeDynFlagsConsistent updated_dflags of
5765                (dflags', ws) -> (dflags', L loc warning : ws)
5766          platform = targetPlatform dflags
5767          arch = platformArch platform
5768          os   = platformOS   platform
5769
5770
5771--------------------------------------------------------------------------
5772-- Do not use unsafeGlobalDynFlags!
5773--
5774-- unsafeGlobalDynFlags is a hack, necessary because we need to be able
5775-- to show SDocs when tracing, but we don't always have DynFlags
5776-- available.
5777--
5778-- Do not use it if you can help it. You may get the wrong value, or this
5779-- panic!
5780
5781-- | This is the value that 'unsafeGlobalDynFlags' takes before it is
5782-- initialized.
5783defaultGlobalDynFlags :: DynFlags
5784defaultGlobalDynFlags =
5785    (defaultDynFlags settings llvmConfig) { verbosity = 2 }
5786  where
5787    settings = panic "v_unsafeGlobalDynFlags: settings not initialised"
5788    llvmConfig = panic "v_unsafeGlobalDynFlags: llvmConfig not initialised"
5789
5790#if GHC_STAGE < 2
5791GLOBAL_VAR(v_unsafeGlobalDynFlags, defaultGlobalDynFlags, DynFlags)
5792#else
5793SHARED_GLOBAL_VAR( v_unsafeGlobalDynFlags
5794                 , getOrSetLibHSghcGlobalDynFlags
5795                 , "getOrSetLibHSghcGlobalDynFlags"
5796                 , defaultGlobalDynFlags
5797                 , DynFlags )
5798#endif
5799
5800unsafeGlobalDynFlags :: DynFlags
5801unsafeGlobalDynFlags = unsafePerformIO $ readIORef v_unsafeGlobalDynFlags
5802
5803setUnsafeGlobalDynFlags :: DynFlags -> IO ()
5804setUnsafeGlobalDynFlags = writeIORef v_unsafeGlobalDynFlags
5805
5806-- -----------------------------------------------------------------------------
5807-- SSE and AVX
5808
5809-- TODO: Instead of using a separate predicate (i.e. isSse2Enabled) to
5810-- check if SSE is enabled, we might have x86-64 imply the -msse2
5811-- flag.
5812
5813data SseVersion = SSE1
5814                | SSE2
5815                | SSE3
5816                | SSE4
5817                | SSE42
5818                deriving (Eq, Ord)
5819
5820isSseEnabled :: DynFlags -> Bool
5821isSseEnabled dflags = case platformArch (targetPlatform dflags) of
5822    ArchX86_64 -> True
5823    ArchX86    -> True
5824    _          -> False
5825
5826isSse2Enabled :: DynFlags -> Bool
5827isSse2Enabled dflags = case platformArch (targetPlatform dflags) of
5828  -- We Assume  SSE1 and SSE2 operations are available on both
5829  -- x86 and x86_64. Historically we didn't default to SSE2 and
5830  -- SSE1 on x86, which results in defacto nondeterminism for how
5831  -- rounding behaves in the associated x87 floating point instructions
5832  -- because variations in the spill/fpu stack placement of arguments for
5833  -- operations would change the precision and final result of what
5834  -- would otherwise be the same expressions with respect to single or
5835  -- double precision IEEE floating point computations.
5836    ArchX86_64 -> True
5837    ArchX86    -> True
5838    _          -> False
5839
5840
5841isSse4_2Enabled :: DynFlags -> Bool
5842isSse4_2Enabled dflags = sseVersion dflags >= Just SSE42
5843
5844isAvxEnabled :: DynFlags -> Bool
5845isAvxEnabled dflags = avx dflags || avx2 dflags || avx512f dflags
5846
5847isAvx2Enabled :: DynFlags -> Bool
5848isAvx2Enabled dflags = avx2 dflags || avx512f dflags
5849
5850isAvx512cdEnabled :: DynFlags -> Bool
5851isAvx512cdEnabled dflags = avx512cd dflags
5852
5853isAvx512erEnabled :: DynFlags -> Bool
5854isAvx512erEnabled dflags = avx512er dflags
5855
5856isAvx512fEnabled :: DynFlags -> Bool
5857isAvx512fEnabled dflags = avx512f dflags
5858
5859isAvx512pfEnabled :: DynFlags -> Bool
5860isAvx512pfEnabled dflags = avx512pf dflags
5861
5862-- -----------------------------------------------------------------------------
5863-- BMI2
5864
5865data BmiVersion = BMI1
5866                | BMI2
5867                deriving (Eq, Ord)
5868
5869isBmiEnabled :: DynFlags -> Bool
5870isBmiEnabled dflags = case platformArch (targetPlatform dflags) of
5871    ArchX86_64 -> bmiVersion dflags >= Just BMI1
5872    ArchX86    -> bmiVersion dflags >= Just BMI1
5873    _          -> False
5874
5875isBmi2Enabled :: DynFlags -> Bool
5876isBmi2Enabled dflags = case platformArch (targetPlatform dflags) of
5877    ArchX86_64 -> bmiVersion dflags >= Just BMI2
5878    ArchX86    -> bmiVersion dflags >= Just BMI2
5879    _          -> False
5880
5881-- -----------------------------------------------------------------------------
5882-- Linker/compiler information
5883
5884-- LinkerInfo contains any extra options needed by the system linker.
5885data LinkerInfo
5886  = GnuLD    [Option]
5887  | GnuGold  [Option]
5888  | LlvmLLD  [Option]
5889  | DarwinLD [Option]
5890  | SolarisLD [Option]
5891  | AixLD    [Option]
5892  | UnknownLD
5893  deriving Eq
5894
5895-- CompilerInfo tells us which C compiler we're using
5896data CompilerInfo
5897   = GCC
5898   | Clang
5899   | AppleClang
5900   | AppleClang51
5901   | UnknownCC
5902   deriving Eq
5903
5904
5905-- | Should we use `-XLinker -rpath` when linking or not?
5906-- See Note [-fno-use-rpaths]
5907useXLinkerRPath :: DynFlags -> OS -> Bool
5908useXLinkerRPath _ OSDarwin = False -- See Note [Dynamic linking on macOS]
5909useXLinkerRPath dflags _ = gopt Opt_RPath dflags
5910
5911{-
5912Note [-fno-use-rpaths]
5913~~~~~~~~~~~~~~~~~~~~~~
5914
5915First read, Note [Dynamic linking on macOS] to understand why on darwin we never
5916use `-XLinker -rpath`.
5917
5918The specification of `Opt_RPath` is as follows:
5919
5920The default case `-fuse-rpaths`:
5921* On darwin, never use `-Xlinker -rpath -Xlinker`, always inject the rpath
5922  afterwards, see `runInjectRPaths`. There is no way to use `-Xlinker` on darwin
5923  as things stand but it wasn't documented in the user guide before this patch how
5924  `-fuse-rpaths` should behave and the fact it was always disabled on darwin.
5925* Otherwise, use `-Xlinker -rpath -Xlinker` to set the rpath of the executable,
5926  this is the normal way you should set the rpath.
5927
5928The case of `-fno-use-rpaths`
5929* Never inject anything into the rpath.
5930
5931When this was first implemented, `Opt_RPath` was disabled on darwin, but
5932the rpath was still always augmented by `runInjectRPaths`, and there was no way to
5933stop this. This was problematic because you couldn't build an executable in CI
5934with a clean rpath.
5935
5936-}
5937
5938-- -----------------------------------------------------------------------------
5939-- RTS hooks
5940
5941-- Convert sizes like "3.5M" into integers
5942decodeSize :: String -> Integer
5943decodeSize str
5944  | c == ""      = truncate n
5945  | c == "K" || c == "k" = truncate (n * 1000)
5946  | c == "M" || c == "m" = truncate (n * 1000 * 1000)
5947  | c == "G" || c == "g" = truncate (n * 1000 * 1000 * 1000)
5948  | otherwise            = throwGhcException (CmdLineError ("can't decode size: " ++ str))
5949  where (m, c) = span pred str
5950        n      = readRational m
5951        pred c = isDigit c || c == '.'
5952
5953foreign import ccall unsafe "setHeapSize"       setHeapSize       :: Int -> IO ()
5954foreign import ccall unsafe "enableTimingStats" enableTimingStats :: IO ()
5955
5956-- -----------------------------------------------------------------------------
5957-- Types for managing temporary files.
5958--
5959-- these are here because FilesToClean is used in DynFlags
5960
5961-- | A collection of files that must be deleted before ghc exits.
5962-- The current collection
5963-- is stored in an IORef in DynFlags, 'filesToClean'.
5964data FilesToClean = FilesToClean {
5965  ftcGhcSession :: !(Set FilePath),
5966  -- ^ Files that will be deleted at the end of runGhc(T)
5967  ftcCurrentModule :: !(Set FilePath)
5968  -- ^ Files that will be deleted the next time
5969  -- 'FileCleanup.cleanCurrentModuleTempFiles' is called, or otherwise at the
5970  -- end of the session.
5971  }
5972
5973-- | An empty FilesToClean
5974emptyFilesToClean :: FilesToClean
5975emptyFilesToClean = FilesToClean Set.empty Set.empty
5976