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