GHC¶
Synopsis¶
ghc [option|filename]
ghci [option|filename]
Description¶
This manual page documents briefly the ghc
and ghci
commands. Note that
ghci
is not yet available on all architectures. Extensive documentation is
available in various other formats including PDF and HTML.
Each of GHC’s command line options is classified as either static or
dynamic. A static flag may only be specified on the command line, whereas a
dynamic flag may also be given in an OPTIONS
pragma in a source file or
set from the GHCi command-line with :set
.
As a rule of thumb, all the language options are dynamic, as are the warning options and the debugging options.
The rest are static, with the notable exceptions of
-v
, -cpp
, -fasm
, -fvia-C
, -fllvm
, and
-#include
.
The OPTIONS sections lists the status of each flag.
Common suffixes of file names for Haskell are:
.hs
- Haskell source code; preprocess, compile
.lhs
- literate Haskell source; unlit, preprocess, compile
.hi
- Interface file; contains information about exported symbols
.hc
- intermediate C files
.⟨way⟩_o
object files for “way” ⟨way⟩; common ways are:
dyn
- dynamically-linked
p
- built with profiling
.⟨way⟩_hi
- interface files for “way” ⟨way⟩; common ways are:
Options¶
-dynamic-too
-fasm
-fllvm
-fbyte-code
-fbyte-code-and-object-code
-fexpose-internal-symbols
-fexternal-dynamic-refs
-fllvm
-fasm
-fno-code
-fobject-code
-fPIC
-fPIE
-fprefer-byte-code
-fwrite-if-simplified-core
-fwrite-interface
-dasm-lint
-dcmm-lint
-dcore-lint
-ddisable-js-c-sources
-ddisable-js-minifier
-ddump-asm
-ddump-asm-conflicts
-ddump-asm-liveness
-ddump-asm-native
-ddump-asm-regalloc
-ddump-asm-regalloc-stages
-ddump-asm-stats
-ddump-bcos
-ddump-c-backend
-ddump-call-arity
-ddump-cfg-weights
-ddump-cmm
-ddump-cmm-caf
-ddump-cmm-cbe
-ddump-cmm-cfg
-ddump-cmm-cps
-ddump-cmm-from-stg
-ddump-cmm-info
-ddump-cmm-opt
-ddump-cmm-proc
-ddump-cmm-procmap
-ddump-cmm-raw
-ddump-cmm-sink
-ddump-cmm-sp
-ddump-cmm-split
-ddump-cmm-switch
-ddump-cmm-thread-sanitizer
-ddump-cmm-verbose
-ddump-cmm-verbose-by-proc
-ddump-core-stats
-ddump-cpr-signatures
-ddump-cpranal
-ddump-cs-trace
-ddump-cse
-ddump-debug
-ddump-deriv
-ddump-dmd-signatures
-ddump-dmdanal
-ddump-ds
-ddump-ds-preopt
-ddump-ec-trace
-ddump-exitify
-ddump-faststrings
-ddump-file-prefix=⟨str⟩
-ddump-float-in
-ddump-foreign
-ddump-full-laziness
-ddump-float-out
-ddump-hie
-ddump-hpc
-ddump-if-trace
-ddump-inlinings
-ddump-js
-ddump-json
-ddump-late-cc
-ddump-liberate-case
-ddump-llvm
-ddump-mod-map
-ddump-occur-anal
-ddump-opt-cmm
-ddump-parsed
-ddump-parsed-ast
-ddump-prep
-ddump-rn
-ddump-rn-ast
-ddump-rn-stats
-ddump-rn-trace
-ddump-rtti
-ddump-rule-firings
-ddump-rule-rewrites
-ddump-rules
-ddump-simpl
-ddump-simpl-iterations
-ddump-simpl-stats
-ddump-simpl-trace
-ddump-spec
-ddump-spec-constr
-ddump-splices
-ddump-static-argument-transformation
-ddump-stg
-ddump-stg-cg
-ddump-stg-final
-ddump-stg-from-core
-ddump-stg-tags
-ddump-stg-unarised
-ddump-str-signatures
-ddump-stranal
-ddump-tc
-ddump-tc-ast
-ddump-tc-trace
-ddump-ticked
-ddump-timings
-ddump-to-file
-ddump-types
-ddump-verbose-inlinings
-ddump-view-pattern-commoning
-ddump-worker-wrapper
-dfaststring-stats
-dhex-word-literals
-dinitial-unique=⟨s⟩
-dinline-check=⟨str⟩
-dipe-stats
-dkeep-comments
-dlinear-core-lint
-dlint
-dno-debug-output
-ddebug-output
-dno-typeable-binds
-dppr-case-as-let
-dppr-cols=⟨n⟩
-dppr-debug
-dppr-user-length
-drule-check=⟨str⟩
-dshow-passes
-dstg-lint
-dsuppress-all
-dsuppress-coercion-types
-dsuppress-coercions
-dsuppress-core-sizes
-dsuppress-idinfo
-dsuppress-module-prefixes
-dsuppress-stg-free-vars
-dsuppress-stg-reps
-dsuppress-ticks
-dsuppress-timestamps
-dsuppress-type-applications
-dsuppress-type-signatures
-dsuppress-unfoldings
-dsuppress-uniques
-dsuppress-var-kinds
-dtag-inference-checks
-dth-dec-file
-dunique-increment=⟨i⟩
-dverbose-core2core
-dverbose-stg2stg
-falignment-sanitisation
-fcatch-nonexhaustive-cases
-fcheck-prim-bounds
-fcmm-thread-sanitizer
-fdistinct-constructor-tables
-fdump-with-ways
-finfo-table-map
-finfo-table-map-with-fallback
-fno-info-table-map-with-fallback
-finfo-table-map-with-stack
-fno-info-table-map-with-stack
-fllvm-fill-undef-with-garbage
-fno-info-table-map-with-fallback
-finfo-table-map-with-fallback
-fno-info-table-map-with-stack
-finfo-table-map-with-stack
-forig-thunk-info
-fproc-alignment
-funoptimized-core-for-interpreter
-fno-unoptimized-core-for-interpreter
-g
-g⟨n⟩
-cpp
-D⟨symbol⟩[=⟨value⟩]
-U⟨symbol⟩
-I⟨dir⟩
-U⟨symbol⟩
-i
-i⟨dir⟩[:⟨dir⟩]*
-fbreak-on-error
-fno-break-on-error
-fbreak-on-exception
-fno-break-on-exception
-fbreak-points
-fno-break-points
-fghci-hist-size=⟨n⟩
-fghci-leak-check
-fno-ghci-leak-check
-fimplicit-import-qualified
-fno-implicit-import-qualified
-flocal-ghci-history
-fno-local-ghci-history
-fno-it
-fno-no-it
-fprint-bind-result
-fno-print-bind-result
-fprint-evld-with-show
-fshow-loaded-modules
-ghci-script
-ignore-dot-ghci
-no-ignore-dot-ghci
-interactive-print ⟨name⟩
--show-iface ⟨file⟩
-ddump-hi
-ddump-hi-diffs
-ddump-minimal-imports
-keep-hc-file
-keep-hc-files
-keep-hi-files
-no-keep-hi-files
-keep-hscpp-file
-keep-hscpp-files
-keep-llvm-file
-keep-llvm-files
-keep-o-files
-no-keep-o-files
-keep-s-file
-keep-s-files
-keep-tmp-files
-XAllowAmbiguousTypes
-XApplicativeDo
-XArrows
-XBangPatterns
-XBinaryLiterals
-XBlockArguments
-XCApiFFI
-XConstrainedClassMethods
-XConstraintKinds
-XCPP
-XCUSKs
-XDataKinds
-XDatatypeContexts
-XDeepSubsumption
-XDefaultSignatures
-XDeriveAnyClass
-XDeriveDataTypeable
-XDeriveFoldable
-XDeriveFunctor
-XDeriveGeneric
-XDeriveLift
-XDeriveTraversable
-XDerivingStrategies
-XDerivingVia
-XDisambiguateRecordFields
-XDuplicateRecordFields
-XEmptyCase
-XEmptyDataDecls
-XEmptyDataDeriving
-XExistentialQuantification
-XExplicitForAll
-XExplicitNamespaces
-XExtendedDefaultRules
-XExtendedLiterals
-XFieldSelectors
-XFlexibleContexts
-XFlexibleInstances
-XForeignFunctionInterface
-XFunctionalDependencies
-XGADTs
-XGADTSyntax
-XGeneralisedNewtypeDeriving
-XGeneralizedNewtypeDeriving
-XGHC2021
-XGHC2024
-XGHCForeignImportPrim
-XHaskell2010
-XHaskell98
-XHexFloatLiterals
-XImplicitParams
-XImportQualifiedPost
-XImpredicativeTypes
-XIncoherentInstances
-XInstanceSigs
-XInterruptibleFFI
-XKindSignatures
-XLambdaCase
-XLexicalNegation
-XLiberalTypeSynonyms
-XLinearTypes
-XListTuplePuns
-XMagicHash
-XMonadComprehensions
-XMonoLocalBinds
-XMultiParamTypeClasses
-XMultiWayIf
-XNamedFieldPuns
-XNamedWildCards
-XNegativeLiterals
-XNoImplicitPrelude
-XNoMonomorphismRestriction
-XNondecreasingIndentation
-XNoPatternGuards
-XNoTraditionalRecordSyntax
-XNPlusKPatterns
-XNullaryTypeClasses
-XNumDecimals
-XNumericUnderscores
-XOverlappingInstances
-XOverloadedLabels
-XOverloadedLists
-XOverloadedRecordDot
-XOverloadedRecordUpdate
-XOverloadedStrings
-XPackageImports
-XParallelListComp
-XPartialTypeSignatures
-XPatternSynonyms
-XPolyKinds
-XPostfixOperators
-XQualifiedDo
-XQuantifiedConstraints
-XQuasiQuotes
-XRank2Types
-XRankNTypes
-XRebindableSyntax
-XRecordWildCards
-XRecursiveDo
-XRequiredTypeArguments
-XRoleAnnotations
-XSafe
-XScopedTypeVariables
-XStandaloneDeriving
-XStandaloneKindSignatures
-XStarIsType
-XStaticPointers
-XStrict
-XStrictData
-XTemplateHaskell
-XTemplateHaskellQuotes
-XTransformListComp
-XTrustworthy
-XTupleSections
-XTypeAbstractions
-XTypeApplications
-XTypeData
-XTypeFamilies
-XTypeFamilyDependencies
-XTypeInType
-XTypeOperators
-XTypeSynonymInstances
-XUnboxedSums
-XUnboxedTuples
-XUndecidableInstances
-XUndecidableSuperClasses
-XUnicodeSyntax
-XUnliftedDatatypes
-XUnliftedFFITypes
-XUnliftedNewtypes
-XUnsafe
-XViewPatterns
-c
-debug
-dylib-install-name ⟨path⟩
-dynamic
-dynload
-eventlog
-fcompact-unwind
-fkeep-cafs
-flink-rts
-fno-embed-manifest
-fno-gen-manifest
-fno-shared-implib
-framework ⟨name⟩
-framework-path ⟨dir⟩
-fsplit-sections
-split-sections
-fno-split-sections
-fuse-rpaths
-fwhole-archive-hs-libs
-L ⟨dir⟩
-l ⟨lib⟩
-main-is ⟨thing⟩
-no-hs-main
-no-pie
-pie
-no-rtsopts-suggestions
-package ⟨name⟩
-pie
-no-pie
-rdynamic
-rtsopts[=⟨none|some|all|ignore|ignoreAll⟩]
-shared
-single-threaded
-threaded
-static
-staticlib
-threaded
-single-threaded
-with-rtsopts=⟨opts⟩
-ddump-mod-cycles
-fdefer-out-of-scope-variables
-fno-defer-out-of-scope-variables
-fdefer-type-errors
-fno-defer-type-errors
-fdefer-typed-holes
-fno-defer-typed-holes
-fexternal-interpreter
-ffamily-application-cache
-fno-family-application-cache
-fglasgow-exts
-fno-glasgow-exts
-fno-safe-haskell
-ghcversion-file ⟨path to ghcversion.h⟩
-H ⟨size⟩
-hidden-module ⟨module name⟩
-j[⟨n⟩]
-jsem
-reexported-module ⟨module name⟩
-this-package-name ⟨unit-id⟩
-unit @⟨filename⟩
-working-dir ⟨dir⟩
--frontend ⟨module⟩
--help
-?
--info
--interactive
--make
--numeric-version
--print-booter-version
--print-build-platform
--print-c-compiler-flags
--print-c-compiler-link-flags
--print-debug-on
--print-global-package-db
--print-have-interpreter
--print-have-native-code-generator
--print-host-platform
--print-ld-flags
--print-leading-underscore
--print-libdir
--print-object-splitting-supported
--print-project-git-commit-id
--print-project-version
--print-rts-ways
--print-stage
--print-support-smp
--print-tables-next-to-code
--print-target-platform
--print-unregisterised
--run ⟨file⟩
--show-iface ⟨file⟩
--show-options
--supported-extensions
--supported-languages
--version
-V
-e ⟨expr⟩
-M
-shared
-fasm-shortcutting
-fno-asm-shortcutting
-fbinary-blob-threshold=⟨n⟩
-fblock-layout-cfg
-fno-block-layout-cfg
-fblock-layout-weightless
-fno-block-layout-weightless
-fblock-layout-weights
-fcall-arity
-fno-call-arity
-fcase-folding
-fno-case-folding
-fcase-merge
-fno-case-merge
-fcmm-control-flow
-fno-cmm-control-flow
-fcmm-elim-common-blocks
-fno-cmm-elim-common-blocks
-fcmm-sink
-fno-cmm-sink
-fcmm-static-pred
-fno-cmm-static-pred
-fcore-constant-folding
-fno-core-constant-folding
-fcpr-anal
-fno-cpr-anal
-fcross-module-specialise
-fno-cross-module-specialise
-fcse
-fno-cse
-fdicts-cheap
-fno-dicts-cheap
-fdicts-strict
-fno-dicts-strict
-fdmd-tx-dict-sel
-fno-dmd-tx-dict-sel
-fdmd-unbox-width=⟨n⟩
-fdo-clever-arg-eta-expansion
-fno-do-clever-arg-eta-expansion
-fdo-eta-reduction
-fno-do-eta-reduction
-fdo-lambda-eta-expansion
-fno-do-lambda-eta-expansion
-feager-blackholing
-fenable-rewrite-rules
-fno-enable-rewrite-rules
-fexcess-precision
-fno-excess-precision
-fexitification
-fno-exitification
-fexpose-all-unfoldings
-fno-expose-all-unfoldings
-ffloat-in
-fno-float-in
-ffull-laziness
-fno-full-laziness
-ffun-to-thunk
-fno-fun-to-thunk
-fignore-asserts
-fno-ignore-asserts
-fignore-interface-pragmas
-fno-ignore-interface-pragmas
-finline-generics
-fno-inline-generics
-finline-generics-aggressively
-fno-inline-generics-aggressively
-fkeep-auto-rules
-fno-keep-auto-rules
-flate-dmd-anal
-fno-late-dmd-anal
-flate-specialise
-fno-late-specialise
-fliberate-case
-fno-liberate-case
-fliberate-case-threshold=⟨n⟩
-fno-liberate-case-threshold
-fllvm-pass-vectors-in-regs
-flocal-float-out
-fno-local-float-out
-flocal-float-out-top-level
-fno-local-float-out-top-level
-floopification
-fno-loopification
-fmax-inline-alloc-size=⟨n⟩
-fmax-inline-memcpy-insns=⟨n⟩
-fmax-inline-memset-insns=⟨n⟩
-fmax-simplifier-iterations=⟨n⟩
-fmax-uncovered-patterns=⟨n⟩
-fmax-worker-args=⟨n⟩
-fno-opt-coercion
-fno-pre-inlining
-fno-state-hack
-fomit-interface-pragmas
-fno-omit-interface-pragmas
-fomit-yields
-fno-omit-yields
-foptimal-applicative-do
-fno-optimal-applicative-do
-fpedantic-bottoms
-fno-pedantic-bottoms
-fpolymorphic-specialisation
-fno-polymorphic-specialisation
-fregs-graph
-fno-regs-graph
-fregs-iterative
-fno-regs-iterative
-fsimpl-tick-factor=⟨n⟩
-fsimplifier-phases=⟨n⟩
-fsolve-constant-dicts
-fno-solve-constant-dicts
-fspec-constr
-fno-spec-constr
-fspec-constr-count=⟨n⟩
-fno-spec-constr-count
-fspec-constr-keen
-fno-spec-constr-keen
-fspec-constr-threshold=⟨n⟩
-fno-spec-constr-threshold
-fspecialise
-fno-specialise
-fspecialise-aggressively
-fno-specialise-aggressively
-fspecialise-incoherents
-fno-specialise-incoherents
-fstatic-argument-transformation
-fno-static-argument-transformation
-fstg-cse
-fno-stg-cse
-fstg-lift-lams
-fno-stg-lift-lams
-fstg-lift-lams-known
-fno-stg-lift-lams-known
-fstg-lift-lams-non-rec-args
-fstg-lift-lams-non-rec-args-any
-fstg-lift-lams-rec-args
-fstg-lift-lams-rec-args-any
-fstrictness
-fno-strictness
-fstrictness-before=⟨n⟩
-funbox-small-strict-fields
-fno-unbox-small-strict-fields
-funbox-strict-fields
-fno-unbox-strict-fields
-funfolding-case-scaling=⟨n⟩
-funfolding-case-threshold=⟨n⟩
-funfolding-creation-threshold=⟨n⟩
-funfolding-dict-discount=⟨n⟩
-funfolding-fun-discount=⟨n⟩
-funfolding-keeness-factor=⟨n⟩
-funfolding-use-threshold=⟨n⟩
-fworker-wrapper
-fworker-wrapper-cbv
-O
-O1
-O0
-O0
-O2
-O0
-O⟨n⟩
-O0
-clear-package-db
-distrust ⟨pkg⟩
-distrust-all-packages
-fpackage-trust
-global-package-db
-hide-all-packages
-hide-package ⟨pkg⟩
-ignore-package ⟨pkg⟩
-no-auto-link-packages
-no-global-package-db
-no-user-package-db
-package ⟨pkg⟩
-package-db ⟨file⟩
-package-env ⟨file⟩|⟨name⟩
-package-id ⟨unit-id⟩
-this-unit-id ⟨unit-id⟩
-trust ⟨pkg⟩
-user-package-db
--merge-objs
-C
-c
-E
-F
-S
-x ⟨suffix⟩
-pgma ⟨cmd⟩
-pgmc ⟨cmd⟩
-pgmcxx ⟨cmd⟩
-pgmF ⟨cmd⟩
-pgmi ⟨cmd⟩
-pgminstall_name_tool ⟨cmd⟩
-pgmL ⟨cmd⟩
-pgml ⟨cmd⟩
-pgmlas ⟨cmd⟩
-pgmlc ⟨cmd⟩
-pgmlm ⟨cmd⟩
-pgmlo ⟨cmd⟩
-pgmotool ⟨cmd⟩
-pgmP ⟨cmd⟩
-pgms ⟨cmd⟩
-pgmwindres ⟨cmd⟩
-opta ⟨option⟩
-optc ⟨option⟩
-optcxx ⟨option⟩
-optF ⟨option⟩
-opti ⟨option⟩
-optL ⟨option⟩
-optl ⟨option⟩
-optlas ⟨option⟩
-optlc ⟨option⟩
-optlm ⟨option⟩
-optlo ⟨option⟩
-optP ⟨option⟩
-optwindres ⟨option⟩
-pgmc-supports-no-pie
-pgml-supports-no-pie
-mavx
-mavx2
-mavx512cd
-mavx512er
-mavx512f
-mavx512pf
-mbmi
-mbmi2
-mfma
-msse
-msse2
-msse3
-msse4
-msse4.2
-fclear-plugins
-fplugin-library=⟨file-path⟩;⟨unit-id⟩;⟨module⟩;⟨args⟩
-fplugin-opt=⟨module⟩:⟨args⟩
-fplugin-trustworthy
-fplugin=⟨module⟩
-hide-all-plugin-packages
-plugin-package ⟨pkg⟩
-plugin-package-id ⟨pkg-id⟩
-auto
-auto-all
-caf-all
-fno-prof-count-entries
-fprof-count-entries
-fprof-auto
-fno-prof-auto
-fprof-auto-calls
-fno-prof-auto
-fprof-auto-exported
-fno-prof-auto
-fprof-auto-top
-fno-prof-auto
-fprof-cafs
-fno-prof-cafs
-fprof-callers=⟨name⟩
-fprof-late
-fno-prof-late
-fprof-late-inline
-fno-prof-late-inline
-fprof-late-overloaded
-fno-prof-late-overloaded
-fprof-late-overloaded-calls
-fno-prof-late-overloaded-calls
-fprof-manual
-fno-prof-manual
-no-auto
-no-auto-all
-no-caf-all
-prof
-ticky
-ticky-allocd
-ticky-ap-thunk
-ticky-dyn-thunk
-ticky-LNE
-ticky-tag-checks
-fhpc
-hpcdir⟨dir⟩
-exclude-module=⟨file⟩
-fforce-recomp
-fno-force-recomp
-fignore-hpc-changes
-fno-ignore-hpc-changes
-fignore-optim-changes
-fno-ignore-optim-changes
-include-cpp-deps
-include-pkg-deps
-dep-makefile ⟨file⟩
-dep-suffix ⟨suffix⟩
-dumpdir ⟨dir⟩
-dynhisuf ⟨suffix⟩
-dyno ⟨file⟩
-dynohi ⟨file⟩
-dynosuf ⟨suffix⟩
-hcsuf ⟨suffix⟩
-hidir ⟨dir⟩
-hiedir ⟨dir⟩
-hiesuf ⟨suffix⟩
-hisuf ⟨suffix⟩
-o ⟨file⟩
-odir ⟨dir⟩
-ohi ⟨file⟩
-osuf ⟨suffix⟩
-outputdir ⟨dir⟩
-stubdir ⟨dir⟩
-tmpdir ⟨dir⟩
-fabstract-refinement-hole-fits
-fno-abstract-refinement-hole-fits
-fdefer-diagnostics
-fdiagnostics-as-json
-fdiagnostics-color=⟨always|auto|never⟩
-fdiagnostics-show-caret
-fno-diagnostics-show-caret
-ferror-spans
-fhide-source-paths
-fkeep-going
-fmax-refinement-hole-fits=⟨n⟩
-fno-max-refinement-hole-fits
-fmax-relevant-binds=⟨n⟩
-fno-max-relevant-binds
-fmax-valid-hole-fits=⟨n⟩
-fno-max-valid-hole-fits
-fno-show-valid-hole-fits
-fno-sort-valid-hole-fits
-fsort-valid-hole-fits
-fprint-axiom-incomps
-fno-print-axiom-incomps
-fprint-equality-relations
-fno-print-equality-relations
-fprint-error-index-links=⟨always|auto|never⟩
-fprint-expanded-synonyms
-fno-print-expanded-synonyms
-fprint-explicit-coercions
-fno-print-explicit-coercions
-fprint-explicit-foralls
-fno-print-explicit-foralls
-fprint-explicit-kinds
-fno-print-explicit-kinds
-fprint-explicit-runtime-reps
-fno-print-explicit-runtime-reps
-fprint-potential-instances
-fno-print-potential-instances
-fprint-redundant-promotion-ticks
-fno-print-redundant-promotion-ticks
-fprint-typechecker-elaboration
-fno-print-typechecker-elaboration
-fprint-unicode-syntax
-fno-print-unicode-syntax
-frefinement-level-hole-fits=⟨n⟩
-fno-refinement-level-hole-fits
-freverse-errors
-fno-reverse-errors
-fshow-docs-of-hole-fits
-fno-show-docs-of-hole-fits
-fshow-error-context
-fno-show-error-context
-fshow-hole-constraints
-fshow-hole-matches-of-hole-fits
-fno-show-hole-matches-of-hole-fits
-fshow-provenance-of-hole-fits
-fno-show-provenance-of-hole-fits
-fshow-type-app-of-hole-fits
-fno-show-type-app-of-hole-fits
-fshow-type-app-vars-of-hole-fits
-fno-show-type-app-vars-of-hole-fits
-fshow-type-of-hole-fits
-fno-show-type-of-hole-fits
-fsort-by-size-hole-fits
-fno-sort-by-size-hole-fits
-fsort-by-subsumption-hole-fits
-fno-sort-by-subsumption-hole-fits
-funclutter-valid-hole-fits
-Rghc-timing
-v
-v⟨n⟩
-fenable-th-splice-warnings
-fno-enable-th-splice-warnings
-fhelpful-errors
-fno-helpful-errors
-fmax-pmcheck-models=⟨n⟩
-fshow-warning-groups
-fno-show-warning-groups
-fvia-C
-W
-Wno-extra
-w
-Wall
-Wno-all
-Wall-missed-specialisations
-Wno-all-missed-specialisations
-Wall-missed-specializations
-Wno-all-missed-specializations
-Wambiguous-fields
-Wauto-orphans
-Wbadly-staged-types
-Wno-badly-staged-types
-Wcompat
-Wno-compat
-Wcompat-unqualified-imports
-Wno-compat-unqualified-imports
-Wcpp-undef
-Wdata-kinds-tc
-Wno-data-kinds-tc
-Wdefault
-Wno-default
-Wdefaulted-exception-context
-Wnop-defaulted-exception-context
-Wdeferred-out-of-scope-variables
-Wno-deferred-out-of-scope-variables
-Wdeferred-type-errors
-Wno-deferred-type-errors
-Wdeprecated-flags
-Wno-deprecated-flags
-Wdeprecated-type-abstractions
-Wno-deprecated-type-abstractions
-Wdeprecations
-Wno-deprecations
-Wderiving-defaults
-Wno-deriving-defaults
-Wderiving-typeable
-Wno-deriving-typeable
-Wdodgy-exports
-Wno-dodgy-exports
-Wdodgy-foreign-imports
-Wno-dodgy-foreign-imports
-Wdodgy-imports
-Wno-dodgy-imports
-Wduplicate-constraints
-Wno-duplicate-constraints
-Wduplicate-exports
-Wno-duplicate-exports
-Wempty-enumerations
-Wno-empty-enumerations
-Werror
-Wwarn
-Weverything
-w
-Wextended-warnings
-Wno-extended-warnings
-Wextra
-Wno-extra
-Wforall-identifier
-Wgadt-mono-local-binds
-Wno-gadt-mono-local-binds
-Whi-shadowing
-Wno-hi-shadowing
-Widentities
-Wno-identities
-Wimplicit-kind-vars
-Wno-implicit-kind-vars
-Wimplicit-lift
-Wno-implicit-lift
-Wimplicit-prelude
-Wno-implicit-prelude
-Wimplicit-rhs-quantification
-Wno-implicit-rhs-quantification
-Winaccessible-code
-Wno-inaccessible-code
-Wincomplete-export-warnings
-Wno-incomplete-export-warnings
-Wincomplete-patterns
-Wno-incomplete-patterns
-Wincomplete-record-selectors
-Wno-incomplete-record-selectors
-Wincomplete-record-updates
-Wno-incomplete-record-updates
-Wincomplete-uni-patterns
-Wno-incomplete-uni-patterns
-Winconsistent-flags
-Wno-inconsistent-flags
-Winferred-safe-imports
-Wno-inferred-safe-imports
-Winline-rule-shadowing
-Wno-inline-rule-shadowing
-Winvalid-haddock
-Wno-invalid-haddock
-Wloopy-superclass-solve
-Wno-loopy-superclass-solve
-Wmisplaced-pragmas
-Wno-misplaced-pragmas
-Wmissed-extra-shared-lib
-Wno-missed-extra-shared-lib
-Wmissed-specialisations
-Wno-missed-specialisations
-Wmissed-specializations
-Wno-missed-specializations
-Wmissing-deriving-strategies
-Wno-missing-deriving-strategies
-Wmissing-export-lists
-Wno-missing-export-lists
-Wmissing-exported-pattern-synonym-signatures
-Wno-missing-exported-pattern-synonym-signatures
-Wmissing-exported-signatures
-Wno-missing-exported-signatures
-Wmissing-exported-sigs
-Wno-missing-exported-sigs
-Wmissing-fields
-Wno-missing-fields
-Wmissing-home-modules
-Wno-missing-home-modules
-Wmissing-import-lists
-Wno-missing-import-lists
-Wmissing-kind-signatures
-Wno-missing-kind-signatures
-Wmissing-local-signatures
-Wno-missing-local-signatures
-Wmissing-local-sigs
-Wno-missing-local-sigs
-Wmissing-methods
-Wno-missing-methods
-Wmissing-monadfail-instances
-Wno-missing-monadfail-instances
-Wmissing-pattern-synonym-signatures
-Wno-missing-pattern-synonym-signatures
-Wmissing-poly-kind-signatures
-Wno-missing-poly-kind-signatures
-Wmissing-role-annotations
-Wno-role-annotations-signatures
-Wmissing-safe-haskell-mode
-Wno-missing-safe-haskell-mode
-Wmissing-signatures
-Wno-missing-signatures
-Wmissing-space-after-bang
-Wmonomorphism-restriction
-Wno-monomorphism-restriction
-Wname-shadowing
-Wno-name-shadowing
-Wnoncanonical-monad-instances
-Wno-noncanonical-monad-instances
-Wnoncanonical-monadfail-instances
-Wno-noncanonical-monadfail-instances
-Wnoncanonical-monoid-instances
-Wno-noncanonical-monoid-instances
-Wnot
-Woperator-whitespace
-Wno-operator-whitespace
-Woperator-whitespace-ext-conflict
-Wno-operator-whitespace-ext-conflict
-Worphans
-Wno-orphans
-Woverflowed-literals
-Wno-overflowed-literals
-Woverlapping-patterns
-Wno-overlapping-patterns
-Wpartial-fields
-Wno-partial-fields
-Wpartial-type-signatures
-Wno-partial-type-signatures
-Wprepositive-qualified-module
-Wno-prepositive-qualified-module
-Wredundant-bang-patterns
-Wno-redundant-bang-patterns
-Wredundant-constraints
-Wno-redundant-constraints
-Wredundant-record-wildcards
-Wno-redundant-record-wildcards
-Wredundant-strictness-flags
-Wno-redundant-strictness-flags
-Wsafe
-Wno-safe
-Wsemigroup
-Wno-semigroup
-Wsimplifiable-class-constraints
-Wno-simplifiable-class-constraints
-Wstar-binder
-Wno-star-binder
-Wstar-is-type
-Wno-star-is-type
-Wtabs
-Wno-tabs
-Wterm-variable-capture
-Wtrustworthy-safe
-Wno-safe
-Wtype-defaults
-Wno-type-defaults
-Wtype-equality-out-of-scope
-Wno-type-equality-out-of-scope
-Wtype-equality-requires-operators
-Wno-type-equality-requires-operators
-Wtyped-holes
-Wno-typed-holes
-Wunbanged-strict-patterns
-Wno-unbanged-strict-patterns
-Wunicode-bidirectional-format-characters
-Wunrecognised-pragmas
-Wno-unrecognised-pragmas
-Wunrecognised-warning-flags
-Wno-unrecognised-warning-flags
-Wunsafe
-Wno-unsafe
-Wunsupported-calling-conventions
-Wno-unsupported-calling-conventions
-Wunsupported-llvm-version
-Wno-unsupported-llvm-version
-Wunticked-promoted-constructors
-Wno-unticked-promoted-constructors
-Wunused-binds
-Wno-unused-binds
-Wunused-do-bind
-Wno-unused-do-bind
-Wunused-foralls
-Wno-unused-foralls
-Wunused-imports
-Wno-unused-imports
-Wunused-local-binds
-Wno-unused-local-binds
-Wunused-matches
-Wno-unused-matches
-Wunused-packages
-Wno-unused-packages
-Wunused-pattern-binds
-Wno-unused-pattern-binds
-Wunused-record-wildcards
-Wno-unused-record-wildcards
-Wunused-top-binds
-Wno-unused-top-binds
-Wunused-type-patterns
-Wno-unused-type-patterns
-Wwarn
-Werror
-Wwarnings-deprecations
-Wno-warnings-deprecations
-Wwrong-do-bind
-Wno-wrong-do-bind
-Wx-⟨category⟩
-Wno-x-⟨category⟩
Code generation¶
-dynamic-too
Build dynamic object files as well as static object files during compilation
-fasm
Use the native code generator
-fbyte-code
Generate byte-code
-fbyte-code-and-object-code
Generate object code and byte-code
-fexpose-internal-symbols
Produce symbols for all functions, including internal functions.
-fexternal-dynamic-refs
Generate code for linking against dynamic libraries
-fllvm
Compile using the LLVM code generator
-fno-code
Omit code generation
-fobject-code
Generate object code
-fPIC
Generate position-independent code (where available)
-fPIE
Generate code for a position-independent executable (where available)
-fprefer-byte-code
Use byte-code if it is available to evaluate TH splices
-fwrite-if-simplified-core
Write an interface file containing the simplified core of the module.
-fwrite-interface
Always write interface files
Debugging the compiler¶
-dasm-lint
ASM pass sanity checking
-dcmm-lint
C-\- pass sanity checking
-dcore-lint
Turn on internal sanity checking
-ddisable-js-c-sources
Disable the link with C sources compiled to JavaScript
-ddisable-js-minifier
Generate pretty-printed JavaScript code instead of minified (compacted) code.
-ddump-asm
Dump final assembly
-ddump-asm-conflicts
Dump register conflicts from the register allocator.
-ddump-asm-liveness
Dump assembly augmented with register liveness
-ddump-asm-native
Dump initial assembly
-ddump-asm-regalloc
Dump the result of register allocation
-ddump-asm-regalloc-stages
Dump the build/spill stages of the
-fregs-graph
register allocator.-ddump-asm-stats
Dump statistics from the register allocator.
-ddump-bcos
Dump interpreter byte code
-ddump-c-backend
Dump C code produced by the C (unregisterised) backend.
-ddump-call-arity
Dump output of the call arity analysis pass.
-ddump-cfg-weights
Dump the assumed weights of the CFG.
-ddump-cmm
Dump the final C-\- output
-ddump-cmm-caf
Dump the results of the C-\- CAF analysis pass.
-ddump-cmm-cbe
Dump the results of common block elimination
-ddump-cmm-cfg
Dump the results of the C-\- control flow optimisation pass.
-ddump-cmm-cps
Dump the results of the CPS pass
-ddump-cmm-from-stg
Dump STG-to-C-\- output
-ddump-cmm-info
Dump the results of the C-\- info table augmentation pass.
-ddump-cmm-opt
Dump the results of C-\- to C-\- optimising passes
-ddump-cmm-proc
Dump the results of proc-point analysis
-ddump-cmm-procmap
Dump the results of the C-\- proc-point map pass.
-ddump-cmm-raw
Dump raw C-\-
-ddump-cmm-sink
Dump the results of the C-\- sinking pass.
-ddump-cmm-sp
Dump the results of the C-\- stack layout pass.
-ddump-cmm-split
Dump the results of the C-\- proc-point splitting pass.
-ddump-cmm-switch
Dump the results of switch lowering passes
-ddump-cmm-thread-sanitizer
Dump the results of the C-\- ThreadSanitizer elaboration pass.
-ddump-cmm-verbose
Write output from main C-\- pipeline passes to files
-ddump-cmm-verbose-by-proc
Show output from main C-\- pipeline passes (grouped by proc)
-ddump-core-stats
Print a one-line summary of the size of the Core program at the end of the optimisation pipeline
-ddump-cpr-signatures
Dump CPR signatures
-ddump-cpranal
Dump CPR analysis output
-ddump-cs-trace
Trace constraint solver
-ddump-cse
Dump CSE output
-ddump-debug
Dump generated DWARF debug information
-ddump-deriv
Dump deriving output
-ddump-dmd-signatures
Dump top-level demand signatures
-ddump-dmdanal
Dump demand analysis output
-ddump-ds
Dump desugarer output.
-ddump-ec-trace
Trace exhaustiveness checker
-ddump-exitify
Dump output of the exitification pass.
-ddump-faststrings
Dump the whole FastString table when finished
-ddump-file-prefix=⟨str⟩
Set the prefix of the filenames used for debugging output.
-ddump-float-in
Dump float in output
-ddump-foreign
Dump
foreign export
stubs-ddump-full-laziness
Dump full laziness pass output
-ddump-hie
Dump the hie file syntax tree
-ddump-hpc
An alias for
-ddump-ticked
.-ddump-if-trace
Trace interface files
-ddump-inlinings
Dump inlinings performed by the simplifier.
-ddump-js
Dump final JavaScript code
-ddump-json
(deprecated) Use
-fdiagnostics-as-json
instead-ddump-late-cc
Dump core with late cost centres added
-ddump-liberate-case
Dump liberate case output
-ddump-llvm
Dump LLVM intermediate code.
-ddump-mod-map
Dump the state of the module mapping database.
-ddump-occur-anal
Dump occurrence analysis output
-ddump-opt-cmm
Dump the results of C-\- to C-\- optimising passes
-ddump-parsed
Dump parse tree
-ddump-parsed-ast
Dump parser output as a syntax tree
-ddump-prep
Dump prepared core
-ddump-rn
Dump renamer output
-ddump-rn-ast
Dump renamer output as a syntax tree
-ddump-rn-stats
Renamer stats
-ddump-rn-trace
Trace renamer
-ddump-rtti
Trace runtime type inference
-ddump-rule-firings
Dump rule firing info
-ddump-rule-rewrites
Dump detailed rule firing info
-ddump-rules
Dump rewrite rules
-ddump-simpl
Dump final simplifier output
-ddump-simpl-iterations
Dump output from each simplifier iteration
-ddump-simpl-stats
Dump simplifier stats
-ddump-simpl-trace
Dump trace messages in simplifier
-ddump-spec
Dump specialiser output
-ddump-spec-constr
Dump specialiser output from SpecConstr
-ddump-splices
Dump TH spliced expressions, and what they evaluate to
-ddump-static-argument-transformation
Dump static argument transformation output
-ddump-stg
(deprecated) Alias for
-ddump-stg-from-core
-ddump-stg-cg
Show output after Stg2Stg
-ddump-stg-final
Show output of last STG pass.
-ddump-stg-from-core
Show CoreToStg output
-ddump-stg-tags
Show output of the tag inference pass.
-ddump-stg-unarised
Show unarised STG
-ddump-str-signatures
(deprecated) Alias for
-ddump-dmd-signatures
-ddump-stranal
(deprecated) Alias for
-ddump-dmdanal
-ddump-tc
Dump typechecker output
-ddump-tc-ast
Dump typechecker output as a syntax tree
-ddump-tc-trace
Trace typechecker
-ddump-ticked
Dump the code instrumented by HPC (Observing Code Coverage).
-ddump-timings
Dump per-pass timing and allocation statistics
-ddump-to-file
Dump to files instead of stdout
-ddump-types
Dump type signatures
-ddump-verbose-inlinings
Dump all considered inlinings
-ddump-view-pattern-commoning
Dump commoned view patterns
-ddump-worker-wrapper
Dump worker-wrapper output
-dfaststring-stats
Show statistics for fast string usage when finished
-dhex-word-literals
Print values of type Word# in hexadecimal.
-dinitial-unique=⟨s⟩
Start
UniqSupply
allocation from ⟨s⟩.-dinline-check=⟨str⟩
Dump information about inlining decisions
-dipe-stats
Show statistics about IPE information
-dkeep-comments
Include comments in the parser. Useful in combination with
-ddump-parsed-ast
.-dlinear-core-lint
Turn on internal sanity checking
-dlint
Enable several common internal sanity checkers
-dno-debug-output
Suppress unsolicited debugging output
-dno-typeable-binds
Don't generate bindings for Typeable methods
-dppr-case-as-let
Print single alternative case expressions as strict lets.
-dppr-cols=⟨n⟩
Set the width of debugging output. For example
-dppr-cols200
-dppr-debug
Turn on debug printing (more verbose)
-dppr-user-length
Set the depth for printing expressions in error msgs
-drule-check=⟨str⟩
Dump information about potential rule application
-dshow-passes
Print out each pass name as it happens
-dstg-lint
STG pass sanity checking
-dsuppress-all
In dumps, suppress everything (except for uniques) that is suppressible.
-dsuppress-coercion-types
Suppress the printing of coercion types in Core dumps to make them shorter
-dsuppress-coercions
Suppress the printing of coercions in Core dumps to make them shorter
-dsuppress-core-sizes
Suppress the printing of core size stats per binding (since 9.4)
-dsuppress-idinfo
Suppress extended information about identifiers where they are bound
-dsuppress-module-prefixes
Suppress the printing of module qualification prefixes
-dsuppress-stg-free-vars
Suppress the printing of closure free variable lists in STG output
-dsuppress-stg-reps
Suppress rep annotations on STG args.
-dsuppress-ticks
Suppress "ticks" in the pretty-printer output.
-dsuppress-timestamps
Suppress timestamps in dumps
-dsuppress-type-applications
Suppress type applications
-dsuppress-type-signatures
Suppress type signatures
-dsuppress-unfoldings
Suppress the printing of the stable unfolding of a variable at its binding site
-dsuppress-uniques
Suppress the printing of uniques in debug output (easier to use
diff
)-dsuppress-var-kinds
Suppress the printing of variable kinds
-dtag-inference-checks
Affirm tag inference results are correct at runtime.
-dth-dec-file
Dump evaluated TH declarations into *.th.hs files
-dunique-increment=⟨i⟩
Set the increment for the generated
Unique
's to ⟨i⟩.-dverbose-core2core
Show output from each core-to-core pass
-dverbose-stg2stg
Show output from each STG-to-STG pass
-falignment-sanitisation
Compile with alignment checks for all info table dereferences.
-fcatch-nonexhaustive-cases
Add a default
error
alternative to case expressions without a default alternative.-fcheck-prim-bounds
Instrument array primops with bounds checks.
-fcmm-thread-sanitizer
Enable ThreadSanitizer instrumentation of memory accesses.
-fdistinct-constructor-tables
Generate a fresh info table for each usage of a data constructor.
-fdump-with-ways
Include the tag of the enabled ways in the extension of dump files.
-finfo-table-map
Embed a lookup table in the generated binary which maps the address of an info table to the source position the closure originated from.
-finfo-table-map-with-fallback
Include info tables with no source location information in the info table map.
-finfo-table-map-with-stack
Include info tables for
STACK
closures in the info table map.-fllvm-fill-undef-with-garbage
Intruct LLVM to fill dead STG registers with garbage
-fno-info-table-map-with-fallback
Omit info tables with no source location information from the info table map.
-fno-info-table-map-with-stack
Omit info tables for
STACK
closures from the info table map.-forig-thunk-info
Generate
stg_orig_thunk_info
stack frames on thunk entry-fproc-alignment
Align functions at given boundary.
-funoptimized-core-for-interpreter
Disable optimizations with the interpreter
-g
Produce DWARF debug information in compiled object files. ⟨n⟩ can be 0, 1, or 2, with higher numbers producing richer output. If ⟨n⟩ is omitted, level 2 is assumed.
C pre-processor¶
-cpp
Run the C pre-processor on Haskell source files
-D⟨symbol⟩[=⟨value⟩]
Define a symbol in the C pre-processor
-I⟨dir⟩
Add ⟨dir⟩ to the directory search list for
#include
files-U⟨symbol⟩
Undefine a symbol in the C pre-processor
Finding imports¶
-i
Empty the import directory list
-i⟨dir⟩[:⟨dir⟩]*
add ⟨dir⟩, ⟨dir2⟩, etc. to import path
Interactive mode¶
-fbreak-on-error
-fbreak-on-exception
-fbreak-points
-fghci-hist-size=⟨n⟩
Set the number of entries GHCi keeps for
:history
. See The GHCi Debugger.-fghci-leak-check
(Debugging only) check for space leaks when loading new modules in GHCi.
-fimplicit-import-qualified
Put in scope qualified identifiers for every loaded module
-flocal-ghci-history
Use current directory for the GHCi command history file
.ghci-history
.-fno-it
No longer set the special variable
it
.-fprint-bind-result
-fprint-evld-with-show
Instruct
:print
to useShow
instances where possible.-fshow-loaded-modules
Show the names of modules that GHCi loaded after a
:load
command.-ghci-script
Read additional
.ghci
files-ignore-dot-ghci
Disable reading of
.ghci
files-interactive-print ⟨name⟩
Select the function to use for printing evaluated expressions in GHCi
Interface files¶
--show-iface ⟨file⟩
See Modes of operation.
-ddump-hi
Dump the new interface to stdout
-ddump-hi-diffs
Show the differences vs. the old interface
-ddump-minimal-imports
Dump a minimal set of imports
Keeping intermediate files¶
-keep-hc-file
Retain intermediate
.hc
files.-keep-hi-files
Retain intermediate
.hi
files (the default).-keep-hscpp-file
Retain intermediate
.hscpp
files.-keep-llvm-file
Retain intermediate LLVM
.ll
files. Implies-fllvm
.-keep-o-files
Retain intermediate
.o
files (the default).-keep-s-file
Retain intermediate
.s
files.-keep-tmp-files
Retain all intermediate temporary files.
Language options¶
-XAllowAmbiguousTypes
- Allow the user to write ambiguous types, and the type inference engine to infer them.
-XApplicativeDo
- Enable Applicative do-notation desugaring
-XArrows
- Enable arrow notation extension
-XBangPatterns
- Enable bang patterns.
-XBinaryLiterals
- Enable support for binary literals.
-XBlockArguments
- Allow
do
blocks and other constructs as function arguments. -XCApiFFI
- Enable the CAPI calling convention.
-XConstrainedClassMethods
- Enable constrained class methods.
Implied by
MultiParamTypeClasses
. -XConstraintKinds
- Enable a kind of constraints.
-XCPP
- Enable the C preprocessor.
-XCUSKs
- Enable detection of complete user-supplied kind signatures.
-XDataKinds
- Enable datatype promotion.
-XDatatypeContexts
- Allow contexts on
data
types. -XDeepSubsumption
- Enable deep subsumption
-XDefaultSignatures
- Enable default signatures.
-XDeriveAnyClass
- Enable deriving for any class.
-XDeriveDataTypeable
- Enable deriving for the
Data
class. -XDeriveFoldable
- Enable deriving for the Foldable class.
Implied by
DeriveTraversable
. -XDeriveFunctor
- Enable deriving for the Functor class.
Implied by
DeriveTraversable
. -XDeriveGeneric
- Enable deriving for the Generic class.
-XDeriveLift
- Enable deriving for the Lift class
-XDeriveTraversable
- Enable deriving for the Traversable class.
Implies
DeriveFunctor
andDeriveFoldable
. -XDerivingStrategies
- Enables deriving strategies.
-XDerivingVia
- Enable deriving instances
via
types of the same runtime representation. ImpliesDerivingStrategies
. -XDisambiguateRecordFields
- Enable record field disambiguation.
Implied by
RecordWildCards
. -XDuplicateRecordFields
- Allow definition of record types with identically-named fields.
-XEmptyCase
- Allow empty case alternatives.
-XEmptyDataDecls
- Allow definition of empty
data
types. -XEmptyDataDeriving
- Allow deriving instances of standard type classes for empty data types.
-XExistentialQuantification
- Enable liberalised type synonyms.
-XExplicitForAll
- Enable explicit universal quantification.
Implied by
ScopedTypeVariables
,LiberalTypeSynonyms
,RankNTypes
andExistentialQuantification
. -XExplicitNamespaces
- Enable using the keyword
type
to specify the namespace of entries in imports and exports (Explicit namespaces in import/export). Implied byTypeOperators
andTypeFamilies
. -XExtendedDefaultRules
- Use GHCi's extended default rules in a normal module.
-XExtendedLiterals
- Enable numeric literal postfix syntax for unboxed integers.
-XFieldSelectors
- Control visibility of field selector functions.
-XFlexibleContexts
- Remove some restrictions on class contexts
-XFlexibleInstances
- Enable flexible instances.
Implies
TypeSynonymInstances
. -XForeignFunctionInterface
- Enable foreign function interface.
-XFunctionalDependencies
- Enable functional dependencies.
Implies
MultiParamTypeClasses
. -XGADTs
- Enable generalised algebraic data types.
Implies
GADTSyntax
andMonoLocalBinds
. -XGADTSyntax
- Enable generalised algebraic data type syntax.
-XGeneralisedNewtypeDeriving
- Enable newtype deriving.
-XGeneralizedNewtypeDeriving
- Enable newtype deriving.
-XGHC2021
- Use GHC’s set of default language extensions from 2021
-XGHC2024
- Use GHC’s set of default language extensions from 2024
-XGHCForeignImportPrim
- Enable prim calling convention. Intended for internal use only.
-XHaskell2010
- Use the Haskell 2010 language edition.
-XHaskell98
- Use the Haskell 98 language edition.
-XHexFloatLiterals
- Enable support for hexadecimal floating point literals.
-XImplicitParams
- Enable Implicit Parameters.
-XImportQualifiedPost
ImportQualifiedPost
allows the syntaximport M qualified
-XImpredicativeTypes
- Enable impredicative types.
Implies
RankNTypes
. -XIncoherentInstances
- Enable incoherent instances.
Implies
OverlappingInstances
. -XInstanceSigs
- Enable instance signatures.
-XInterruptibleFFI
- Enable interruptible FFI.
-XKindSignatures
- Enable kind signatures.
Implied by
TypeFamilies
andPolyKinds
. -XLambdaCase
- Enable lambda-case expressions.
-XLexicalNegation
- Use whitespace to determine whether the minus sign stands for negation or subtraction.
-XLiberalTypeSynonyms
- Enable liberalised type synonyms.
-XLinearTypes
- Enable linear types.
Implies
MonoLocalBinds
. -XListTuplePuns
- Enable punning for list, tuple and sum types.
-XMagicHash
- Allow
#
as a postfix modifier on identifiers. -XMonadComprehensions
- Enable monad comprehensions.
-XMonoLocalBinds
- Enable do not generalise local bindings.
Implied by
TypeFamilies
andGADTs
. -XMultiParamTypeClasses
- Enable multi parameter type classes.
Implied by
FunctionalDependencies
. ImpliesConstrainedClassMethods
. -XMultiWayIf
- Enable multi-way if-expressions.
-XNamedFieldPuns
- Enable record puns.
-XNamedWildCards
- Enable named wildcards.
-XNegativeLiterals
- Enable support for negative literals.
-XNoImplicitPrelude
- Don't implicitly
import Prelude
. Implied byRebindableSyntax
. -XNoMonomorphismRestriction
- Disable the monomorphism restriction.
-XNondecreasingIndentation
- Allow nested contexts to be at the same indentation level as its enclosing context.
-XNoPatternGuards
- Disable pattern guards.
Implied by
Haskell98
. -XNoTraditionalRecordSyntax
- Disable support for traditional record syntax
(as supported by Haskell 98)
C {f = x}
-XNPlusKPatterns
- Enable support for
n+k
patterns. Implied byHaskell98
. -XNullaryTypeClasses
- Deprecated, does nothing. nullary (no parameter) type
classes are now enabled using
MultiParamTypeClasses
. -XNumDecimals
- Enable support for 'fractional' integer literals.
-XNumericUnderscores
- Enable support for numeric underscores.
-XOverlappingInstances
- Enable overlapping instances.
-XOverloadedLabels
- Enable overloaded labels.
-XOverloadedLists
- Enable overloaded lists.
-XOverloadedRecordDot
- Record '.' syntax
-XOverloadedRecordUpdate
- Record '.' syntax record updates
-XOverloadedStrings
- Enable overloaded string literals.
-XPackageImports
- Enable package-qualified imports.
-XParallelListComp
- Enable parallel list comprehensions.
-XPartialTypeSignatures
- Enable partial type signatures.
-XPatternSynonyms
- Enable pattern synonyms.
-XPolyKinds
- Enable kind polymorphism.
Implies
KindSignatures
. -XPostfixOperators
- Enable postfix operators.
-XQualifiedDo
- Enable qualified do-notation desugaring.
-XQuantifiedConstraints
- Allow
forall
quantifiers in constraints. -XQuasiQuotes
- Enable quasiquotation.
-XRank2Types
- Enable rank-2 types.
Synonym for
RankNTypes
. -XRankNTypes
- Enable rank-N types.
Implied by
ImpredicativeTypes
. -XRebindableSyntax
- Employ rebindable syntax.
Implies
NoImplicitPrelude
. -XRecordWildCards
- Enable record wildcards.
Implies
DisambiguateRecordFields
. -XRecursiveDo
- Enable recursive do (mdo) notation.
-XRequiredTypeArguments
- Enable required type arguments in terms.
-XRoleAnnotations
- Enable role annotations.
-XSafe
- Enable the Safe Haskell Safe mode.
-XScopedTypeVariables
- Enable lexically-scoped type variables.
-XStandaloneDeriving
- Enable standalone deriving.
-XStandaloneKindSignatures
- Allow the use of standalone kind signatures.
-XStarIsType
- Treat
*
asData.Kind.Type
. -XStaticPointers
- Enable static pointers.
-XStrict
- Make bindings in the current module strict by default.
-XStrictData
- Enable default strict datatype fields.
-XTemplateHaskell
- Enable Template Haskell.
-XTemplateHaskellQuotes
- Enable quotation subset of Template Haskell.
-XTransformListComp
- Enable generalised list comprehensions.
-XTrustworthy
- Enable the Safe Haskell Trustworthy mode.
-XTupleSections
- Enable tuple sections.
-XTypeAbstractions
- Enable type abstraction syntax in patterns and type variable binders.
-XTypeApplications
- Enable type application syntax in terms and types.
-XTypeData
- Enable type data declarations.
-XTypeFamilies
- Enable type families.
Implies
ExplicitNamespaces
,KindSignatures
, andMonoLocalBinds
. -XTypeFamilyDependencies
- Enable injective type families.
Implies
TypeFamilies
. -XTypeInType
- Deprecated. Enable kind polymorphism and datatype promotion.
-XTypeOperators
- Enable type operators.
Implies
ExplicitNamespaces
. -XTypeSynonymInstances
- Enable type synonyms in instance heads.
Implied by
FlexibleInstances
. -XUnboxedSums
- Enable unboxed sums.
-XUnboxedTuples
- Enable the use of unboxed tuple syntax.
-XUndecidableInstances
- Enable undecidable instances.
-XUndecidableSuperClasses
- Allow all superclass constraints, including those that may result in non-termination of the typechecker.
-XUnicodeSyntax
- Enable unicode syntax.
-XUnliftedDatatypes
- Enable unlifted data types.
-XUnliftedFFITypes
- Enable unlifted FFI types
-XUnliftedNewtypes
- Enable unlifted newtypes.
-XUnsafe
- Enable Safe Haskell Unsafe mode.
-XViewPatterns
- Enable view patterns.
Linking options¶
-c
Stop after generating object (
.o
) file-debug
Use the debugging runtime
-dylib-install-name ⟨path⟩
Set 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
Build dynamically-linked object files and executables
-dynload
Selects one of a number of modes for finding shared libraries at runtime.
-eventlog
Enable runtime event tracing
-fcompact-unwind
Instruct the linker to produce a __compact_unwind section.
-fkeep-cafs
Do not garbage-collect CAFs (top-level expressions) at runtime
-flink-rts
Link the runtime when generating a shared or static library
-fno-embed-manifest
Do not embed the manifest in the executable (Windows only)
-fno-gen-manifest
Do not generate a manifest file (Windows only)
-fno-shared-implib
Don't generate an import library for a DLL (Windows only)
-framework ⟨name⟩
On Darwin/OS X/iOS only, link in the framework ⟨name⟩. This option corresponds to the
-framework
option for Apple's Linker.-framework-path ⟨dir⟩
On 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.-fsplit-sections
Split sections for link-time dead-code stripping
-fuse-rpaths
Set the rpath based on -L flags
-fwhole-archive-hs-libs
When linking a binary executable, this inserts the flag
-Wl,--whole-archive
before any-l
flags for Haskell libraries, and-Wl,--no-whole-archive
afterwards-L ⟨dir⟩
Add ⟨dir⟩ to the list of directories searched for libraries
-l ⟨lib⟩
Link in library ⟨lib⟩
-main-is ⟨thing⟩
Set main module and function
-no-hs-main
Don't assume this program contains
main
-no-pie
Don't instruct the linker to produce a position-independent executable.
-no-rtsopts-suggestions
Don't print RTS suggestions about linking with
-rtsopts[=⟨none|some|all|ignore|ignoreAll⟩]
.-package ⟨name⟩
Expose package ⟨pkg⟩
-pie
Instruct the linker to produce a position-independent executable.
-rdynamic
This 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.-rtsopts[=⟨none|some|all|ignore|ignoreAll⟩]
Control whether the RTS behaviour can be tweaked via command-line flags and the
GHCRTS
environment variable. Usingnone
means no RTS flags can be given;some
means only a minimum of safe options can be given (the default);all
(or no argument at all) means that all RTS flags are permitted;ignore
means RTS flags can be given, but are treated as regular arguments and passed to the Haskell program as arguments;ignoreAll
is the same asignore
, butGHCRTS
is also ignored.-rtsopts
does not affect-with-rtsopts
behavior; flags passed via-with-rtsopts
are used regardless of-rtsopts
.-shared
Generate a shared library (as opposed to an executable)
-single-threaded
Use the single-threaded runtime
-static
Use static Haskell libraries
-staticlib
Generate a standalone static library (as opposed to an executable). This is useful when cross compiling. The library together with all its dependencies ends up in in a single static library that can be linked against.
-threaded
Use the threaded runtime
-with-rtsopts=⟨opts⟩
Set the default RTS options to ⟨opts⟩.
Miscellaneous options¶
-ddump-mod-cycles
Dump module cycles
-fdefer-out-of-scope-variables
Convert variable out of scope variables errors into warnings. Implied by
-fdefer-type-errors
. See also-Wdeferred-out-of-scope-variables
.-fdefer-type-errors
Turn type errors into warnings, deferring the error until runtime. Implies
-fdefer-typed-holes
and-fdefer-out-of-scope-variables
. See also-Wdeferred-type-errors
.-fdefer-typed-holes
Convert typed hole errors into warnings, deferring the error until runtime. Implied by
-fdefer-type-errors
. See also-Wtyped-holes
.-fexternal-interpreter
Run interpreted code in a separate process
-ffamily-application-cache
Use a cache when reducing type family applications
-fglasgow-exts
Deprecated. Enable most language extensions; see Controlling editions and extensions for exactly which ones.
-fno-safe-haskell
Disable Safe Haskell
-ghcversion-file ⟨path to ghcversion.h⟩
(GHC as a C compiler only) Use this
ghcversion.h
file-H ⟨size⟩
Set the minimum size of the heap to ⟨size⟩
-hidden-module ⟨module name⟩
A module which should not be visible outside its unit.
-j[⟨n⟩]
When compiling with
--make
, compile ⟨n⟩ modules in parallel.-jsem
When compiling with
--make
, coordinate with other processes through the semaphore ⟨sem⟩ to compile modules in parallel.-reexported-module ⟨module name⟩
A module which should be reexported from this unit.
-this-package-name ⟨unit-id⟩
The name of the package which this module would be part of when installed.
-unit @⟨filename⟩
Specify the options to build a specific unit.
-working-dir ⟨dir⟩
Specify the directory a unit is expected to be compiled in.
Modes of operation¶
--frontend ⟨module⟩
run GHC with the given frontend plugin; see Frontend plugins for details.
--help
Display help
--info
display information about the compiler
--interactive
Interactive mode - normally used by just running
ghci
; see Using GHCi for details.--make
Build a multi-module Haskell program, automatically figuring out dependencies. Likely to be much easier, and faster, than using
make
; see Using ghc --make for details.--numeric-version
display GHC version (numeric only)
--print-booter-version
display bootstrap compiler version
--print-build-platform
display platform on which GHC was built
--print-c-compiler-flags
C compiler flags used to build GHC
--print-c-compiler-link-flags
C linker flags used to build GHC
--print-debug-on
print whether GHC was built with
-DDEBUG
--print-global-package-db
display GHC's global package database directory
--print-have-interpreter
display whether GHC was built with interactive support
--print-have-native-code-generator
display whether target platform has NCG support
--print-host-platform
display host platform of GHC
--print-ld-flags
display linker flags used to compile GHC
--print-leading-underscore
display use of leading underscores on symbol names
--print-libdir
display GHC library directory
--print-object-splitting-supported
display whether GHC supports object splitting
--print-project-git-commit-id
display Git commit id GHC is built from
--print-project-version
display GHC version
--print-rts-ways
display which way RTS was built
--print-stage
display
stage
number of GHC--print-support-smp
display whether GHC was compiled with SMP support
--print-tables-next-to-code
display whether GHC was compiled with
--enable-tables-next-to-code
--print-target-platform
display target platform of GHC
--print-unregisterised
display whether this GHC was built in unregisterised mode
--run ⟨file⟩
Run a Haskell program.
--show-iface ⟨file⟩
display the contents of an interface file.
--show-options
display the supported command line options
--supported-extensions
display the supported language extensions
--version
display GHC version
-e ⟨expr⟩
Evaluate
expr
; see Expression evaluation mode for details.-M
generate dependency information suitable for use in a
Makefile
; see Dependency generation for details.-shared
Create a shared object.
Individual optimizations¶
-fasm-shortcutting
Enable shortcutting on assembly. Implied by
-O2
.-fbinary-blob-threshold=⟨n⟩
default: 500K. Tweak assembly generator for binary blobs.
-fblock-layout-cfg
Use the new cfg based block layout algorithm. Implied by
-O
.-fblock-layout-weightless
Ignore cfg weights for code layout.
-fblock-layout-weights
Sets edge weights used by the new code layout algorithm.
-fcall-arity
Enable call-arity optimisation. Implied by
-O
.-fcase-folding
Enable constant folding in case expressions. Implied by
-O
.-fcase-merge
Enable case-merging. Implied by
-O
.-fcmm-control-flow
Enable control flow optimisation in the Cmm backend. Implied by
-O
.-fcmm-elim-common-blocks
Enable Cmm common block elimination. Implied by
-O
.-fcmm-sink
Enable Cmm sinking. Implied by
-O
.-fcmm-static-pred
Enable static control flow prediction. Implied by
-O
.-fcore-constant-folding
Enable constant folding in Core. Implied by
-O
.-fcpr-anal
Turn on Constructed Product Result analysis. Implied by
-O
.-fcross-module-specialise
Turn on specialisation of overloaded functions imported from other modules. Implied by
-O
.-fcse
Enable common sub-expression elimination. Implied by
-O
.-fdicts-cheap
Make dictionary-valued expressions seem cheap to the optimiser.
-fdicts-strict
Make dictionaries strict. Implied by
-O2
.-fdmd-tx-dict-sel
(deprecated) Use a special demand transformer for dictionary selectors.
-fdmd-unbox-width=⟨n⟩
default: 3. Boxity analysis pretends that returned records with this many fields can be unboxed.
-fdo-clever-arg-eta-expansion
Enable sophisticated argument eta-expansion. Implied by
-O2
.-fdo-eta-reduction
Enable eta-reduction. Always enabled by default.
-fdo-lambda-eta-expansion
Enable lambda eta-expansion. Always enabled by default.
-feager-blackholing
Turn on eager blackholing
-fenable-rewrite-rules
Switch on all rewrite rules (including rules generated by automatic specialisation of overloaded functions). Implied by
-O
.-fexcess-precision
Enable excess intermediate precision
-fexitification
Enables exitification optimisation. Implied by
-O
.-fexpose-all-unfoldings
Expose all unfoldings, even for very large or recursive functions.
-ffloat-in
Turn on the float-in transformation. Implied by
-O
.-ffull-laziness
Turn on full laziness (floating bindings outwards). Implied by
-O
.-ffun-to-thunk
(deprecated) superseded by -ffull-laziness.
-fignore-asserts
Ignore assertions in the source. Implied by
-O
.-fignore-interface-pragmas
Ignore pragmas in interface files. Implied by
-O0
only.-finline-generics
Annotate methods of derived Generic and Generic1 instances with INLINE[1] pragmas based on heuristics. Implied by
-O
.-finline-generics-aggressively
Annotate methods of all derived Generic and Generic1 instances with INLINE[1] pragmas.
-fkeep-auto-rules
Keep all "auto" rules, generated by specialisation
-flate-dmd-anal
Run demand analysis again, at the end of the simplification pipeline
-flate-specialise
Run a late specialisation pass
-fliberate-case
Turn on the liberate-case transformation. Implied by
-O2
.-fliberate-case-threshold=⟨n⟩
default: 2000. Set the size threshold for the liberate-case transformation to ⟨n⟩
-fllvm-pass-vectors-in-regs
(deprecated) Does nothing
-flocal-float-out
Enable local floating definitions out of let-binds.
-flocal-float-out-top-level
Enable local floating to float top-level bindings
-floopification
Turn saturated self-recursive tail-calls into local jumps in the generated assembly. Implied by
-O
.-fmax-inline-alloc-size=⟨n⟩
default: 128. Set the maximum size of inline array allocations to ⟨n⟩ bytes (default: 128).
-fmax-inline-memcpy-insns=⟨n⟩
default: 32. Inline
memcpy
calls if they would generate no more than ⟨n⟩ pseudo instructions.-fmax-inline-memset-insns=⟨n⟩
default: 32. Inline
memset
calls if they would generate no more than ⟨n⟩ pseudo instructions-fmax-simplifier-iterations=⟨n⟩
default: 4. Set the max iterations for the simplifier.
-fmax-uncovered-patterns=⟨n⟩
default: 4. Set the maximum number of patterns to display in warnings about non-exhaustive ones.
-fmax-worker-args=⟨n⟩
default: 10. Maximum number of value arguments for a worker.
-fno-opt-coercion
Turn off the coercion optimiser
-fno-pre-inlining
Turn off pre-inlining
-fno-state-hack
Turn off the state hackwhereby any lambda with a real-world state token as argument is considered to be single-entry. Hence OK to inline things inside it.
-fomit-interface-pragmas
Don't generate interface pragmas. Implied by
-O0
only.-fomit-yields
Omit heap checks when no allocation is being performed.
-foptimal-applicative-do
Use a slower but better algorithm for ApplicativeDo
-fpedantic-bottoms
Make 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.-fpolymorphic-specialisation
Allow specialisation to abstract over free type variables
-fregs-graph
Use the graph colouring register allocator for register allocation in the native code generator.
-fregs-iterative
Use the iterative coalescing graph colouring register allocator in the native code generator.
-fsimpl-tick-factor=⟨n⟩
default: 100. Set the percentage factor for simplifier ticks.
-fsimplifier-phases=⟨n⟩
default: 2. Set the number of phases for the simplifier. Ignored with
-O0
.-fsolve-constant-dicts
When solving constraints, try to eagerly solve super classes using available dictionaries. Implied by
-O
.-fspec-constr
Turn on the SpecConstr transformation. Implied by
-O2
.-fspec-constr-count=⟨n⟩
default: 3.* Set to ⟨n⟩ the maximum number of specialisations that will be created for any one function by the SpecConstr transformation.
-fspec-constr-keen
Specialize a call with an explicit constructor argument, even if the argument is not scrutinised in the body of the function
-fspec-constr-threshold=⟨n⟩
default: 2000. Set the size threshold for the SpecConstr transformation to ⟨n⟩.
-fspecialise
Turn on specialisation of overloaded functions. Implied by
-O
.-fspecialise-aggressively
Turn on specialisation of overloaded functions regardless of size, if unfolding is available
-fspecialise-incoherents
Enable specialisation on incoherent instances
-fstatic-argument-transformation
Turn on the static argument transformation.
-fstg-cse
Enable common sub-expression elimination on the STG intermediate language. Implied by
-O
.-fstg-lift-lams
Enable late lambda lifting on the STG intermediate language. Implied by
-O2
.-fstg-lift-lams-known
Allow turning known into unknown calls while performing late lambda lifting.
-fstg-lift-lams-non-rec-args
Create top-level non-recursive functions with at most <n> parameters while performing late lambda lifting.
-fstg-lift-lams-rec-args
Create top-level recursive functions with at most <n> parameters while performing late lambda lifting.
-fstrictness
Turn on demand analysis. Implied by
-O
. Implies-fworker-wrapper
-fstrictness-before=⟨n⟩
Run an additional demand analysis before simplifier phase ⟨n⟩
-funbox-small-strict-fields
Flatten strict constructor fields with a pointer-sized representation. Implied by
-O
.-funbox-strict-fields
Flatten strict constructor fields
-funfolding-case-scaling=⟨n⟩
default: 30. Apply a penalty of (inlining_cost * 1/n) for each level of case nesting.
-funfolding-case-threshold=⟨n⟩
default: 2. Reduce inlining for cases nested deeper than n.
-funfolding-creation-threshold=⟨n⟩
default: 750. Tweak unfolding settings.
-funfolding-dict-discount=⟨n⟩
default: 30. Tweak unfolding settings.
-funfolding-fun-discount=⟨n⟩
default: 60. Tweak unfolding settings.
-funfolding-keeness-factor=⟨n⟩
This has been deprecated in GHC 9.0.1.
-funfolding-use-threshold=⟨n⟩
default: 80. Tweak unfolding settings.
-fworker-wrapper
Enable the worker/wrapper transformation. Implied by
-O
and by-fstrictness
.-fworker-wrapper-cbv
Enable w/w splits for wrappers whos sole purpose is evaluating arguments.
Optimization levels¶
Package options¶
-clear-package-db
Clear the package db stack.
-distrust ⟨pkg⟩
Expose package ⟨pkg⟩ and set it to be distrusted. See Safe Haskell.
-distrust-all-packages
Distrust all packages by default. See Safe Haskell.
-fpackage-trust
Enable Safe Haskell trusted package requirement for trustworthy modules.
-global-package-db
Add the global package db to the stack.
-hide-all-packages
Hide all packages by default
-hide-package ⟨pkg⟩
Hide package ⟨pkg⟩
-ignore-package ⟨pkg⟩
Ignore package ⟨pkg⟩
-no-auto-link-packages
Don't automatically link in the base and rts packages.
-no-global-package-db
Remove the global package db from the stack.
-no-user-package-db
Remove the user's package db from the stack.
-package ⟨pkg⟩
Expose package ⟨pkg⟩
-package-db ⟨file⟩
Add ⟨file⟩ to the package db stack.
-package-env ⟨file⟩|⟨name⟩
Use the specified package environment.
-package-id ⟨unit-id⟩
Expose package by id ⟨unit-id⟩
-this-unit-id ⟨unit-id⟩
Compile to be part of unit (i.e. package) ⟨unit-id⟩
-trust ⟨pkg⟩
Expose package ⟨pkg⟩ and set it to be trusted. See Safe Haskell.
-user-package-db
Add the user's package db to the stack.
Phases of compilation¶
--merge-objs
Merge a set of objects into a GHCi library.
-C
Stop after generating C (
.hc
file)-c
Stop after generating object (
.o
) file-E
Stop after preprocessing (
.hspp
file)-F
Enable the use of a pre-processor (set with
-pgmF ⟨cmd⟩
)-S
Stop after generating assembly (
.s
file)-x ⟨suffix⟩
Override default behaviour for source files
Overriding external programs¶
-pgma ⟨cmd⟩
Use ⟨cmd⟩ as the assembler
-pgmc ⟨cmd⟩
Use ⟨cmd⟩ as the C compiler
-pgmcxx ⟨cmd⟩
Use ⟨cmd⟩ as the C++ compiler
-pgmF ⟨cmd⟩
Use ⟨cmd⟩ as the pre-processor (with
-F
only)-pgmi ⟨cmd⟩
Use ⟨cmd⟩ as the external interpreter command.
-pgminstall_name_tool ⟨cmd⟩
Use ⟨cmd⟩ as the program to inject
runpath
into mach-o dylibs on macOS-pgmL ⟨cmd⟩
Use ⟨cmd⟩ as the literate pre-processor
-pgml ⟨cmd⟩
Use ⟨cmd⟩ as the linker
-pgmlas ⟨cmd⟩
Use ⟨cmd⟩ as the LLVM assembler
-pgmlc ⟨cmd⟩
Use ⟨cmd⟩ as the LLVM compiler
-pgmlm ⟨cmd⟩
Use ⟨cmd⟩ as the linker when merging object files
-pgmlo ⟨cmd⟩
Use ⟨cmd⟩ as the LLVM optimiser
-pgmotool ⟨cmd⟩
Use ⟨cmd⟩ as the program to inspect mach-o dylibs on macOS
-pgmP ⟨cmd⟩
Use ⟨cmd⟩ as the C pre-processor (with
-cpp
only)-pgms ⟨cmd⟩
Use ⟨cmd⟩ as the splitter
-pgmwindres ⟨cmd⟩
Use ⟨cmd⟩ as the program for embedding manifests on Windows.
Phase-specific options¶
-opta ⟨option⟩
pass ⟨option⟩ to the assembler
-optc ⟨option⟩
pass ⟨option⟩ to the C compiler
-optcxx ⟨option⟩
pass ⟨option⟩ to the C++ compiler
-optF ⟨option⟩
pass ⟨option⟩ to the custom pre-processor
-opti ⟨option⟩
pass ⟨option⟩ to the interpreter sub-process.
-optL ⟨option⟩
pass ⟨option⟩ to the literate pre-processor
-optl ⟨option⟩
pass ⟨option⟩ to the linker
-optlas ⟨option⟩
pass ⟨option⟩ to the LLVM assembler
-optlc ⟨option⟩
pass ⟨option⟩ to the LLVM compiler
-optlm ⟨option⟩
pass ⟨option⟩ to the linker when merging object files.
-optlo ⟨option⟩
pass ⟨option⟩ to the LLVM optimiser
-optP ⟨option⟩
pass ⟨option⟩ to cpp (with
-cpp
only)-optwindres ⟨option⟩
pass ⟨option⟩ to
windres
.-pgmc-supports-no-pie
(deprecated) Indicate that the linker supports
-no-pie
-pgml-supports-no-pie
Indicate that the linker supports
-no-pie
Platform-specific options¶
-mavx
(x86 only) Enable support for AVX SIMD extensions
-mavx2
(x86 only) Enable support for AVX2 SIMD extensions
-mavx512cd
(x86 only) Enable support for AVX512-CD SIMD extensions
-mavx512er
(x86 only) Enable support for AVX512-ER SIMD extensions
-mavx512f
(x86 only) Enable support for AVX512-F SIMD extensions
-mavx512pf
(x86 only) Enable support for AVX512-PF SIMD extensions
-mbmi
(x86 only) Use BMI1 for bit manipulation operations
-mbmi2
(x86 only) Use BMI2 for bit manipulation operations
-mfma
Use native FMA instructions for fused multiply-add floating-point operations
-msse
(x86 only) Use SSE for floating-point operations
-msse2
(x86 only) Use SSE2 for floating-point operations
-msse3
(x86 only) Use SSE3 for floating-point operations
-msse4
(x86 only) Use SSE4 for floating-point operations
-msse4.2
(x86 only) Use SSE4.2 for floating-point operations
Compiler plugins¶
-fclear-plugins
Clear the list of active plugins
-fplugin-library=⟨file-path⟩;⟨unit-id⟩;⟨module⟩;⟨args⟩
Load a pre-compiled static plugin from an external library
-fplugin-opt=⟨module⟩:⟨args⟩
Give arguments to a plugin module; module must be specified with
-fplugin=⟨module⟩
-fplugin-trustworthy
Trust the used plugins and no longer mark the compiled module as unsafe
-fplugin=⟨module⟩
Load a plugin exported by a given module
-hide-all-plugin-packages
Hide all packages for plugins by default
-plugin-package ⟨pkg⟩
Expose ⟨pkg⟩ for plugins
-plugin-package-id ⟨pkg-id⟩
Expose ⟨pkg-id⟩ for plugins
Profiling¶
-auto
(deprecated) Alias for
-fprof-auto-exported
-auto-all
(deprecated) Alias for
-fprof-auto
-caf-all
(deprecated) Alias for
-fprof-cafs
-fno-prof-count-entries
Do not collect entry counts
-fprof-auto
Auto-add
SCC
\ s to all bindings not marked INLINE-fprof-auto-calls
Auto-add
SCC
\ s to all call sites-fprof-auto-exported
Auto-add
SCC
\ s to all exported bindings not markedINLINE
-fprof-auto-top
Auto-add
SCC
\ s to all top-level bindings not marked INLINE-fprof-cafs
Auto-add
SCC
\ s to all CAFs-fprof-callers=⟨name⟩
Auto-add
SCC
\ s to all call-sites of the named function.-fprof-late
Auto-add
SCC
\ s to all top level bindings after the core pipeline has run.-fprof-late-inline
Auto-add
SCC
\ s to all top level bindings after the optimizer has run and retain them when inlining.-fprof-late-overloaded
Auto-add
SCC
\ s to all top level overloaded bindings after the core pipeline has run.-fprof-late-overloaded-calls
Auto-add
SCC
\ s to all call sites that include dictionary arguments after the core pipeline has run.-fprof-manual
Process manual
SCC
annotations.-no-auto
(deprecated) Alias for
-fno-prof-auto
-no-auto-all
(deprecated) Alias for
-fno-prof-auto
-no-caf-all
(deprecated) Alias for
-fno-prof-cafs
-prof
Turn on profiling
-ticky
Turn on ticky-ticky profiling
-ticky-allocd
Track the number of times each closure type is allocated.
-ticky-ap-thunk
Don't use standard AP thunks on order to get more reliable entry counters.
-ticky-dyn-thunk
Track allocations of dynamic thunks
-ticky-LNE
Treat join point binders similar to thunks/functions.
-ticky-tag-checks
Emit dummy ticky counters to record how many tag-inference checks tag inference avoided.
Program coverage¶
-fhpc
Turn on Haskell program coverage instrumentation
-hpcdir⟨dir⟩
Set the directory where GHC places
.mix
files.
Recompilation checking¶
-exclude-module=⟨file⟩
Regard
⟨file⟩
as "stable"; i.e., exclude it from having dependencies on it.-fforce-recomp
Turn off recompilation checking. This is implied by any
-ddump-X
option when compiling a single file (i.e. when using-c
).-fignore-hpc-changes
Do not recompile modules just to match changes to HPC flags. This is especially useful for avoiding recompilation when using GHCi, and is enabled by default for GHCi.
-fignore-optim-changes
Do not recompile modules just to match changes to optimisation flags. This is especially useful for avoiding recompilation when using GHCi, and is enabled by default for GHCi.
-include-cpp-deps
Include preprocessor dependencies
-include-pkg-deps
Regard modules imported from packages as unstable
Redirecting output¶
-dep-makefile ⟨file⟩
Use ⟨file⟩ as the makefile
-dep-suffix ⟨suffix⟩
Make dependencies that declare that files with suffix
.⟨suf⟩⟨osuf⟩
depend on interface files with suffix.⟨suf⟩hi
-dumpdir ⟨dir⟩
redirect dump files
-dynhisuf ⟨suffix⟩
set the suffix to use for dynamic interface files
-dyno ⟨file⟩
set dynamic output filename
-dynohi ⟨file⟩
set the filename in which to put the dynamic interface
-dynosuf ⟨suffix⟩
set the dynamic output file suffix
-hcsuf ⟨suffix⟩
set the suffix to use for intermediate C files
-hidir ⟨dir⟩
set directory for interface files
-hiedir ⟨dir⟩
set directory for extended interface files
-hiesuf ⟨suffix⟩
set the suffix to use for extended interface files
-hisuf ⟨suffix⟩
set the suffix to use for interface files
-o ⟨file⟩
set output filename
-odir ⟨dir⟩
set directory for object files
-ohi ⟨file⟩
set the filename in which to put the interface
-osuf ⟨suffix⟩
set the output file suffix
-outputdir ⟨dir⟩
set output directory
-stubdir ⟨dir⟩
redirect FFI stub files
Temporary files¶
-tmpdir ⟨dir⟩
set the directory for temporary files
Verbosity options¶
-fabstract-refinement-hole-fits
default: off. Toggles whether refinements where one or more of the holes are abstract are reported.
-fdefer-diagnostics
Defer and group diagnostic messages by severity
-fdiagnostics-as-json
Output diagnostics in Json format specified by JSON schema
-fdiagnostics-color=⟨always|auto|never⟩
Use colors in error messages
-fdiagnostics-show-caret
Whether to show snippets of original source code
-ferror-spans
Output full span in error messages
-fhide-source-paths
hide module source and object paths
-fkeep-going
Continue compilation as far as possible on errors
-fmax-refinement-hole-fits=⟨n⟩
default: 6. Set the maximum number of refinement hole fits for typed holes to display in type error messages.
-fmax-relevant-binds=⟨n⟩
default: 6. Set the maximum number of bindings to display in type error messages.
-fmax-valid-hole-fits=⟨n⟩
default: 6. Set the maximum number of valid hole fits for typed holes to display in type error messages.
-fno-show-valid-hole-fits
Disables showing a list of valid hole fits for typed holes in type error messages.
-fno-sort-valid-hole-fits
Disables the sorting of the list of valid hole fits for typed holes in type error messages.
-fprint-axiom-incomps
Display equation incompatibilities in closed type families
-fprint-equality-relations
Distinguish between equality relations when printing
-fprint-error-index-links=⟨always|auto|never⟩
Whether to emit diagnostic codes as ANSI hyperlinks to the Haskell Error Index.
-fprint-expanded-synonyms
In type errors, also print type-synonym-expanded types.
-fprint-explicit-coercions
Print coercions in types
-fprint-explicit-foralls
Print explicit
forall
quantification in types. See alsoExplicitForAll
-fprint-explicit-kinds
Print explicit kind foralls and kind arguments in types. See also
KindSignatures
-fprint-explicit-runtime-reps
Print
RuntimeRep
andLevity
variables in types which are runtime-representation polymorphic.-fprint-potential-instances
display all available instances in type error messages
-fprint-redundant-promotion-ticks
Print redundant
DataKinds
promotion ticks-fprint-typechecker-elaboration
Print extra information from typechecker.
-fprint-unicode-syntax
Use unicode syntax when printing expressions, types and kinds. See also
UnicodeSyntax
-frefinement-level-hole-fits=⟨n⟩
default: off. Sets the level of refinement of the refinement hole fits, where level
n
means that hole fits of up ton
holes will be considered.-freverse-errors
Output errors in reverse order
-fshow-docs-of-hole-fits
Toggles whether to show the documentation of the valid hole fits in the output.
-fshow-error-context
Whether to show textual information about error context
-fshow-hole-constraints
Show constraints when reporting typed holes.
-fshow-hole-matches-of-hole-fits
Toggles whether to show the type of the additional holes in refinement hole fits.
-fshow-provenance-of-hole-fits
Toggles whether to show the provenance of the valid hole fits in the output.
-fshow-type-app-of-hole-fits
Toggles whether to show the type application of the valid hole fits in the output.
-fshow-type-app-vars-of-hole-fits
Toggles whether to show what type each quantified variable takes in a valid hole fit.
-fshow-type-of-hole-fits
Toggles whether to show the type of the valid hole fits in the output.
-fsort-by-size-hole-fits
Sort valid hole fits by size.
-fsort-by-subsumption-hole-fits
Sort valid hole fits by subsumption.
-funclutter-valid-hole-fits
Unclutter the list of valid hole fits by not showing provenance nor type applications of suggestions.
-Rghc-timing
Summarise timing stats for GHC (same as
+RTS -tstderr
).-v
verbose mode (equivalent to
-v3
)-v⟨n⟩
set verbosity level
Warnings¶
-fenable-th-splice-warnings
Generate warnings for Template Haskell splices
-fhelpful-errors
Make suggestions for mis-spelled names.
-fmax-pmcheck-models=⟨n⟩
soft limit on the number of parallel models the pattern match checker should check a pattern match clause against
-fshow-warning-groups
show which group an emitted warning belongs to.
-fvia-C
use the C code generator
-W
enable normal warnings
-w
disable all warnings
-Wall
enable almost all warnings (details in Warnings and sanity-checking)
-Wall-missed-specialisations
warn when specialisation of any overloaded function fails.
-Wall-missed-specializations
alias for
-Wall-missed-specialisations
-Wambiguous-fields
warn about ambiguous field selectors or updates
-Wauto-orphans
(deprecated) Does nothing
-Wbadly-staged-types
warn when type binding is used at the wrong TH stage.
-Wcompat
enable future compatibility warnings (details in Warnings and sanity-checking)
-Wcompat-unqualified-imports
Report unqualified imports of core libraries which are expected to cause compatibility problems in future releases.
-Wcpp-undef
warn on uses of the #if directive on undefined identifiers
-Wdata-kinds-tc
warn when an illegal use of a type or kind without
DataKinds
is caught by the typechecker-Wdefault
enable default flags
-Wdefaulted-exception-context
warn when an Control.Exception.Context.ExceptionContext implicit parameter is defaulted to Control.Exception.Context.emptyExceptionContext.
-Wdeferred-out-of-scope-variables
Report warnings when variable out-of-scope errors are deferred until runtime. See
-fdefer-out-of-scope-variables
.-Wdeferred-type-errors
Report warnings when deferred type errors are enabled. This option is enabled by default. See
-fdefer-type-errors
.-Wdeprecated-flags
warn about uses of commandline flags that are deprecated
-Wdeprecated-type-abstractions
warn when type abstractions in constructor patterns are used without enabling
TypeApplications
-Wdeprecations
warn about uses of functions & types that have DEPRECATED pragmas, or WARNING pragmas with the
deprecated
category.-Wderiving-defaults
warn about default deriving when using both
DeriveAnyClass
andGeneralizedNewtypeDeriving
-Wderiving-typeable
warn when Typeable is derived
-Wdodgy-exports
warn about dodgy exports
-Wdodgy-foreign-imports
warn about dodgy foreign imports
-Wdodgy-imports
warn about dodgy imports
-Wduplicate-constraints
warn when a constraint appears duplicated in a type signature
-Wduplicate-exports
warn when an entity is exported multiple times
-Wempty-enumerations
warn about enumerations that are empty
-Werror
make warnings fatal
-Weverything
enable all warnings supported by GHC
-Wextended-warnings
warn about uses of functions & types that have WARNING or DEPRECATED pragmas, across all categories
-Wextra
alias for
-W
-Wforall-identifier
(deprecated) Does nothing
-Wgadt-mono-local-binds
warn when pattern matching on a GADT without MonoLocalBinds
-Whi-shadowing
(deprecated) warn when a
.hi
file in the current directory shadows a library-Widentities
warn about uses of Prelude numeric conversions that are probably the identity (and hence could be omitted)
-Wimplicit-kind-vars
(deprecated) warn when kind variables are implicitly quantified over.
-Wimplicit-lift
warn about implicit
lift
in Template Haskell quotes-Wimplicit-prelude
warn when the Prelude is implicitly imported
-Wimplicit-rhs-quantification
warn when type variables on the RHS of a type synonym are implicitly quantified
-Winaccessible-code
warn about inaccessible code
-Wincomplete-export-warnings
warn when some but not all of exports for a name are warned about
-Wincomplete-patterns
warn when a pattern match could fail
-Wincomplete-record-selectors
warn when a record selector application could fail
-Wincomplete-record-updates
warn when a record update could fail
-Wincomplete-uni-patterns
warn when a pattern match in a lambda expression, pattern binding or a lazy pattern could fail
-Winconsistent-flags
warn when command line options are inconsistent in some way.
-Winferred-safe-imports
warn when an explicitly Safe Haskell module imports a Safe-Inferred one
-Winline-rule-shadowing
Warn if a rewrite RULE might fail to fire because the function might be inlined before the rule has a chance to fire. See How rules interact with INLINE/NOINLINE pragmas.
-Winvalid-haddock
warn when a Haddock comment occurs in an invalid position
-Wloopy-superclass-solve
(deprecated) warn when creating potentially-loopy superclass constraint evidence
-Wmisplaced-pragmas
warn about uses of file header pragmas in the module body
-Wmissed-extra-shared-lib
Warn when GHCi can't load a shared lib.
-Wmissed-specialisations
warn when specialisation of an imported, overloaded function fails.
-Wmissed-specializations
alias for
-Wmissed-specialisations
-Wmissing-deriving-strategies
warn when a deriving clause is missing a deriving strategy
-Wmissing-export-lists
warn when a module declaration does not explicitly list all exports
-Wmissing-exported-pattern-synonym-signatures
warn about pattern synonyms without signatures, only if they are exported
-Wmissing-exported-signatures
warn about top-level functions without signatures, only if they are exported
-Wmissing-exported-sigs
(deprecated) warn about top-level functions without signatures, only if they are exported. takes precedence over -Wmissing-signatures
-Wmissing-fields
warn when fields of a record are uninitialised
-Wmissing-home-modules
warn when encountering a home module imported, but not listed on the command line. Useful for cabal to ensure GHC won't pick up modules, not listed neither in
exposed-modules
, nor inother-modules
.-Wmissing-import-lists
warn when an import declaration does not explicitly list all the names brought into scope
-Wmissing-kind-signatures
warn when type declarations don't have kind signatures nor CUSKs
-Wmissing-local-signatures
warn about polymorphic local bindings without signatures
-Wmissing-local-sigs
(deprecated) warn about polymorphic local bindings without signatures
-Wmissing-methods
warn when class methods are undefined
-Wmissing-monadfail-instances
(deprecated) Warn when a failable pattern is used in a do-block that does not have a
MonadFail
instance.-Wmissing-pattern-synonym-signatures
warn when pattern synonyms do not have type signatures
-Wmissing-poly-kind-signatures
warn when inferred polykinded type or class declaration don't have kind signatures nor CUSKs
-Wmissing-role-annotations
warn when type declarations don't have role annotations
-Wmissing-safe-haskell-mode
warn when the Safe Haskell mode is not explicitly specified.
-Wmissing-signatures
warn about top-level functions without signatures
-Wmissing-space-after-bang
(deprecated) Does nothing
-Wmonomorphism-restriction
warn when the Monomorphism Restriction is applied
-Wname-shadowing
warn when names are shadowed
-Wnoncanonical-monad-instances
warn when
Applicative
orMonad
instances have noncanonical definitions ofreturn
,pure
,(>>)
, or(*>)
. See flag description in Warnings and sanity-checking for more details.-Wnoncanonical-monadfail-instances
(deprecated) warn when
Monad
orMonadFail
instances have noncanonical definitions offail
.-Wnoncanonical-monoid-instances
warn when
Semigroup
orMonoid
instances have noncanonical definitions of(<>)
ormappend
. See flag description in Warnings and sanity-checking for more details.-Wnot
(deprecated) Alias for
-w
-Woperator-whitespace
warn on prefix, suffix, and tight infix uses of infix operators
-Woperator-whitespace-ext-conflict
warn on uses of infix operators that would be parsed differently were a particular GHC extension enabled
-Worphans
warn when the module contains orphan instance declarations or rewrite rules
-Woverflowed-literals
warn about literals that will overflow their type
-Woverlapping-patterns
warn about overlapping patterns
-Wpartial-fields
warn when defining a partial record field.
-Wpartial-type-signatures
warn about holes in partial type signatures when
PartialTypeSignatures
is enabled. Not applicable whenPartialTypeSignatures
is not enabled, in which case errors are generated for such holes.-Wprepositive-qualified-module
Report imports with a leading/prepositive "qualified"
-Wredundant-bang-patterns
Warn about redundant bang patterns.
-Wredundant-constraints
Have the compiler warn about redundant constraints in type signatures.
-Wredundant-record-wildcards
Warn about record wildcard matches when the wildcard binds no patterns.
-Wredundant-strictness-flags
Warn about redundant strictness flags.
-Wsafe
warn if the module being compiled is regarded to be safe.
-Wsemigroup
(deprecated) Warn when a
Monoid
is notSemigroup
, and on non-Semigroup
definitions of(<>)
-Wsimplifiable-class-constraints
Warn about class constraints in a type signature that can be simplified using a top-level instance declaration.
-Wstar-binder
warn about binding the
(*)
type operator despiteStarIsType
-Wstar-is-type
warn when
*
is used to meanData.Kind.Type
-Wtabs
warn if there are tabs in the source file
-Wterm-variable-capture
warn when an implicitly quantified type variable captures a term's name
-Wtrustworthy-safe
warn if the module being compiled is marked as
Trustworthy
but it could instead be marked asSafe
, a more informative bound.-Wtype-defaults
warn when defaulting happens
-Wtype-equality-out-of-scope
warn when type equality
a ~ b
is used despite being out of scope-Wtype-equality-requires-operators
warn when type equality
a ~ b
is used despite being out of scope-Wtyped-holes
Report warnings when typed hole errors are deferred until runtime. See
-fdefer-typed-holes
.-Wunbanged-strict-patterns
warn on pattern bind of unlifted variable that is neither bare nor banged
-Wunicode-bidirectional-format-characters
warn about the usage of unicode bidirectional layout override characters
-Wunrecognised-pragmas
warn about uses of pragmas that GHC doesn't recognise
-Wunrecognised-warning-flags
throw a warning when an unrecognised
-W...
flag is encountered on the command line.-Wunsafe
warn if the module being compiled is regarded to be unsafe. See Safe Haskell
-Wunsupported-calling-conventions
warn about use of an unsupported calling convention
-Wunsupported-llvm-version
Warn when using
-fllvm
with an unsupported version of LLVM.-Wunticked-promoted-constructors
warn if promoted constructors are not ticked
-Wunused-binds
warn about bindings that are unused. Alias for
-Wunused-top-binds
,-Wunused-local-binds
and-Wunused-pattern-binds
-Wunused-do-bind
warn about do bindings that appear to throw away values of types other than
()
-Wunused-foralls
warn about type variables in user-written
forall
\s that are unused-Wunused-imports
warn about unnecessary imports
-Wunused-local-binds
warn about local bindings that are unused
-Wunused-matches
warn about variables in patterns that aren't used
-Wunused-packages
warn when package is requested on command line, but not needed.
-Wunused-pattern-binds
warn about pattern match bindings that are unused
-Wunused-record-wildcards
Warn about record wildcard matches when none of the bound variables are used.
-Wunused-top-binds
warn about top-level bindings that are unused
-Wunused-type-patterns
warn about unused type variables which arise from patterns in in type family and data family instances
-Wwarn
make warnings non-fatal
-Wwarnings-deprecations
warn about uses of functions & types that have DEPRECATED pragmas, or WARNING pragmas with the
deprecated
category. Alias for-Wdeprecations
.-Wwrong-do-bind
warn about do bindings that appear to throw away monadic values that you should have bound instead
-Wx-⟨category⟩
warn about uses of functions & types that have WARNING pragmas with the given category
Copyright¶
Copyright 2015. The University Court of the University of Glasgow. All rights reserved.
See also¶
https://www.haskell.org/ghc the GHC homepage