4.19. Flag reference

This section is a quick-reference for GHC's command-line flags. For each flag, we also list its static/dynamic status (see Section 4.3, “Static, Dynamic, and Mode options”), and the flag's opposite (if available).

4.19.1. Verbosity options

More details in Section 4.6, “Verbosity options”

FlagDescriptionStatic/DynamicReverse
-vverbose mode (equivalent to -v3)dynamic-
-vnset verbosity leveldynamic-
-fprint-explicit-forallsprint explicit forall quantification in typesdynamic-fno-print-explicit-foralls
-fprint-explicit-kindsprint explicit kind foralls and kind arguments in typesdynamic-fno-print-explicit-kinds
-ferror-spansoutput full span in error messagesdynamic-
-HsizeSet the minimum heap size to sizedynamic-
-Rghc-timingSummarise timing stats for GHC (same as +RTS -tstderr)dynamic-

4.19.2. Alternative modes of operation

More details in Section 4.5, “Modes of operation”

FlagDescriptionStatic/DynamicReverse
--help,-?Disply helpmode-
--interactiveInteractive mode - normally used by just running ghci; see Chapter 2, Using GHCi for details.mode-
--makeBuild a multi-module Haskell program, automatically figuring out dependencies. Likely to be much easier, and faster, than using make; see Section 4.5.1, “Using ghc --make for details..mode-
-e exprEvaluate expr; see Section 4.5.2, “Expression evaluation mode” for details.mode-
--show-ifaceDisplay the contents of an interface file.mode-
-MGenerate dependency information suitable for use in a Makefile; see Section 4.7.12, “Dependency generation” for details.mode-
--supported-extensions, --supported-languagesdisplay the supported language extensionsmode-
--show-optionsdisplay the supported command line optionsmode-
--infodisplay information about the compilermode-
--version, -Vdisplay GHC versionmode-
--numeric-versiondisplay GHC version (numeric only)mode-
--print-libdirdisplay GHC library directorymode-

4.19.3. Which phases to run

Section 4.5.3, “Batch compiler mode”

FlagDescriptionStatic/DynamicReverse
-EStop after preprocessing (.hspp file)mode-
-CStop after generating C (.hc file)mode-
-SStop after generating assembly (.s file)mode-
-cStop after generating object (.o) filemode-
-x suffixOverride default behaviour for source filesdynamic-

4.19.4. Redirecting output

Section 4.7.4, “Redirecting the compilation output(s)”

FlagDescriptionStatic/DynamicReverse
-hcsuf suffixset the suffix to use for intermediate C filesdynamic-
-hidir dirset directory for interface filesdynamic-
-hisuf suffixset the suffix to use for interface filesdynamic-
-o filenameset output filenamedynamic-
-odir dirset directory for object filesdynamic-
-ohi filenameset the filename in which to put the interfacedynamic 
-osuf suffixset the output file suffixdynamic-
-stubdir dirredirect FFI stub filesdynamic-
-dumpdir dirredirect dump filesdynamic-
-outputdir dirset output directorydynamic-

4.19.5. Keeping intermediate files

Section 4.7.5, “Keeping Intermediate Files”

FlagDescriptionStatic/DynamicReverse
-keep-hc-file or -keep-hc-filesretain intermediate .hc filesdynamic-
-keep-llvm-file or -keep-llvm-filesretain intermediate LLVM .ll filesdynamic-
-keep-s-file or -keep-s-filesretain intermediate .s filesdynamic-
-keep-tmp-filesretain all intermediate temporary filesdynamic-

4.19.6. Temporary files

Section 4.7.6, “Redirecting temporary files”

FlagDescriptionStatic/DynamicReverse
-tmpdirset the directory for temporary filesdynamic-

4.19.7. Finding imports

Section 4.7.3, “The search path”

FlagDescriptionStatic/DynamicReverse
-idir1:dir2:...add dir, dir2, etc. to import pathdynamic/:set-
-iEmpty the import directory listdynamic/:set-

4.19.8. Interface file options

Section 4.7.7, “Other options related to interface files”

FlagDescriptionStatic/DynamicReverse
-ddump-hiDump the new interface to stdoutdynamic-
-ddump-hi-diffsShow the differences vs. the old interfacedynamic-
-ddump-minimal-importsDump a minimal set of importsdynamic-
--show-iface fileSee Section 4.5, “Modes of operation”.  

4.19.9. Recompilation checking

Section 4.7.8, “The recompilation checker”

FlagDescriptionStatic/DynamicReverse
-fforce-recompTurn off recompilation checking. This is implied by any -ddump-X option when compiling a single file (i.e. when using -c).dynamic-fno-force-recomp

4.19.10. Interactive-mode options

Section 2.9, “The .ghci file”

FlagDescriptionStatic/DynamicReverse
-ignore-dot-ghciDisable reading of .ghci filesdynamic-
-ghci-scriptRead additional .ghci filesdynamic-
-fbreak-on-errorBreak on uncaught exceptions and errorsdynamic-fno-break-on-error
-fbreak-on-exceptionBreak on any exception throwndynamic-fno-break-on-exception
-fghci-hist-size=nSet the number of entries GHCi keeps for :historydynamic(default is 50)
-fprint-evld-with-showEnable usage of Show instances in :printdynamic-fno-print-evld-with-show
-fprint-bind-resultTurn on printing of binding results in GHCidynamic-fno-print-bind-result
-fno-print-bind-contentsTurn off printing of binding contents in GHCidynamic-
-fno-implicit-import-qualifiedTurn off implicit qualified import of everything in GHCidynamic-
-interactive-printSelect the function to use for printing evaluated expressions in GHCidynamic-

4.19.11. Packages

Section 4.9, “ Packages ”

FlagDescriptionStatic/DynamicReverse
-this-package-key PCompile to be part of package Pdynamic-
-package PExpose package Pdynamic/:set-
-hide-all-packagesHide all packages by defaultdynamic-
-hide-package nameHide package Pdynamic/:set-
-ignore-package nameIgnore package Pdynamic/:set-
-package-db fileAdd file to the package db stack.dynamic-
-clear-package-dbClear the package db stack.dynamic-
-no-global-package-dbRemove the global package db from the stack.dynamic-
-global-package-dbAdd the global package db to the stack.dynamic-
-no-user-package-dbRemove the user's package db from the stack.dynamic-
-user-package-dbAdd the user's package db to the stack.dynamic-
-no-auto-link-packagesDon't automatically link in the base and rts packages.dynamic-
-trust PExpose package P and set it to be trusteddynamic/:set-
-distrust PExpose package P and set it to be distrusteddynamic/:set-
-distrust-all Distrust all packages by defaultdynamic/:set-

4.19.12. Language options

Language options can be enabled either by a command-line option -Xblah, or by a {-# LANGUAGE blah #-} pragma in the file itself. See Section 7.1, “Language options”. Some options are enabled using -f* flags.

FlagDescriptionStatic/DynamicReverse
-fcontext-stack=nset the limit for type-class context reduction. Default is 100.dynamic 
-fglasgow-extsDeprecated. Enable most language extensions; see Section 7.1, “Language options” for exactly which ones.dynamic-fno-glasgow-exts
-firrefutable-tuplesMake tuple pattern matching irrefutabledynamic-fno-irrefutable-tuples
-fpackage-trustEnable Safe Haskell trusted package requirement for trustworthy modules.dynamic-
-ftype-function-depth=nset the limit for type function reductions. Default is 200.dynamic 
-XAllowAmbiguousTypesAllow the user to write ambiguous types, and the type inference engine to infer them. dynamic-XNoAllowAmbiguousTypes
-XArrowsEnable arrow notation extensiondynamic-XNoArrows
-XAutoDeriveTypeableAs of GHC 7.10, this option is not needed, and should not be used. Automatically derive Typeable instances for every datatype and type class declaration. Implies -XDeriveDataTypeable.dynamic-XNoAutoDeriveTypeable
-XBangPatternsEnable bang patterns.dynamic-XNoBangPatterns
-XBinaryLiteralsEnable support for binary literals.dynamic-XNoBinaryLiterals
-XCApiFFIEnable the CAPI calling convention.dynamic-XNoCAPIFFI
-XConstrainedClassMethodsEnable constrained class methods.dynamic-XNoConstrainedClassMethods
-XConstraintKindsEnable a kind of constraints.dynamic-XNoConstraintKinds
-XCPPEnable the C preprocessor.dynamic-XNoCPP
-XDataKindsEnable datatype promotion.dynamic-XNoDataKinds
-XDefaultSignaturesEnable default signatures.dynamic-XNoDefaultSignatures
-XDeriveAnyClassEnable deriving for any class.dynamic-XNoDeriveAnyClass
-XDeriveDataTypeableEnable deriving for the Data class. Implied by -XAutoDeriveTypeable.dynamic-XNoDeriveDataTypeable
-XDeriveFunctorEnable deriving for the Functor class. Implied by -XDeriveTraversable.dynamic-XNoDeriveFunctor
-XDeriveFoldableEnable deriving for the Foldable class. Implied by -XDeriveTraversable.dynamic-XNoDeriveFoldable
-XDeriveGenericEnable deriving for the Generic class.dynamic-XNoDeriveGeneric
-XDeriveTraversableEnable deriving for the Traversable class. Implies -XDeriveFunctor and -XDeriveFoldable.dynamic-XNoDeriveTraversable
-XDisambiguateRecordFieldsEnable record field disambiguation. Implied by -XRecordWildCards.dynamic-XNoDisambiguateRecordFields
-XEmptyCaseAllow empty case alternatives.dynamic-XNoEmptyCase
-XEmptyDataDeclsEnable empty data declarations.dynamic-XNoEmptyDataDecls
-XExistentialQuantificationEnable existential quantification.dynamic-XNoExistentialQuantification
-XExplicitForAllEnable explicit universal quantification. Implied by -XScopedTypeVariables, -XLiberalTypeSynonyms, -XRankNTypes and -XExistentialQuantification. dynamic-XNoExplicitForAll
-XExplicitNamespacesEnable using the keyword type to specify the namespace of entries in imports and exports (Section 7.3.26.4, “Explicit namespaces in import/export”). Implied by -XTypeOperators and -XTypeFamilies.dynamic-XNoExplicitNamespaces
-XExtendedDefaultRulesUse GHCi's extended default rules in a normal module.dynamic-XNoExtendedDefaultRules
-XFlexibleContextsEnable flexible contexts. Implied by -XImplicitParams.dynamic-XNoFlexibleContexts
-XFlexibleInstancesEnable flexible instances. Implies -XTypeSynonymInstances. Implied by -XImplicitParams.dynamic-XNoFlexibleInstances
-XForeignFunctionInterfaceEnable foreign function interface.dynamic-XNoForeignFunctionInterface
-XFunctionalDependenciesEnable functional dependencies. Implies -XMultiParamTypeClasses.dynamic-XNoFunctionalDependencies
-XGADTsEnable generalised algebraic data types. Implies -XGADTSyntax and -XMonoLocalBinds.dynamic-XNoGADTs
-XGADTSyntaxEnable generalised algebraic data type syntax. dynamic-XNoGADTSyntax
-XGeneralizedNewtypeDerivingEnable newtype deriving.dynamic-XNoGeneralizedNewtypeDeriving
-XGenericsDeprecated, does nothing. No longer enables generic classes. See also GHC's support for generic programming.dynamic-XNoGenerics
-XImplicitParamsEnable Implicit Parameters. Implies -XFlexibleContexts and -XFlexibleInstances.dynamic-XNoImplicitParams
-XNoImplicitPreludeDon't implicitly import Prelude. Implied by -XRebindableSyntax.dynamic-XImplicitPrelude
-XImpredicativeTypesEnable impredicative types. Implies -XRankNTypes.dynamic-XNoImpredicativeTypes
-XIncoherentInstancesEnable incoherent instances. Implies -XOverlappingInstances.dynamic-XNoIncoherentInstances
-XInstanceSigsEnable instance signatures.dynamic-XNoInstanceSigs
-XInterruptibleFFIEnable interruptible FFI.dynamic-XNoInterruptibleFFI
-XKindSignaturesEnable kind signatures. Implied by -XTypeFamilies and -XPolyKinds.dynamic-XNoKindSignatures
-XLambdaCaseEnable lambda-case expressions.dynamic-XNoLambdaCase
-XLiberalTypeSynonymsEnable liberalised type synonyms.dynamic-XNoLiberalTypeSynonyms
-XMagicHashAllow "#" as a postfix modifier on identifiers.dynamic-XNoMagicHash
-XMonadComprehensionsEnable monad comprehensions.dynamic-XNoMonadComprehensions
-XMonoLocalBindsEnable do not generalise local bindings. Implied by -XTypeFamilies and -XGADTs. dynamic-XNoMonoLocalBinds
-XNoMonomorphismRestrictionDisable the monomorphism restriction.dynamic-XMonomorphismRestriction
-XMultiParamTypeClassesEnable multi parameter type classes. Implied by -XFunctionalDependencies.dynamic-XNoMultiParamTypeClasses
-XMultiWayIfEnable multi-way if-expressions.dynamic-XNoMultiWayIf
-XNamedFieldPunsEnable record puns.dynamic-XNoNamedFieldPuns
-XNamedWildCardsEnable named wildcards.dynamic-XNoNamedWildCards
-XNegativeLiteralsEnable support for negative literals.dynamic-XNoNegativeLiterals
-XNoNPlusKPatternsDisable support for n+k patterns.dynamic-XNPlusKPatterns
-XNullaryTypeClassesDeprecated, does nothing. nullary (no parameter) type classes are now enabled using -XMultiParamTypeClasses.dynamic-XNoNullaryTypeClasses
-XNumDecimalsEnable support for 'fractional' integer literals.dynamic-XNoNumDecimals
-XOverlappingInstancesEnable overlapping instances.dynamic-XNoOverlappingInstances
-XOverloadedListsEnable overloaded lists. dynamic-XNoOverloadedLists
-XOverloadedStringsEnable overloaded string literals. dynamic-XNoOverloadedStrings
-XPackageImportsEnable package-qualified imports.dynamic-XNoPackageImports
-XParallelArraysEnable parallel arrays. Implies -XParallelListComp.dynamic-XNoParallelArrays
-XParallelListCompEnable parallel list comprehensions. Implied by -XParallelArrays.dynamic-XNoParallelListComp
-XPartialTypeSignaturesEnable partial type signatures.dynamic-XNoPartialTypeSignatures
-XPatternGuardsEnable pattern guards.dynamic-XNoPatternGuards
-XPatternSynonymsEnable pattern synonyms.dynamic-XNoPatternSynonyms
-XPolyKindsEnable kind polymorphism. Implies -XKindSignatures.dynamic-XNoPolyKinds
-XPolymorphicComponentsEnable polymorphic components for data constructors.dynamic, synonym for -XRankNTypes-XNoPolymorphicComponents
-XPostfixOperatorsEnable postfix operators.dynamic-XNoPostfixOperators
-XQuasiQuotesEnable quasiquotation.dynamic-XNoQuasiQuotes
-XRank2TypesEnable rank-2 types.dynamic, synonym for -XRankNTypes-XNoRank2Types
-XRankNTypesEnable rank-N types. Implied by -XImpredicativeTypes.dynamic-XNoRankNTypes
-XRebindableSyntaxEmploy rebindable syntax. Implies -XNoImplicitPrelude.dynamic-XNoRebindableSyntax
-XRecordWildCardsEnable record wildcards. Implies -XDisambiguateRecordFields.dynamic-XNoRecordWildCards
-XRecursiveDoEnable recursive do (mdo) notation.dynamic-XNoRecursiveDo
-XRelaxedPolyRec(deprecated) Relaxed checking for mutually-recursive polymorphic functions.dynamic-XNoRelaxedPolyRec
-XRoleAnnotationsEnable role annotations.dynamic-XNoRoleAnnotations
-XSafeEnable the Safe Haskell Safe mode.dynamic-
-XScopedTypeVariablesEnable lexically-scoped type variables. dynamic-XNoScopedTypeVariables
-XStandaloneDerivingEnable standalone deriving.dynamic-XNoStandaloneDeriving
-XTemplateHaskellEnable Template Haskell.dynamic-XNoTemplateHaskell
-XNoTraditionalRecordSyntaxDisable support for traditional record syntax (as supported by Haskell 98) C {f = x}dynamic-XTraditionalRecordSyntax
-XTransformListCompEnable generalised list comprehensions.dynamic-XNoTransformListComp
-XTrustworthyEnable the Safe Haskell Trustworthy mode.dynamic-
-XTupleSectionsEnable tuple sections.dynamic-XNoTupleSections
-XTypeFamiliesEnable type families. Implies -XExplicitNamespaces, -XKindSignatures and -XMonoLocalBinds.dynamic-XNoTypeFamilies
-XTypeOperatorsEnable type operators. Implies -XExplicitNamespaces.dynamic-XNoTypeOperators
-XTypeSynonymInstancesEnable type synonyms in instance heads. Implied by -XFlexibleInstances.dynamic-XNoTypeSynonymInstances
-XUnboxedTuplesEnable unboxed tuples.dynamic-XNoUnboxedTuples
-XUndecidableInstancesEnable undecidable instances.dynamic-XNoUndecidableInstances
-XUnicodeSyntaxEnable unicode syntax.dynamic-XNoUnicodeSyntax
-XUnliftedFFITypesEnable unlifted FFI types.dynamic-XNoUnliftedFFITypes
-XUnsafeEnable Safe Haskell Unsafe mode.dynamic-
-XViewPatternsEnable view patterns.dynamic-XNoViewPatterns

4.19.13. Warnings

Section 4.8, “Warnings and sanity-checking”

FlagDescriptionStatic/DynamicReverse
-Wenable normal warningsdynamic-w
-wdisable all warningsdynamic-
-Wallenable almost all warnings (details in Section 4.8, “Warnings and sanity-checking”)dynamic-w
-Werrormake warnings fataldynamic-Wwarn
-Wwarnmake warnings non-fataldynamic-Werror
-fdefer-type-errors Turn type errors into warnings, deferring the error until runtime. Implies -fdefer-typed-holes. dynamic-fno-defer-type-errors
-fdefer-typed-holes Convert typed hole errors into warnings, deferring the error until runtime. Implied by -fdefer-type-errors. See also -fwarn-typed-holes. dynamic-fno-defer-typed-holes
-fhelpful-errorsMake suggestions for mis-spelled names.dynamic-fno-helpful-errors
-fwarn-deprecated-flagswarn about uses of commandline flags that are deprecateddynamic-fno-warn-deprecated-flags
-fwarn-duplicate-constraintswarn when a constraint appears duplicated in a type signaturedynamic-fno-warn-duplicate-constraints
-fwarn-duplicate-exportswarn when an entity is exported multiple timesdynamic-fno-warn-duplicate-exports
-fwarn-hi-shadowingwarn when a .hi file in the current directory shadows a librarydynamic-fno-warn-hi-shadowing
-fwarn-identitieswarn about uses of Prelude numeric conversions that are probably the identity (and hence could be omitted)dynamic-fno-warn-identities
-fwarn-implicit-preludewarn when the Prelude is implicitly importeddynamic-fno-warn-implicit-prelude
-fwarn-incomplete-patternswarn when a pattern match could faildynamic-fno-warn-incomplete-patterns
-fwarn-incomplete-uni-patternswarn when a pattern match in a lambda expression or pattern binding could faildynamic-fno-warn-incomplete-uni-patterns
-fwarn-incomplete-record-updateswarn when a record update could faildynamic-fno-warn-incomplete-record-updates
-fwarn-lazy-unlifted-bindings(deprecated) warn when a pattern binding looks lazy but must be strictdynamic-fno-warn-lazy-unlifted-bindings
-fwarn-missing-fieldswarn when fields of a record are uninitialiseddynamic-fno-warn-missing-fields
-fwarn-missing-import-listswarn when an import declaration does not explicitly list all the names brought into scopedynamic-fnowarn-missing-import-lists
-fwarn-missing-methodswarn when class methods are undefineddynamic-fno-warn-missing-methods
-fwarn-missing-signatureswarn about top-level functions without signaturesdynamic-fno-warn-missing-signatures
-fwarn-missing-exported-sigswarn about top-level functions without signatures, only if they are exported. takes precedence over -fwarn-missing-signaturesdynamic-fno-warn-missing-exported-sigs
-fwarn-missing-local-sigswarn about polymorphic local bindings without signaturesdynamic-fno-warn-missing-local-sigs
-fwarn-monomorphism-restrictionwarn when the Monomorphism Restriction is applieddynamic-fno-warn-monomorphism-restriction
-fwarn-name-shadowingwarn when names are shadoweddynamic-fno-warn-name-shadowing
-fwarn-orphans, -fwarn-auto-orphanswarn when the module contains orphan instance declarations or rewrite rulesdynamic-fno-warn-orphans, -fno-warn-auto-orphans
-fwarn-overlapping-patternswarn about overlapping patternsdynamic-fno-warn-overlapping-patterns
-fwarn-tabswarn if there are tabs in the source filedynamic-fno-warn-tabs
-fwarn-type-defaultswarn when defaulting happensdynamic-fno-warn-type-defaults
-fwarn-unrecognised-pragmaswarn about uses of pragmas that GHC doesn't recognisedynamic-fno-warn-unrecognised-pragmas
-fwarn-unticked-promoted-constructorswarn if promoted constructors are not ticked dynamic-fno-warn-unticked-promoted-constructors
-fwarn-unused-bindswarn about bindings that are unuseddynamic-fno-warn-unused-binds
-fwarn-unused-importswarn about unnecessary importsdynamic-fno-warn-unused-imports
-fwarn-unused-matcheswarn about variables in patterns that aren't useddynamic-fno-warn-unused-matches
-fwarn-unused-do-bindwarn about do bindings that appear to throw away values of types other than ()dynamic-fno-warn-unused-do-bind
-fwarn-wrong-do-bindwarn about do bindings that appear to throw away monadic values that you should have bound insteaddynamic-fno-warn-wrong-do-bind
-fwarn-unsafewarn if the module being compiled is regarded to be unsafe. Should be used to check the safety status of modules when using safe inference. Works on all module types, even those using explicit Safe Haskell modes (such as -XTrustworthy) and so can be used to have the compiler check any assumptions made.dynamic-fno-warn-unsafe
-fwarn-safewarn if the module being compiled is regarded to be safe. Should be used to check the safety status of modules when using safe inference. Works on all module types, even those using explicit Safe Haskell modes (such as -XTrustworthy) and so can be used to have the compiler check any assumptions made.dynamic-fno-warn-safe
-fwarn-trustworthy-safewarn if the module being compiled is marked as -XTrustworthy but it could instead be marked as -XSafe, a more informative bound. Can be used to detect once a Safe Haskell bound can be improved as dependencies are updated.dynamic-fno-warn-safe
-fwarn-warnings-deprecationswarn about uses of functions & types that have warnings or deprecated pragmasdynamic-fno-warn-warnings-deprecations
-fwarn-amp(deprecated) warn on definitions conflicting with the Applicative-Monad Proposal (AMP)dynamic-fno-warn-amp
-fwarn-typed-holes Report warnings when typed hole errors are deferred until runtime. See -fdefer-typed-holes. dynamic-fno-warn-typed-holes
-fwarn-partial-type-signatures warn about holes in partial type signatures when -XPartialTypesignatures is enabled. Not applicable when -XPartialTypesignatures is not enabled, in which case errors are generated for such holes. See Section 7.15, “Partial Type Signatures”. dynamic-fno-warn-partial-type-signatures
-fwarn-deriving-typeable warn when encountering a request to derive an instance of class Typeable. As of GHC 7.10, such declarations are unnecessary and are ignored by the compiler because GHC has a custom solver for discharging this type of constraint. dynamic-fno-warn-deriving-typeable

4.19.14. Optimisation levels

These options are described in more detail in Section 4.10, “Optimisation (code improvement)”

FlagDescriptionStatic/DynamicReverse
-O0Disable optimisations (default)dynamic-O
-O or -O1Enable level 1 optimisationsdynamic-O0
-O2Enable level 2 optimisationsdynamic-O0
-OdphEnable level 2 optimisations, set -fmax-simplifier-iterations=20 and -fsimplifier-phases=3.dynamic-

See Section 4.19.15, “Individual optimisations” for a list of optimisations enabled on level 1 and level 2.

4.19.15. Individual optimisations

These options are described in more detail in Section 4.10.2, “-f*: platform-independent flags”. If a flag is implied by -O then it is also implied by -O2 (unless flag description explicitly says otherwise). If a flag is implied by -O0 only then the flag is not implied by -O and -O2.

FlagDescriptionStatic/DynamicReverse
-fcall-arityEnable call-arity optimisation. Implied by -O.dynamic-fno-call-arity
-fcase-mergeEnable case-merging. Implied by -O.dynamic-fno-case-merge
-fcmm-elim-common-blocksEnable Cmm common block elimination. Implied by -O.dynamic-fno-cmm-elim-common-blocks
-fcmm-sinkEnable Cmm sinking. Implied by -O.dynamic-fno-cmm-sink
-fcpr-offSwitch off CPR analysis in the demand analyser.static-
-fcseEnable common sub-expression elimination. Implied by -O.dynamic-fno-cse
-fdicts-cheapMake dictionary-valued expressions seem cheap to the optimiser.dynamic-fno-dicts-cheap
-fdicts-strictMake dictionaries strictdynamic-fno-dicts-strict
-fdmd-tx-dict-sel Use a special demand transformer for dictionary selectors. Always enabled by default. dynamic-fno-dmd-tx-dict-sel
-fdo-eta-reductionEnable eta-reduction. Implied by -O.dynamic-fno-do-eta-reduction
-fdo-lambda-eta-expansionEnable lambda eta-expansion. Always enabled by default.dynamic-fno-do-lambda-eta-expansion
-feager-blackholingTurn on eager blackholingdynamic-
-fenable-rewrite-rulesSwitch on all rewrite rules (including rules generated by automatic specialisation of overloaded functions). Implied by -O. dynamic-fno-enable-rewrite-rules
-fexcess-precisionEnable excess intermediate precisiondynamic-fno-excess-precision
-fexpose-all-unfoldingsExpose all unfoldings, even for very large or recursive functions.dynamic-fno-expose-all-unfoldings
-ffloat-inTurn on the float-in transformation. Implied by -O.dynamic-fno-float-in
-ffull-lazinessTurn on full laziness (floating bindings outwards). Implied by -O.dynamic-fno-full-laziness
-ffun-to-thunkAllow worker-wrapper to convert a function closure into a thunk if the function does not use any of its arguments. Off by default.dynamic-fno-fun-to-thunk
-fignore-assertsIgnore assertions in the source. Implied by -O.dynamic-fno-ignore-asserts
-fignore-interface-pragmasIgnore pragmas in interface files. Implied by -O0 only.dynamic-fno-ignore-interface-pragmas
-flate-dmd-analRun demand analysis again, at the end of the simplification pipelinedynamic-fno-late-dmd-anal
-fliberate-caseTurn on the liberate-case transformation. Implied by -O2.dynamic-fno-liberate-case
-fliberate-case-threshold=nSet the size threshold for the liberate-case transformation to n (default: 2000)dynamis-fno-liberate-case-threshold
-floopificationTurn saturated self-recursive tail-calls into local jumps in the generated assembly. Implied by -O.dynamic-fno-loopification
-fmax-inline-alloc-size=nSet the maximum size of inline array allocations to n bytes (default: 128). GHC will allocate non-pinned arrays of statically known size in the current nursery block if they're no bigger than n bytes, ignoring GC overheap. This value should be quite a bit smaller than the block size (typically: 4096).dynamic-
-fmax-inline-memcpy-insns=n Inline memcpy calls if they would generate no more than n pseudo instructions (default: 32). dynamic-
-fmax-inline-memset-insns=n Inline memset calls if they would generate no more than n pseudo instructions (default: 32). dynamic-
-fmax-relevant-binds=nSet the maximum number of bindings to display in type error messages (default 6).dynamic-fno-max-relevant-bindings
-fmax-simplifier-iterations=nSet the max iterations for the simplifier (default 4).dynamic-
-fmax-worker-args=nIf a worker has that many arguments, none will be unpacked anymore (default: 10)dynamic-
-fno-opt-coercionTurn off the coercion optimiserstatic-
-fno-pre-inliningTurn off pre-inliningdynamic-
-fno-state-hackTurn off the "state hack" whereby any lambda with a real-world state token as argument is considered to be single-entry. Hence OK to inline things inside it.static-
-fomit-interface-pragmasDon't generate interface pragmas. Implied by -O0 only.dynamic-fno-omit-interface-pragmas
-fomit-yieldsOmit heap checks when no allocation is being performed.dynamic-fno-omit-yields
-fpedantic-bottomsMake GHC be more precise about its treatment of bottom (but see also -fno-state-hack). In particular, GHC will not eta-expand through a case expression.dynamic-fno-pedantic-bottoms
-fregs-graphUse the graph colouring register allocator for register allocation in the native code generator. Implied by -O2.dynamic-fno-regs-graph
-fregs-iterativeUse the iterative coalescing graph colouring register allocator in the native code generator.dynamic-fno-regs-iterative
-fsimplifier-phases=nSet the number of phases for the simplifier (default 2). Ignored with -O0.dynamic-
-fsimpl-tick-factor=nSet the percentage factor for simplifier ticks (default 100)dynamic-
-fspec-constrTurn on the SpecConstr transformation. Implied by -O2.dynamic-fno-spec-constr
-fspec-constr-count=nSet to n (default: 3) the maximum number of specialisations that will be created for any one function by the SpecConstr transformationdynamic-fno-spec-constr-count
-fspec-constr-threshold=nSet the size threshold for the SpecConstr transformation to n (default: 2000)dynamic-fno-spec-constr-threshold
-fspecialiseTurn on specialisation of overloaded functions. Implied by -O.dynamic-fno-specialise
-fstatic-argument-transformationTurn on the static argument transformation.dynamic-fno-static-argument-transformation
-fstrictnessTurn on strictness analysis. Implied by -O.dynamic-fno-strictness
-fstrictness-before=nRun an additional strictness analysis before simplifier phase ndynamic-
-funbox-small-strict-fieldsFlatten strict constructor fields with a pointer-sized representation. Implied by -O.dynamic-fno-unbox-small-strict-fields
-funbox-strict-fieldsFlatten strict constructor fieldsdynamic-fno-unbox-strict-fields
-funfolding-creation-threshold=nTweak unfolding settings. Default: 750dynamic-
-funfolding-dict-discount=nTweak unfolding settings. Default: 30dynamic-
-funfolding-fun-discount=nTweak unfolding settings. Default: 60dynamic-
-funfolding-keeness-factor=nTweak unfolding settings. Default: 1.5dynamic-
-funfolding-use-threshold=nTweak unfolding settings. Default: 60dynamic-
-fvectorisation-avoidanceEnable vectorisation avoidance. Always enabled by default.dynamic-fno-vectorisation-avoidance
-fvectoriseEnable vectorisation of nested data parallelismdynamic-fno-vectorise

4.19.16. Profiling options

Chapter 5, Profiling

FlagDescriptionStatic/DynamicReverse
-profTurn on profilingdynamic-
-fprof-autoAuto-add SCCs to all bindings not marked INLINEdynamic-fno-prof-auto
-fprof-auto-topAuto-add SCCs to all top-level bindings not marked INLINEdynamic-fno-prof-auto
-fprof-auto-exportedAuto-add SCCs to all exported bindings not marked INLINEdynamic-fno-prof-auto
-fprof-cafsAuto-add SCCs to all CAFsdynamic-fno-prof-cafs
-fno-prof-count-entriesDo not collect entry countsdynamic-fprof-count-entries
-tickyTurn on ticky-ticky profilingdynamic-

4.19.17. Program coverage options

Section 5.7, “Observing Code Coverage”

FlagDescriptionStatic/DynamicReverse
-fhpcTurn on Haskell program coverage instrumentationdynamic-
-hpcdir dirDirectory to deposit .mix files during compilation (default is .hpc)dynamic-

4.19.18. Haskell pre-processor options

Section 4.12.4, “Options affecting a Haskell pre-processor”

FlagDescriptionStatic/DynamicReverse
-F Enable the use of a pre-processor (set with -pgmF) dynamic-

4.19.19. C pre-processor options

Section 4.12.3, “Options affecting the C pre-processor”

FlagDescriptionStatic/DynamicReverse
-cppRun the C pre-processor on Haskell source filesdynamic-
-Dsymbol[=value]Define a symbol in the C pre-processordynamic-Usymbol
-UsymbolUndefine a symbol in the C pre-processordynamic-
-IdirAdd dir to the directory search list for #include filesdynamic-

4.19.20. Code generation options

Section 4.12.5, “Options affecting code generation”

FlagDescriptionStatic/DynamicReverse
-fasmUse the native code generatordynamic-fllvm
-fllvmCompile using the LLVM code generatordynamic-fasm
-fno-codeOmit code generationdynamic-
-fwrite-interfaceAlways write interface filesdynamic-
-fbyte-codeGenerate byte-codedynamic-
-fobject-codeGenerate object codedynamic-

4.19.21. Linking options

Section 4.12.6, “Options affecting linking”

FlagDescriptionStatic/DynamicReverse
-sharedGenerate a shared library (as opposed to an executable)dynamic-
-staticlibOn Darwin/OS X/iOS only, generate a standalone static library (as opposed to an executable). This is the usual way to compile for iOS. dynamic-
-fPICGenerate position-independent code (where available)dynamic-
-dynamicUse dynamic Haskell libraries (if available)dynamic-
-dynamic-tooBuild dynamic object files as well as static object files during compilationdynamic-
-dynoSet the output path for the dynamically linked objectsdynamic-
-dynosufSet the output suffix for dynamic object filesdynamic-
-dynloadSelects one of a number of modes for finding shared libraries at runtime.dynamic-
-framework nameOn Darwin/OS X/iOS only, link in the framework name. This option corresponds to the -framework option for Apple's Linker.dynamic-
-framework-path nameOn Darwin/OS X/iOS only, add dir to the list of directories searched for frameworks. This option corresponds to the -F option for Apple's Linker.dynamic-
-llibLink in library libdynamic-
-LdirAdd dir to the list of directories searched for librariesdynamic-
-main-isSet main module and functiondynamic-
--mk-dllDLL-creation mode (Windows only)dynamic-
-no-hs-mainDon't assume this program contains maindynamic-
-rtsopts, -rtsopts={none,some,all}Control whether the RTS behaviour can be tweaked via command-line flags and the GHCRTS environment variable. Using none means no RTS flags can be given; some means only a minimum of safe options can be given (the default), and all (or no argument at all) means that all RTS flags are permitted.dynamic-
-with-rtsopts=optsSet the default RTS options to opts.dynamic-
-no-linkOmit linkingdynamic-
-split-objsSplit objects (for libraries)dynamic-
-staticUse static Haskell librariesdynamic-
-threadedUse the threaded runtimedynamic-
-debugUse the debugging runtimedynamic-
-tickyFor linking, this simply implies -debug; see Section 5.8, “Using “ticky-ticky” profiling (for implementors)”.dynamic-
-eventlogEnable runtime event tracingdynamic-
-fno-gen-manifestDo not generate a manifest file (Windows only)dynamic-
-fno-embed-manifestDo not embed the manifest in the executable (Windows only)dynamic-
-fno-shared-implibDon't generate an import library for a DLL (Windows only)dynamic-
-dylib-install-name pathSet the install name (via -install_name passed to Apple's linker), specifying the full install path of the library file. Any libraries or executables that link with it later will pick up that path as their runtime search location for it. (Darwin/OS X only)dynamic-
-rdynamicThis instructs the linker to add all symbols, not only used ones, to the dynamic symbol table. Currently Linux and Windows/MinGW32 only. This is equivalent to using -optl -rdynamic on Linux, and -optl -export-all-symbols on Windows.dynamic-

4.19.22. Plugin options

Section 9.3, “Compiler Plugins”

FlagDescriptionStatic/DynamicReverse
-fplugin=moduleLoad a plugin exported by a given moduledynamic-
-fplugin-opt=module:argsGive arguments to a plugin module; module must be specified with -fplugindynamic-

4.19.23. Replacing phases

Section 4.12.1, “Replacing the program for one or more phases”

FlagDescriptionStatic/DynamicReverse
-pgmL cmdUse cmd as the literate pre-processordynamic-
-pgmP cmdUse cmd as the C pre-processor (with -cpp only)dynamic-
-pgmc cmdUse cmd as the C compilerdynamic-
-pgms cmdUse cmd as the splitterdynamic-
-pgma cmdUse cmd as the assemblerdynamic-
-pgml cmdUse cmd as the linkerdynamic-
-pgmdll cmdUse cmd as the DLL generatordynamic-
-pgmF cmdUse cmd as the pre-processor (with -F only)dynamic-
-pgmwindres cmdUse cmd as the program for embedding manifests on Windows.dynamic-
-pgmlibtool cmdUse cmd as the command for libtool (with -staticlib only).dynamic-

4.19.24. Forcing options to particular phases

Section 4.12.2, “Forcing options to a particular phase”

FlagDescriptionStatic/DynamicReverse
-optL optionpass option to the literate pre-processordynamic-
-optP optionpass option to cpp (with -cpp only)dynamic-
-optF optionpass option to the custom pre-processordynamic-
-optc optionpass option to the C compilerdynamic-
-optlo optionpass option to the LLVM optimiserdynamic-
-optlc optionpass option to the LLVM compilerdynamic-
-opta optionpass option to the assemblerdynamic-
-optl optionpass option to the linkerdynamic-
-optdll optionpass option to the DLL generatordynamic-
-optwindres optionpass option to windres.dynamic-

4.19.25. Platform-specific options

Section 4.16, “Platform-specific Flags”

FlagDescriptionStatic/DynamicReverse
-msse2(x86 only) Use SSE2 for floating pointdynamic-

4.19.26. Compiler debugging options

Section 4.18, “Debugging the compiler”

FlagDescriptionStatic/DynamicReverse
-dcore-lintTurn on internal sanity checkingdynamic-
-ddump-to-fileDump to files instead of stdoutdynamic-
-ddump-asmDump assemblydynamic-
-ddump-bcosDump interpreter byte codedynamic-
-ddump-cmmDump C-- outputdynamic-
-ddump-core-statsPrint a one-line summary of the size of the Core program at the end of the optimisation pipeline dynamic-
-ddump-cpranalDump output from CPR analysisdynamic-
-ddump-cseDump CSE outputdynamic-
-ddump-derivDump deriving outputdynamic-
-ddump-dsDump desugarer outputdynamic-
-ddump-flatCDump “flat” Cdynamic-
-ddump-foreignDump foreign export stubsdynamic-
-ddump-hpcDump after instrumentation for program coveragedynamic-
-ddump-inliningsDump inlining infodynamic-
-ddump-llvmDump LLVM intermediate codedynamic-
-ddump-occur-analDump occurrence analysis outputdynamic-
-ddump-opt-cmmDump the results of C-- to C-- optimising passesdynamic-
-ddump-parsedDump parse treedynamic-
-ddump-prepDump prepared coredynamic-
-ddump-rnDump renamer outputdynamic-
-ddump-rule-firingsDump rule firing infodynamic-
-ddump-rule-rewritesDump detailed rule firing infodynamic-
-ddump-rulesDump rulesdynamic-
-ddump-vectDump vectoriser input and outputdynamic-
-ddump-simplDump final simplifier outputdynamic-
-ddump-simpl-iterationsDump output from each simplifier iterationdynamic-
-ddump-specDump specialiser outputdynamic-
-ddump-splicesDump TH spliced expressions, and what they evaluate todynamic-
-ddump-stgDump final STGdynamic-
-ddump-stranalDump strictness analyser outputdynamic-
-ddump-strsigsDump strictness signaturesdynamic-
-ddump-tcDump typechecker outputdynamic-
-dth-dec-fileShow evaluated TH declarations in a .th.hs filedynamic-
-ddump-typesDump type signaturesdynamic-
-ddump-worker-wrapperDump worker-wrapper outputdynamic-
-ddump-if-traceTrace interface filesdynamic-
-ddump-tc-traceTrace typecheckerdynamic-
-ddump-vt-traceTrace vectoriserdynamic-
-ddump-rn-traceTrace renamerdynamic-
-ddump-rn-statsRenamer statsdynamic-
-ddump-simpl-statsDump simplifier statsdynamic-
-dno-debug-outputSuppress unsolicited debugging outputstatic-
-dppr-debugTurn on debug printing (more verbose)static-
-dppr-user-lengthSet the depth for printing expressions in error msgsdynamic-
-dppr-colsNNNSet the width of debugging output. For example -dppr-cols200dynamic-
-dppr-case-as-letPrint single alternative case expressions as strict lets.dynamic-
-dsuppress-allIn core dumps, suppress everything (except for uniques) that is suppressible.dynamic-
-dsuppress-uniquesSuppress the printing of uniques in debug output (easier to use diff)dynamic-
-dsuppress-idinfoSuppress extended information about identifiers where they are bounddynamic-
-dsuppress-module-prefixesSuppress the printing of module qualification prefixesdynamic-
-dsuppress-type-signaturesSuppress type signaturesdynamic-
-dsuppress-type-applicationsSuppress type applicationsdynamic-
-dsuppress-coercionsSuppress the printing of coercions in Core dumps to make them shorterdynamic-
-dsource-statsDump haskell source statsdynamic-
-dcmm-lintC-- pass sanity checkingdynamic-
-dstg-lintSTG pass sanity checkingdynamic-
-dstg-statsDump STG statsdynamic-
-dverbose-core2coreShow output from each core-to-core passdynamic-
-dverbose-stg2stgShow output from each STG-to-STG passdynamic-
-dshow-passesPrint out each pass name as it happensdynamic-
-dfaststring-statsShow statistics for fast string usage when finisheddynamic-
-frule-checkReport sites with rules that could have fired but didn't. Takes a string argument.dynamic-

4.19.27. Misc compiler options

FlagDescriptionStatic/DynamicReverse
-jNWhen compiling with --make, compile N modules in parallel.dynamic-
-fno-hi-version-checkDon't complain about .hi file mismatchesdynamic-
-fhistory-sizeSet simplification history sizedynamic-
-fno-ghci-historyDo not use the load/store the GHCi command history from/to ghci_history.dynamic-
-fno-ghci-sandboxTurn off the GHCi sandbox. Means computations are run in the main thread, rather than a forked thread.dynamic-