summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSimon Peyton Jones <simonpj@microsoft.com>2012-01-13 15:51:44 +0000
committerSimon Peyton Jones <simonpj@microsoft.com>2012-01-13 15:51:44 +0000
commitc96022cbfae44ea9180b78e3c37467613ac98cec (patch)
treeefac74d3d2d1e49a58180629b835f52f643bb3a4
parenta30c2df58c319c99550c9c66827c1a984622866a (diff)
parentcea630797e9cb3a2bcd424a18fa29d4373092e86 (diff)
downloadhaskell-c96022cbfae44ea9180b78e3c37467613ac98cec.tar.gz
Merge branch 'master' of http://darcs.haskell.org/ghc
-rw-r--r--.gitignore3
-rw-r--r--compiler/llvmGen/LlvmCodeGen.hs2
-rw-r--r--compiler/llvmGen/LlvmCodeGen/Base.hs16
-rw-r--r--compiler/llvmGen/LlvmCodeGen/CodeGen.hs31
-rw-r--r--compiler/llvmGen/LlvmCodeGen/Regs.hs13
-rw-r--r--compiler/main/DriverPipeline.hs27
-rw-r--r--compiler/main/DynFlags.hs6
-rw-r--r--docs/users_guide/flags.xml5610
-rw-r--r--ghc.mk107
9 files changed, 2950 insertions, 2865 deletions
diff --git a/.gitignore b/.gitignore
index 2bfec1656b..4897988477 100644
--- a/.gitignore
+++ b/.gitignore
@@ -125,6 +125,8 @@ _darcs/
/docs/users_guide/ug-book.xml
/docs/users_guide/ug-ent.xml
/docs/users_guide/users_guide.xml
+/docs/users_guide/users_guide.pdf
+/docs/users_guide/users_guide.ps
/docs/users_guide/users_guide/
/docs/users_guide/what_glasgow_exts_does.gen.xml
/driver/ghc/dist/
@@ -182,6 +184,7 @@ _darcs/
/libraries/time/
/libraries/*/dist-boot/
/libraries/*/dist-install/
+/libraries/dist-haddock/
/mk/are-validating.mk
/mk/build.mk
/mk/config.h
diff --git a/compiler/llvmGen/LlvmCodeGen.hs b/compiler/llvmGen/LlvmCodeGen.hs
index f239ee50cf..00f4292f63 100644
--- a/compiler/llvmGen/LlvmCodeGen.hs
+++ b/compiler/llvmGen/LlvmCodeGen.hs
@@ -37,7 +37,7 @@ llvmCodeGen :: DynFlags -> Handle -> UniqSupply -> [RawCmmGroup] -> IO ()
llvmCodeGen dflags h us cmms
= let cmm = concat cmms
(cdata,env) = {-# SCC "llvm_split" #-}
- foldr split ([],initLlvmEnv (targetPlatform dflags)) cmm
+ foldr split ([], initLlvmEnv dflags) cmm
split (CmmData s d' ) (d,e) = ((s,d'):d,e)
split (CmmProc i l _) (d,e) =
let lbl = strCLabel_llvm env $ case i of
diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs
index a896cdd482..9bdb115505 100644
--- a/compiler/llvmGen/LlvmCodeGen/Base.hs
+++ b/compiler/llvmGen/LlvmCodeGen/Base.hs
@@ -13,7 +13,7 @@ module LlvmCodeGen.Base (
LlvmEnv, initLlvmEnv, clearVars, varLookup, varInsert,
funLookup, funInsert, getLlvmVer, setLlvmVer, getLlvmPlatform,
- ghcInternalFunctions,
+ getDflags, ghcInternalFunctions,
cmmToLlvmType, widthToLlvmFloat, widthToLlvmInt, llvmFunTy,
llvmFunSig, llvmStdFunAttrs, llvmFunAlign, llvmInfAlign,
@@ -32,6 +32,7 @@ import CLabel
import CgUtils ( activeStgRegs )
import Config
import Constants
+import DynFlags
import FastString
import OldCmm
import qualified Outputable as Outp
@@ -150,12 +151,13 @@ defaultLlvmVersion = 28
--
-- two maps, one for functions and one for local vars.
-newtype LlvmEnv = LlvmEnv (LlvmEnvMap, LlvmEnvMap, LlvmVersion, Platform)
+newtype LlvmEnv = LlvmEnv (LlvmEnvMap, LlvmEnvMap, LlvmVersion, DynFlags)
+
type LlvmEnvMap = UniqFM LlvmType
-- | Get initial Llvm environment.
-initLlvmEnv :: Platform -> LlvmEnv
-initLlvmEnv platform = LlvmEnv (initFuncs, emptyUFM, defaultLlvmVersion, platform)
+initLlvmEnv :: DynFlags -> LlvmEnv
+initLlvmEnv dflags = LlvmEnv (initFuncs, emptyUFM, defaultLlvmVersion, dflags)
where initFuncs = listToUFM $ [ (n, LMFunction ty) | (n, ty) <- ghcInternalFunctions ]
-- | Here we pre-initialise some functions that are used internally by GHC
@@ -211,7 +213,11 @@ setLlvmVer n (LlvmEnv (e1, e2, _, p)) = LlvmEnv (e1, e2, n, p)
-- | Get the platform we are generating code for
getLlvmPlatform :: LlvmEnv -> Platform
-getLlvmPlatform (LlvmEnv (_, _, _, p)) = p
+getLlvmPlatform (LlvmEnv (_, _, _, d)) = targetPlatform d
+
+-- | Get the DynFlags for this compilation pass
+getDflags :: LlvmEnv -> DynFlags
+getDflags (LlvmEnv (_, _, _, d)) = d
-- ----------------------------------------------------------------------------
-- * Label handling
diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
index 4309dcdae1..d5037828c7 100644
--- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
+++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
@@ -16,13 +16,14 @@ import CgUtils ( activeStgRegs, callerSaves )
import CLabel
import OldCmm
import qualified OldPprCmm as PprCmm
-import OrdList
+import DynFlags
import FastString
import ForeignCall
import Outputable hiding ( panic, pprPanic )
import qualified Outputable
import Platform
+import OrdList
import UniqSupply
import Unique
import Util
@@ -475,7 +476,7 @@ genJump :: LlvmEnv -> CmmExpr -> Maybe [GlobalReg] -> UniqSM StmtData
-- Call to known function
genJump env (CmmLit (CmmLabel lbl)) live = do
(env', vf, stmts, top) <- getHsFunc env lbl
- (stgRegs, stgStmts) <- funEpilogue live
+ (stgRegs, stgStmts) <- funEpilogue env live
let s1 = Expr $ Call TailCall vf stgRegs llvmStdFunAttrs
let s2 = Return Nothing
return (env', stmts `appOL` stgStmts `snocOL` s1 `snocOL` s2, top)
@@ -494,7 +495,7 @@ genJump env expr live = do
++ show (ty) ++ ")"
(v1, s1) <- doExpr (pLift fty) $ Cast cast vf (pLift fty)
- (stgRegs, stgStmts) <- funEpilogue live
+ (stgRegs, stgStmts) <- funEpilogue env live
let s2 = Expr $ Call TailCall v1 stgRegs llvmStdFunAttrs
let s3 = Return Nothing
return (env', stmts `snocOL` s1 `appOL` stgStmts `snocOL` s2 `snocOL` s3,
@@ -550,7 +551,7 @@ genStore env addr@(CmmMachOp (MO_Sub _) [
= genStore_fast env addr r (negate $ fromInteger n) val
-- generic case
-genStore env addr val = genStore_slow env addr val [top]
+genStore env addr val = genStore_slow env addr val [other]
-- | CmmStore operation
-- This is a special case for storing to a global register pointer
@@ -1032,7 +1033,7 @@ genLoad env e@(CmmMachOp (MO_Sub _) [
= genLoad_fast env e r (negate $ fromInteger n) ty
-- generic case
-genLoad env e ty = genLoad_slow env e ty [top]
+genLoad env e ty = genLoad_slow env e ty [other]
-- | Handle CmmLoad expression.
-- This is a special case for loading from a global register pointer
@@ -1200,29 +1201,33 @@ funPrologue = concat $ map getReg activeStgRegs
-- | Function epilogue. Load STG variables to use as argument for call.
-funEpilogue :: Maybe [GlobalReg] -> UniqSM ([LlvmVar], LlvmStatements)
-funEpilogue Nothing = do
+-- STG Liveness optimisation done here.
+funEpilogue :: LlvmEnv -> Maybe [GlobalReg] -> UniqSM ([LlvmVar], LlvmStatements)
+
+-- Have information and liveness optimisation is enabled
+funEpilogue env (Just live) | dopt Opt_RegLiveness (getDflags env) = do
loads <- mapM loadExpr activeStgRegs
let (vars, stmts) = unzip loads
return (vars, concatOL stmts)
where
- loadExpr r = do
+ loadExpr r | r `elem` alwaysLive || r `elem` live = do
let reg = lmGlobalRegVar r
(v,s) <- doExpr (pLower $ getVarType reg) $ Load reg
return (v, unitOL s)
+ loadExpr r = do
+ let ty = (pLower . getVarType $ lmGlobalRegVar r)
+ return (LMLitVar $ LMUndefLit ty, unitOL Nop)
-funEpilogue (Just live) = do
+-- don't do liveness optimisation
+funEpilogue _ _ = do
loads <- mapM loadExpr activeStgRegs
let (vars, stmts) = unzip loads
return (vars, concatOL stmts)
where
- loadExpr r | r `elem` alwaysLive || r `elem` live = do
+ loadExpr r = do
let reg = lmGlobalRegVar r
(v,s) <- doExpr (pLower $ getVarType reg) $ Load reg
return (v, unitOL s)
- loadExpr r = do
- let ty = (pLower . getVarType $ lmGlobalRegVar r)
- return (LMLitVar $ LMUndefLit ty, unitOL Nop)
-- | A serries of statements to trash all the STG registers.
diff --git a/compiler/llvmGen/LlvmCodeGen/Regs.hs b/compiler/llvmGen/LlvmCodeGen/Regs.hs
index 55b2e0db80..b7ff9f008e 100644
--- a/compiler/llvmGen/LlvmCodeGen/Regs.hs
+++ b/compiler/llvmGen/LlvmCodeGen/Regs.hs
@@ -4,7 +4,7 @@
module LlvmCodeGen.Regs (
lmGlobalRegArg, lmGlobalRegVar, alwaysLive,
- stgTBAA, top, base, stack, heap, rx, tbaa, getTBAA
+ stgTBAA, top, base, stack, heap, rx, other, tbaa, getTBAA
) where
#include "HsVersions.h"
@@ -70,23 +70,30 @@ stgTBAA
, MetaUnamed heapN [MetaStr (fsLit "heap"), MetaNode topN]
, MetaUnamed rxN [MetaStr (fsLit "rx"), MetaNode heapN]
, MetaUnamed baseN [MetaStr (fsLit "base"), MetaNode topN]
+ -- FIX: Not 100% sure about 'others' place. Might need to be under 'heap'.
+ -- OR I think the big thing is Sp is never aliased, so might want
+ -- to change the hieracy to have Sp on its own branch that is never
+ -- aliased (e.g never use top as a TBAA node).
+ , MetaUnamed otherN [MetaStr (fsLit "other"), MetaNode topN]
]
-- | Id values
-topN, stackN, heapN, rxN, baseN :: LlvmMetaUnamed
+topN, stackN, heapN, rxN, baseN, otherN:: LlvmMetaUnamed
topN = LMMetaUnamed 0
stackN = LMMetaUnamed 1
heapN = LMMetaUnamed 2
rxN = LMMetaUnamed 3
baseN = LMMetaUnamed 4
+otherN = LMMetaUnamed 5
-- | The various TBAA types
-top, heap, stack, rx, base :: MetaData
+top, heap, stack, rx, base, other :: MetaData
top = (tbaa, topN)
heap = (tbaa, heapN)
stack = (tbaa, stackN)
rx = (tbaa, rxN)
base = (tbaa, baseN)
+other = (tbaa, otherN)
-- | The TBAA metadata identifier
tbaa :: LMString
diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs
index 0e8990777b..5c0d1b7d8c 100644
--- a/compiler/main/DriverPipeline.hs
+++ b/compiler/main/DriverPipeline.hs
@@ -1306,15 +1306,18 @@ runPhase SplitAs _input_fn dflags
runPhase LlvmOpt input_fn dflags
= do
- let lo_opts = getOpts dflags opt_lo
- let opt_lvl = max 0 (min 2 $ optLevel dflags)
- -- don't specify anything if user has specified commands. We do this for
- -- opt but not llc since opt is very specifically for optimisation passes
- -- only, so if the user is passing us extra options we assume they know
- -- what they are doing and don't get in the way.
- let optFlag = if null lo_opts
- then [SysTools.Option (llvmOpts !! opt_lvl)]
- else []
+ let lo_opts = getOpts dflags opt_lo
+ opt_lvl = max 0 (min 2 $ optLevel dflags)
+ -- don't specify anything if user has specified commands. We do this
+ -- for opt but not llc since opt is very specifically for optimisation
+ -- passes only, so if the user is passing us extra options we assume
+ -- they know what they are doing and don't get in the way.
+ optFlag = if null lo_opts
+ then [SysTools.Option (llvmOpts !! opt_lvl)]
+ else []
+ tbaa | dopt Opt_LlvmTBAA dflags = "--enable-tbaa=true"
+ | otherwise = "--enable-tbaa=false"
+
output_fn <- phaseOutputFilename LlvmLlc
@@ -1323,6 +1326,7 @@ runPhase LlvmOpt input_fn dflags
SysTools.Option "-o",
SysTools.FileOption "" output_fn]
++ optFlag
+ ++ [SysTools.Option tbaa]
++ map SysTools.Option lo_opts)
return (LlvmLlc, output_fn)
@@ -1341,6 +1345,8 @@ runPhase LlvmLlc input_fn dflags
rmodel | opt_PIC = "pic"
| not opt_Static = "dynamic-no-pic"
| otherwise = "static"
+ tbaa | dopt Opt_LlvmTBAA dflags = "--enable-tbaa=true"
+ | otherwise = "--enable-tbaa=false"
-- hidden debugging flag '-dno-llvm-mangler' to skip mangling
let next_phase = case dopt Opt_NoLlvmMangler dflags of
@@ -1356,6 +1362,7 @@ runPhase LlvmLlc input_fn dflags
SysTools.FileOption "" input_fn,
SysTools.Option "-o", SysTools.FileOption "" output_fn]
++ map SysTools.Option lc_opts
+ ++ [SysTools.Option tbaa]
++ map SysTools.Option fpOpts)
return (next_phase, output_fn)
@@ -1373,7 +1380,7 @@ runPhase LlvmLlc input_fn dflags
else if (elem VFPv3D16 ext)
then ["-mattr=+v7,+vfp3,+d16"]
else []
- _ -> []
+ _ -> []
-----------------------------------------------------------------------------
-- LlvmMangle phase
diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 48830e1b99..fb2e4e58e7 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -250,6 +250,8 @@ data DynFlag
| Opt_RegsGraph -- do graph coloring register allocation
| Opt_RegsIterative -- do iterative coalescing graph coloring register allocation
| Opt_PedanticBottoms -- Be picky about how we treat bottom
+ | Opt_LlvmTBAA -- Use LLVM TBAA infastructure for improving AA
+ | Opt_RegLiveness -- Use the STG Reg liveness information
-- Interface files
| Opt_IgnoreInterfacePragmas
@@ -1823,6 +1825,8 @@ fFlags = [
( "vectorise", Opt_Vectorise, nop ),
( "regs-graph", Opt_RegsGraph, nop ),
( "regs-iterative", Opt_RegsIterative, nop ),
+ ( "llvm-tbaa", Opt_LlvmTBAA, nop),
+ ( "reg-liveness", Opt_RegLiveness, nop),
( "gen-manifest", Opt_GenManifest, nop ),
( "embed-manifest", Opt_EmbedManifest, nop ),
( "ext-core", Opt_EmitExternalCore, nop ),
@@ -2071,6 +2075,8 @@ optLevelFlags
, ([2], Opt_LiberateCase)
, ([2], Opt_SpecConstr)
, ([2], Opt_RegsGraph)
+ , ([0,1,2], Opt_LlvmTBAA)
+ , ([0,1,2], Opt_RegLiveness)
-- , ([2], Opt_StaticArgumentTransformation)
-- Max writes: I think it's probably best not to enable SAT with -O2 for the
diff --git a/docs/users_guide/flags.xml b/docs/users_guide/flags.xml
index ecce941082..a4041348b1 100644
--- a/docs/users_guide/flags.xml
+++ b/docs/users_guide/flags.xml
@@ -1,1211 +1,1211 @@
<?xml version="1.0" encoding="iso-8859-1"?>
- <sect1 id="flag-reference">
- <title>Flag reference</title>
+<sect1 id="flag-reference">
+ <title>Flag reference</title>
- <para>This section is a quick-reference for GHC's command-line
+ <para>This section is a quick-reference for GHC's command-line
flags. For each flag, we also list its static/dynamic status (see
<xref linkend="static-dynamic-flags"/>), and the flag's opposite
(if available).</para>
- <sect2>
- <title>Help and verbosity options</title>
-
- <para><xref linkend="options-help"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-?</option></entry>
- <entry>help</entry>
- <entry>mode</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-help</option></entry>
- <entry>help</entry>
- <entry>mode</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-v</option></entry>
- <entry>verbose mode (equivalent to <option>-v3</option>)</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-v</option><replaceable>n</replaceable></entry>
- <entry>set verbosity level</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-V</option></entry>
- <entry>display GHC version</entry>
- <entry>mode</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>&ndash;&ndash;supported-extensions</option> or <option>&ndash;&ndash;supported-languages</option></entry>
- <entry>display the supported languages and language extensions</entry>
- <entry>mode</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>&ndash;&ndash;info</option></entry>
- <entry>display information about the compiler</entry>
- <entry>mode</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>&ndash;&ndash;version</option></entry>
- <entry>display GHC version</entry>
- <entry>mode</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>&ndash;&ndash;numeric-version</option></entry>
- <entry>display GHC version (numeric only)</entry>
- <entry>mode</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>&ndash;&ndash;print-libdir</option></entry>
- <entry>display GHC library directory</entry>
- <entry>mode</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ferror-spans</option></entry>
- <entry>output full span in error messages</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-H</option><replaceable>size</replaceable></entry>
- <entry>Set the minimum heap size to <replaceable>size</replaceable></entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-Rghc-timing</option></entry>
- <entry>Summarise timing stats for GHC (same as <literal>+RTS -tstderr</literal>)</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
-
- </sect2>
- <sect2>
- <title>Which phases to run</title>
-
- <para><xref linkend="options-order"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-E</option></entry>
- <entry>Stop after preprocessing (<literal>.hspp</literal> file)</entry>
- <entry>mode</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-C</option></entry>
- <entry>Stop after generating C (<literal>.hc</literal> file)</entry>
- <entry>mode</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-S</option></entry>
- <entry>Stop after generating assembly (<literal>.s</literal> file)</entry>
- <entry>mode</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-c</option></entry>
- <entry>Do not link</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-x</option> <replaceable>suffix</replaceable></entry>
- <entry>Override default behaviour for source files</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
-
- <sect2>
- <title>Alternative modes of operation</title>
-
- <para><xref linkend="modes"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>--interactive</option></entry>
- <entry>Interactive mode - normally used by just running <command>ghci</command>;
- see <xref linkend="ghci"/> for details.</entry>
- <entry>mode</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>--make</option></entry>
- <entry>Build a multi-module Haskell program, automatically figuring out dependencies. Likely to be much easier, and faster, than using <command>make</command>;
- see <xref linkend="make-mode"/> for details..</entry>
- <entry>mode</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-e <replaceable>expr</replaceable></option></entry>
- <entry>Evaluate <replaceable>expr</replaceable>;
- see <xref linkend="eval-mode"/> for details.</entry>
- <entry>mode</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-M</option></entry>
- <entry>Generate dependency information suitable for use in a <filename>Makefile</filename>;
- see <xref linkend="makefile-dependencies"/> for details.</entry>
- <entry>mode</entry>
- <entry>-</entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
-
- <sect2>
- <title>Redirecting output</title>
-
- <para><xref linkend="options-output"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-hcsuf</option> <replaceable>suffix</replaceable></entry>
- <entry>set the suffix to use for intermediate C files</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-hidir</option> <replaceable>dir</replaceable></entry>
- <entry>set directory for interface files</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-hisuf</option> <replaceable>suffix</replaceable></entry>
- <entry>set the suffix to use for interface files</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-o</option> <replaceable>filename</replaceable></entry>
- <entry>set output filename</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-odir</option> <replaceable>dir</replaceable></entry>
- <entry>set directory for object files</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ohi</option> <replaceable>filename</replaceable></entry>
- <entry>set the filename in which to put the interface</entry>
- <entry>dynamic</entry>
- <entry></entry>
- </row>
- <row>
- <entry><option>-osuf</option> <replaceable>suffix</replaceable></entry>
- <entry>set the output file suffix</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-stubdir</option> <replaceable>dir</replaceable></entry>
- <entry>redirect FFI stub files</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dumpdir</option> <replaceable>dir</replaceable></entry>
- <entry>redirect dump files</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-outputdir</option> <replaceable>dir</replaceable></entry>
- <entry>set output directory</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
-
- <sect2>
- <title>Keeping intermediate files</title>
-
- <para><xref linkend="keeping-intermediates"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-keep-hc-file</option> or
- <option>-keep-hc-files</option></entry>
- <entry>retain intermediate <literal>.hc</literal> files</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-keep-llvm-file</option> or
- <option>-keep-llvm-files</option></entry>
- <entry>retain intermediate LLVM <literal>.ll</literal> files</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-keep-s-file</option> or
- <option>-keep-s-files</option></entry>
- <entry>retain intermediate <literal>.s</literal> files</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-keep-tmp-files</option></entry>
- <entry>retain all intermediate temporary files</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
-
- <sect2>
- <title>Temporary files</title>
-
- <para><xref linkend="temp-files"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-tmpdir</option></entry>
- <entry>set the directory for temporary files</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
-
- <sect2>
- <title>Finding imports</title>
-
- <para><xref linkend="search-path"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
-
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-i</option><replaceable>dir1</replaceable>:<replaceable>dir2</replaceable>:...</entry>
- <entry>add <replaceable>dir</replaceable>,
- <replaceable>dir2</replaceable>, etc. to import path</entry>
- <entry>static/<literal>:set</literal></entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-i</option></entry>
- <entry>Empty the import directory list</entry>
- <entry>static/<literal>:set</literal></entry>
- <entry>-</entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
-
- <sect2>
- <title>Interface file options</title>
-
- <para><xref linkend="hi-options"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
-
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-ddump-hi</option></entry>
- <entry>Dump the new interface to stdout</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-hi-diffs</option></entry>
- <entry>Show the differences vs. the old interface</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-minimal-imports</option></entry>
- <entry>Dump a minimal set of imports</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>--show-iface</option> <replaceable>file</replaceable></entry>
- <entry>See <xref linkend="modes"/>.</entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
-
- <sect2>
- <title>Recompilation checking</title>
-
- <para><xref linkend="recomp"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
-
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-fforce-recomp</option></entry>
- <entry>Turn off recompilation checking; implied by any
- <option>-ddump-X</option> option</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-force-recomp</option></entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
-
- <sect2 id="interactive-mode-options">
- <title>Interactive-mode options</title>
-
- <para><xref linkend="ghci-dot-files"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-ignore-dot-ghci</option></entry>
- <entry>Disable reading of <filename>.ghci</filename> files</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ghci-script</option></entry>
- <entry>Load the given additional <filename>.ghci</filename> file</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-read-dot-ghci</option></entry>
- <entry>Enable reading of <filename>.ghci</filename> files</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-fbreak-on-exception</option></entry>
- <entry><link linkend="ghci-debugger-exceptions">Break on any exception thrown</link></entry>
- <entry>dynamic</entry>
- <entry><option>-fno-break-on-exception</option></entry>
- </row>
- <row>
- <entry><option>-fbreak-on-error</option></entry>
- <entry><link linkend="ghci-debugger-exceptions">Break on uncaught exceptions and errors</link></entry>
- <entry>dynamic</entry>
- <entry><option>-fno-break-on-error</option></entry>
- </row>
- <row>
- <entry><option>-fprint-evld-with-show</option></entry>
- <entry><link linkend="breakpoints">Enable usage of Show instances in <literal>:print</literal></link></entry>
- <entry>dynamic</entry>
- <entry><option>-fno-print-evld-with-show</option></entry>
- </row>
- <row>
- <entry><option>-fprint-bind-result</option></entry>
- <entry><link linkend="ghci-stmts">Turn on printing of binding results in GHCi</link></entry>
- <entry>dynamic</entry>
- <entry><option>-fno-print-bind-result</option></entry>
- </row>
- <row>
- <entry><option>-fno-print-bind-contents</option></entry>
- <entry><link linkend="breakpoints">Turn off printing of binding contents in GHCi</link></entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-fno-implicit-import-qualified</option></entry>
- <entry><link linkend="ghci-import-qualified">Turn off
- implicit qualified import of everything in GHCi</link></entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
-
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
-
- <sect2>
- <title>Packages</title>
-
- <para><xref linkend="packages"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-package-name</option> <replaceable>P</replaceable></entry>
- <entry>Compile to be part of package <replaceable>P</replaceable></entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-package</option> <replaceable>P</replaceable></entry>
- <entry>Expose package <replaceable>P</replaceable></entry>
- <entry>static/<literal>:set</literal></entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-hide-all-packages</option></entry>
- <entry>Hide all packages by default</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-hide-package</option> <replaceable>name</replaceable></entry>
- <entry>Hide package <replaceable>P</replaceable></entry>
- <entry>static/<literal>:set</literal></entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ignore-package</option> <replaceable>name</replaceable></entry>
- <entry>Ignore package <replaceable>P</replaceable></entry>
- <entry>static/<literal>:set</literal></entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-package-conf</option> <replaceable>file</replaceable></entry>
- <entry>Load more packages from <replaceable>file</replaceable></entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-no-user-package-conf</option></entry>
- <entry>Don't load the user's package config file.</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-no-auto-link-packages</option></entry>
- <entry>Don't automatically link in the haskell98 package.</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-trust</option> <replaceable>P</replaceable></entry>
- <entry>Expose package <replaceable>P</replaceable> and set it to be
- trusted</entry>
- <entry>static/<literal>:set</literal></entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-distrust</option> <replaceable>P</replaceable></entry>
- <entry>Expose package <replaceable>P</replaceable> and set it to be
- distrusted</entry>
- <entry>static/<literal>:set</literal></entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-distrust-all</option> </entry>
- <entry>Distrust all packages by default</entry>
- <entry>static/<literal>:set</literal></entry>
- <entry>-</entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
-
- <sect2>
- <title>Language options</title>
-
- <para>Language options can be enabled either by a command-line option
+ <sect2>
+ <title>Help and verbosity options</title>
+
+ <para><xref linkend="options-help"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-?</option></entry>
+ <entry>help</entry>
+ <entry>mode</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-help</option></entry>
+ <entry>help</entry>
+ <entry>mode</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-v</option></entry>
+ <entry>verbose mode (equivalent to <option>-v3</option>)</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-v</option><replaceable>n</replaceable></entry>
+ <entry>set verbosity level</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-V</option></entry>
+ <entry>display GHC version</entry>
+ <entry>mode</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>&ndash;&ndash;supported-extensions</option> or <option>&ndash;&ndash;supported-languages</option></entry>
+ <entry>display the supported languages and language extensions</entry>
+ <entry>mode</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>&ndash;&ndash;info</option></entry>
+ <entry>display information about the compiler</entry>
+ <entry>mode</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>&ndash;&ndash;version</option></entry>
+ <entry>display GHC version</entry>
+ <entry>mode</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>&ndash;&ndash;numeric-version</option></entry>
+ <entry>display GHC version (numeric only)</entry>
+ <entry>mode</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>&ndash;&ndash;print-libdir</option></entry>
+ <entry>display GHC library directory</entry>
+ <entry>mode</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ferror-spans</option></entry>
+ <entry>output full span in error messages</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-H</option><replaceable>size</replaceable></entry>
+ <entry>Set the minimum heap size to <replaceable>size</replaceable></entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-Rghc-timing</option></entry>
+ <entry>Summarise timing stats for GHC (same as <literal>+RTS -tstderr</literal>)</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+
+ </sect2>
+ <sect2>
+ <title>Which phases to run</title>
+
+ <para><xref linkend="options-order"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-E</option></entry>
+ <entry>Stop after preprocessing (<literal>.hspp</literal> file)</entry>
+ <entry>mode</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-C</option></entry>
+ <entry>Stop after generating C (<literal>.hc</literal> file)</entry>
+ <entry>mode</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-S</option></entry>
+ <entry>Stop after generating assembly (<literal>.s</literal> file)</entry>
+ <entry>mode</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-c</option></entry>
+ <entry>Do not link</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-x</option> <replaceable>suffix</replaceable></entry>
+ <entry>Override default behaviour for source files</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+
+ <sect2>
+ <title>Alternative modes of operation</title>
+
+ <para><xref linkend="modes"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>--interactive</option></entry>
+ <entry>Interactive mode - normally used by just running <command>ghci</command>;
+ see <xref linkend="ghci"/> for details.</entry>
+ <entry>mode</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>--make</option></entry>
+ <entry>Build a multi-module Haskell program, automatically figuring out dependencies. Likely to be much easier, and faster, than using <command>make</command>;
+ see <xref linkend="make-mode"/> for details..</entry>
+ <entry>mode</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-e <replaceable>expr</replaceable></option></entry>
+ <entry>Evaluate <replaceable>expr</replaceable>;
+ see <xref linkend="eval-mode"/> for details.</entry>
+ <entry>mode</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-M</option></entry>
+ <entry>Generate dependency information suitable for use in a <filename>Makefile</filename>;
+ see <xref linkend="makefile-dependencies"/> for details.</entry>
+ <entry>mode</entry>
+ <entry>-</entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+
+ <sect2>
+ <title>Redirecting output</title>
+
+ <para><xref linkend="options-output"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-hcsuf</option> <replaceable>suffix</replaceable></entry>
+ <entry>set the suffix to use for intermediate C files</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-hidir</option> <replaceable>dir</replaceable></entry>
+ <entry>set directory for interface files</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-hisuf</option> <replaceable>suffix</replaceable></entry>
+ <entry>set the suffix to use for interface files</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-o</option> <replaceable>filename</replaceable></entry>
+ <entry>set output filename</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-odir</option> <replaceable>dir</replaceable></entry>
+ <entry>set directory for object files</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ohi</option> <replaceable>filename</replaceable></entry>
+ <entry>set the filename in which to put the interface</entry>
+ <entry>dynamic</entry>
+ <entry></entry>
+ </row>
+ <row>
+ <entry><option>-osuf</option> <replaceable>suffix</replaceable></entry>
+ <entry>set the output file suffix</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-stubdir</option> <replaceable>dir</replaceable></entry>
+ <entry>redirect FFI stub files</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dumpdir</option> <replaceable>dir</replaceable></entry>
+ <entry>redirect dump files</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-outputdir</option> <replaceable>dir</replaceable></entry>
+ <entry>set output directory</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+
+ <sect2>
+ <title>Keeping intermediate files</title>
+
+ <para><xref linkend="keeping-intermediates"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-keep-hc-file</option> or
+ <option>-keep-hc-files</option></entry>
+ <entry>retain intermediate <literal>.hc</literal> files</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-keep-llvm-file</option> or
+ <option>-keep-llvm-files</option></entry>
+ <entry>retain intermediate LLVM <literal>.ll</literal> files</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-keep-s-file</option> or
+ <option>-keep-s-files</option></entry>
+ <entry>retain intermediate <literal>.s</literal> files</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-keep-tmp-files</option></entry>
+ <entry>retain all intermediate temporary files</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+
+ <sect2>
+ <title>Temporary files</title>
+
+ <para><xref linkend="temp-files"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-tmpdir</option></entry>
+ <entry>set the directory for temporary files</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+
+ <sect2>
+ <title>Finding imports</title>
+
+ <para><xref linkend="search-path"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-i</option><replaceable>dir1</replaceable>:<replaceable>dir2</replaceable>:...</entry>
+ <entry>add <replaceable>dir</replaceable>,
+ <replaceable>dir2</replaceable>, etc. to import path</entry>
+ <entry>static/<literal>:set</literal></entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-i</option></entry>
+ <entry>Empty the import directory list</entry>
+ <entry>static/<literal>:set</literal></entry>
+ <entry>-</entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+
+ <sect2>
+ <title>Interface file options</title>
+
+ <para><xref linkend="hi-options"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-ddump-hi</option></entry>
+ <entry>Dump the new interface to stdout</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-hi-diffs</option></entry>
+ <entry>Show the differences vs. the old interface</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-minimal-imports</option></entry>
+ <entry>Dump a minimal set of imports</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>--show-iface</option> <replaceable>file</replaceable></entry>
+ <entry>See <xref linkend="modes"/>.</entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+
+ <sect2>
+ <title>Recompilation checking</title>
+
+ <para><xref linkend="recomp"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-fforce-recomp</option></entry>
+ <entry>Turn off recompilation checking; implied by any
+ <option>-ddump-X</option> option</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-force-recomp</option></entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+
+ <sect2 id="interactive-mode-options">
+ <title>Interactive-mode options</title>
+
+ <para><xref linkend="ghci-dot-files"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-ignore-dot-ghci</option></entry>
+ <entry>Disable reading of <filename>.ghci</filename> files</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ghci-script</option></entry>
+ <entry>Load the given additional <filename>.ghci</filename> file</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-read-dot-ghci</option></entry>
+ <entry>Enable reading of <filename>.ghci</filename> files</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-fbreak-on-exception</option></entry>
+ <entry><link linkend="ghci-debugger-exceptions">Break on any exception thrown</link></entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-break-on-exception</option></entry>
+ </row>
+ <row>
+ <entry><option>-fbreak-on-error</option></entry>
+ <entry><link linkend="ghci-debugger-exceptions">Break on uncaught exceptions and errors</link></entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-break-on-error</option></entry>
+ </row>
+ <row>
+ <entry><option>-fprint-evld-with-show</option></entry>
+ <entry><link linkend="breakpoints">Enable usage of Show instances in <literal>:print</literal></link></entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-print-evld-with-show</option></entry>
+ </row>
+ <row>
+ <entry><option>-fprint-bind-result</option></entry>
+ <entry><link linkend="ghci-stmts">Turn on printing of binding results in GHCi</link></entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-print-bind-result</option></entry>
+ </row>
+ <row>
+ <entry><option>-fno-print-bind-contents</option></entry>
+ <entry><link linkend="breakpoints">Turn off printing of binding contents in GHCi</link></entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-fno-implicit-import-qualified</option></entry>
+ <entry><link linkend="ghci-import-qualified">Turn off
+ implicit qualified import of everything in GHCi</link></entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+
+ <sect2>
+ <title>Packages</title>
+
+ <para><xref linkend="packages"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-package-name</option> <replaceable>P</replaceable></entry>
+ <entry>Compile to be part of package <replaceable>P</replaceable></entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-package</option> <replaceable>P</replaceable></entry>
+ <entry>Expose package <replaceable>P</replaceable></entry>
+ <entry>static/<literal>:set</literal></entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-hide-all-packages</option></entry>
+ <entry>Hide all packages by default</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-hide-package</option> <replaceable>name</replaceable></entry>
+ <entry>Hide package <replaceable>P</replaceable></entry>
+ <entry>static/<literal>:set</literal></entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ignore-package</option> <replaceable>name</replaceable></entry>
+ <entry>Ignore package <replaceable>P</replaceable></entry>
+ <entry>static/<literal>:set</literal></entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-package-conf</option> <replaceable>file</replaceable></entry>
+ <entry>Load more packages from <replaceable>file</replaceable></entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-no-user-package-conf</option></entry>
+ <entry>Don't load the user's package config file.</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-no-auto-link-packages</option></entry>
+ <entry>Don't automatically link in the haskell98 package.</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-trust</option> <replaceable>P</replaceable></entry>
+ <entry>Expose package <replaceable>P</replaceable> and set it to be
+ trusted</entry>
+ <entry>static/<literal>:set</literal></entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-distrust</option> <replaceable>P</replaceable></entry>
+ <entry>Expose package <replaceable>P</replaceable> and set it to be
+ distrusted</entry>
+ <entry>static/<literal>:set</literal></entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-distrust-all</option> </entry>
+ <entry>Distrust all packages by default</entry>
+ <entry>static/<literal>:set</literal></entry>
+ <entry>-</entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+
+ <sect2>
+ <title>Language options</title>
+
+ <para>Language options can be enabled either by a command-line option
<option>-Xblah</option>, or by a <literal>{-# LANGUAGE blah #-}</literal>
pragma in the file itself. See <xref linkend="options-language"/></para>
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-fglasgow-exts</option></entry>
- <entry>Enable most language extensions; see <xref linkend="options-language"/> for exactly which ones.</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-glasgow-exts</option></entry>
- </row>
- <row>
- <entry><option>-XOverlappingInstances</option></entry>
- <entry>Enable <link linkend="instance-overlap">overlapping instances</link></entry>
- <entry>dynamic</entry>
- <entry><option>-XNoOverlappingInstances</option></entry>
- </row>
- <row>
- <entry><option>-XIncoherentInstances</option></entry>
- <entry>Enable <link linkend="instance-overlap">incoherent instances</link>.
- Implies <option>-XOverlappingInstances</option> </entry>
- <entry>dynamic</entry>
- <entry><option>-XNoIncoherentInstances</option></entry>
- </row>
- <row>
- <entry><option>-XUndecidableInstances</option></entry>
- <entry>Enable <link linkend="undecidable-instances">undecidable instances</link></entry>
- <entry>dynamic</entry>
- <entry><option>-XNoUndecidableInstances</option></entry>
- </row>
- <row>
- <entry><option>-fcontext-stack=N</option><replaceable>n</replaceable></entry>
- <entry>set the <link linkend="undecidable-instances">limit for context reduction</link>. Default is 20.</entry>
- <entry>dynamic</entry>
- <entry></entry>
- </row>
- <row>
- <entry><option>-XArrows</option></entry>
- <entry>Enable <link linkend="arrow-notation">arrow
- notation</link> extension</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoArrows</option></entry>
- </row>
- <row>
- <entry><option>-XDisambiguateRecordFields</option></entry>
- <entry>Enable <link linkend="disambiguate-fields">record
- field disambiguation</link></entry>
- <entry>dynamic</entry>
- <entry><option>-XNoDisambiguateRecordFields</option></entry>
- </row>
- <row>
- <entry><option>-XForeignFunctionInterface</option></entry>
- <entry>Enable <link linkend="ffi">foreign function interface</link> (implied by
- <option>-fglasgow-exts</option>)</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoForeignFunctionInterface</option></entry>
- </row>
- <row>
- <entry><option>-XGenerics</option></entry>
- <entry>Deprecated, does nothing. No longer enables <link linkend="generic-classes">generic classes</link>.
- See also GHC's support for
- <link linkend="generic-programming">generic programming</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoGenerics</option></entry>
- </row>
- <row>
- <entry><option>-XImplicitParams</option></entry>
- <entry>Enable <link linkend="implicit-parameters">Implicit Parameters</link>.
- Implied by <option>-fglasgow-exts</option>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoImplicitParams</option></entry>
- </row>
- <row>
- <entry><option>-firrefutable-tuples</option></entry>
- <entry>Make tuple pattern matching irrefutable</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-irrefutable-tuples</option></entry>
- </row>
- <row>
- <entry><option>-XNoImplicitPrelude</option></entry>
- <entry>Don't implicitly <literal>import Prelude</literal></entry>
- <entry>dynamic</entry>
- <entry><option>-XImplicitPrelude</option></entry>
- </row>
- <row>
- <entry><option>-XRebindableSyntax</option></entry>
- <entry>Employ <link linkend="rebindable-syntax">rebindable syntax</link></entry>
- <entry>dynamic</entry>
- <entry><option>-XNoRebindableSyntax</option></entry>
- </row>
- <row>
- <entry><option>-XNoMonomorphismRestriction</option></entry>
- <entry>Disable the <link linkend="monomorphism">monomorphism restriction</link></entry>
- <entry>dynamic</entry>
- <entry><option>-XMonomorphismRrestriction</option></entry>
- </row>
- <row>
- <entry><option>-XNoNPlusKPatterns</option></entry>
- <entry>Disable support for <literal>n+k</literal> patterns</entry>
- <entry>dynamic</entry>
- <entry><option>-XNPlusKPatterns</option></entry>
- </row>
- <row>
- <entry><option>-XNoTraditionalRecordSyntax</option></entry>
- <entry>Disable support for traditional record syntax (as supported by Haskell 98) <literal>C {f = x}</literal></entry>
- <entry>dynamic</entry>
- <entry><option>-XTraditionalRecordSyntax</option></entry>
- </row>
- <row>
- <entry><option>-XNoMonoPatBinds</option></entry>
- <entry>Make <link linkend="monomorphism">pattern bindings polymorphic</link></entry>
- <entry>dynamic</entry>
- <entry><option>-XMonoPatBinds</option></entry>
- </row>
- <row>
- <entry><option>-XRelaxedPolyRec</option></entry>
- <entry>Relaxed checking for <link linkend="typing-binds">mutually-recursive polymorphic functions</link></entry>
- <entry>dynamic</entry>
- <entry><option>-XNoRelaxedPolyRec</option></entry>
- </row>
- <row>
- <entry><option>-XExtendedDefaultRules</option></entry>
- <entry>Use GHCi's <link linkend="extended-default-rules">extended default rules</link> in a normal module</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoExtendedDefaultRules</option></entry>
- </row>
- <row>
- <entry><option>-XOverloadedStrings</option></entry>
- <entry>Enable <link linkend="overloaded-strings">overloaded string literals</link>.
- </entry>
- <entry>dynamic</entry>
- <entry><option>-XNoOverloadedStrings</option></entry>
- </row>
- <row>
- <entry><option>-XGADTs</option></entry>
- <entry>Enable <link linkend="gadt">generalised algebraic data types</link>.
- </entry>
- <entry>dynamic</entry>
- <entry><option>-XNoGADTs</option></entry>
- </row>
- <row>
- <entry><option>-XGADTSyntax</option></entry>
- <entry>Enable <link linkend="gadt-style">generalised algebraic data type syntax</link>.
- </entry>
- <entry>dynamic</entry>
- <entry><option>-XNoGADTSyntax</option></entry>
- </row>
- <row>
- <entry><option>-XTypeFamilies</option></entry>
- <entry>Enable <link linkend="type-families">type families</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoTypeFamilies</option></entry>
- </row>
- <row>
- <entry><option>-XConstraintKinds</option></entry>
- <entry>Enable a <link linkend="constraint-kind">kind of constraints</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoConstraintKinds</option></entry>
- </row>
- <row>
- <entry><option>-XPolyKinds</option></entry>
- <entry>Enable <link linkend="kind-polymorphism">kind polymorphism</link>.
- Implies <option>-XKindSignatures</option>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoPolyKinds</option></entry>
- </row>
- <row>
- <entry><option>-XScopedTypeVariables</option></entry>
- <entry>Enable <link linkend="scoped-type-variables">lexically-scoped type variables</link>.
- Implied by <option>-fglasgow-exts</option>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoScopedTypeVariables</option></entry>
- </row>
- <row>
- <entry><option>-XMonoLocalBinds</option></entry>
- <entry>Enable <link linkend="mono-local-binds">do not generalise local bindings</link>.
- </entry>
- <entry>dynamic</entry>
- <entry><option>-XNoMonoLocalBinds</option></entry>
- </row>
- <row>
- <entry><option>-XTemplateHaskell</option></entry>
- <entry>Enable <link linkend="template-haskell">Template Haskell</link>.
- No longer implied by <option>-fglasgow-exts</option>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoTemplateHaskell</option></entry>
- </row>
- <row>
- <entry><option>-XQuasiQuotes</option></entry>
- <entry>Enable <link linkend="th-quasiquotation">quasiquotation</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoQuasiQuotes</option></entry>
- </row>
- <row>
- <entry><option>-XBangPatterns</option></entry>
- <entry>Enable <link linkend="bang-patterns">bang patterns</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoBangPatterns</option></entry>
- </row>
- <row>
- <entry><option>-XCPP</option></entry>
- <entry>Enable the <link linkend="c-pre-processor">C preprocessor</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoCPP</option></entry>
- </row>
- <row>
- <entry><option>-XPatternGuards</option></entry>
- <entry>Enable <link linkend="pattern-guards">pattern guards</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoPatternGuards</option></entry>
- </row>
- <row>
- <entry><option>-XViewPatterns</option></entry>
- <entry>Enable <link linkend="view-patterns">view patterns</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoViewPatterns</option></entry>
- </row>
- <row>
- <entry><option>-XUnicodeSyntax</option></entry>
- <entry>Enable <link linkend="unicode-syntax">unicode syntax</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoUnicodeSyntax</option></entry>
- </row>
- <row>
- <entry><option>-XMagicHash</option></entry>
- <entry>Allow "#" as a <link linkend="magic-hash">postfix modifier on identifiers</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoMagicHash</option></entry>
- </row>
- <row>
- <entry><option>-XExplicitForAll</option></entry>
- <entry>Enable <link linkend="explicit-foralls">explicit universal quantification</link>.
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-fglasgow-exts</option></entry>
+ <entry>Enable most language extensions; see <xref linkend="options-language"/> for exactly which ones.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-glasgow-exts</option></entry>
+ </row>
+ <row>
+ <entry><option>-XOverlappingInstances</option></entry>
+ <entry>Enable <link linkend="instance-overlap">overlapping instances</link></entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoOverlappingInstances</option></entry>
+ </row>
+ <row>
+ <entry><option>-XIncoherentInstances</option></entry>
+ <entry>Enable <link linkend="instance-overlap">incoherent instances</link>.
+ Implies <option>-XOverlappingInstances</option> </entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoIncoherentInstances</option></entry>
+ </row>
+ <row>
+ <entry><option>-XUndecidableInstances</option></entry>
+ <entry>Enable <link linkend="undecidable-instances">undecidable instances</link></entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoUndecidableInstances</option></entry>
+ </row>
+ <row>
+ <entry><option>-fcontext-stack=N</option><replaceable>n</replaceable></entry>
+ <entry>set the <link linkend="undecidable-instances">limit for context reduction</link>. Default is 20.</entry>
+ <entry>dynamic</entry>
+ <entry></entry>
+ </row>
+ <row>
+ <entry><option>-XArrows</option></entry>
+ <entry>Enable <link linkend="arrow-notation">arrow
+ notation</link> extension</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoArrows</option></entry>
+ </row>
+ <row>
+ <entry><option>-XDisambiguateRecordFields</option></entry>
+ <entry>Enable <link linkend="disambiguate-fields">record
+ field disambiguation</link></entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoDisambiguateRecordFields</option></entry>
+ </row>
+ <row>
+ <entry><option>-XForeignFunctionInterface</option></entry>
+ <entry>Enable <link linkend="ffi">foreign function interface</link> (implied by
+ <option>-fglasgow-exts</option>)</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoForeignFunctionInterface</option></entry>
+ </row>
+ <row>
+ <entry><option>-XGenerics</option></entry>
+ <entry>Deprecated, does nothing. No longer enables <link linkend="generic-classes">generic classes</link>.
+ See also GHC's support for
+ <link linkend="generic-programming">generic programming</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoGenerics</option></entry>
+ </row>
+ <row>
+ <entry><option>-XImplicitParams</option></entry>
+ <entry>Enable <link linkend="implicit-parameters">Implicit Parameters</link>.
+ Implied by <option>-fglasgow-exts</option>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoImplicitParams</option></entry>
+ </row>
+ <row>
+ <entry><option>-firrefutable-tuples</option></entry>
+ <entry>Make tuple pattern matching irrefutable</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-irrefutable-tuples</option></entry>
+ </row>
+ <row>
+ <entry><option>-XNoImplicitPrelude</option></entry>
+ <entry>Don't implicitly <literal>import Prelude</literal></entry>
+ <entry>dynamic</entry>
+ <entry><option>-XImplicitPrelude</option></entry>
+ </row>
+ <row>
+ <entry><option>-XRebindableSyntax</option></entry>
+ <entry>Employ <link linkend="rebindable-syntax">rebindable syntax</link></entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoRebindableSyntax</option></entry>
+ </row>
+ <row>
+ <entry><option>-XNoMonomorphismRestriction</option></entry>
+ <entry>Disable the <link linkend="monomorphism">monomorphism restriction</link></entry>
+ <entry>dynamic</entry>
+ <entry><option>-XMonomorphismRrestriction</option></entry>
+ </row>
+ <row>
+ <entry><option>-XNoNPlusKPatterns</option></entry>
+ <entry>Disable support for <literal>n+k</literal> patterns</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNPlusKPatterns</option></entry>
+ </row>
+ <row>
+ <entry><option>-XNoTraditionalRecordSyntax</option></entry>
+ <entry>Disable support for traditional record syntax (as supported by Haskell 98) <literal>C {f = x}</literal></entry>
+ <entry>dynamic</entry>
+ <entry><option>-XTraditionalRecordSyntax</option></entry>
+ </row>
+ <row>
+ <entry><option>-XNoMonoPatBinds</option></entry>
+ <entry>Make <link linkend="monomorphism">pattern bindings polymorphic</link></entry>
+ <entry>dynamic</entry>
+ <entry><option>-XMonoPatBinds</option></entry>
+ </row>
+ <row>
+ <entry><option>-XRelaxedPolyRec</option></entry>
+ <entry>Relaxed checking for <link linkend="typing-binds">mutually-recursive polymorphic functions</link></entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoRelaxedPolyRec</option></entry>
+ </row>
+ <row>
+ <entry><option>-XExtendedDefaultRules</option></entry>
+ <entry>Use GHCi's <link linkend="extended-default-rules">extended default rules</link> in a normal module</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoExtendedDefaultRules</option></entry>
+ </row>
+ <row>
+ <entry><option>-XOverloadedStrings</option></entry>
+ <entry>Enable <link linkend="overloaded-strings">overloaded string literals</link>.
+ </entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoOverloadedStrings</option></entry>
+ </row>
+ <row>
+ <entry><option>-XGADTs</option></entry>
+ <entry>Enable <link linkend="gadt">generalised algebraic data types</link>.
+ </entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoGADTs</option></entry>
+ </row>
+ <row>
+ <entry><option>-XGADTSyntax</option></entry>
+ <entry>Enable <link linkend="gadt-style">generalised algebraic data type syntax</link>.
+ </entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoGADTSyntax</option></entry>
+ </row>
+ <row>
+ <entry><option>-XTypeFamilies</option></entry>
+ <entry>Enable <link linkend="type-families">type families</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoTypeFamilies</option></entry>
+ </row>
+ <row>
+ <entry><option>-XConstraintKinds</option></entry>
+ <entry>Enable a <link linkend="constraint-kind">kind of constraints</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoConstraintKinds</option></entry>
+ </row>
+ <row>
+ <entry><option>-XPolyKinds</option></entry>
+ <entry>Enable <link linkend="kind-polymorphism">kind polymorphism</link>.
+ Implies <option>-XKindSignatures</option>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoPolyKinds</option></entry>
+ </row>
+ <row>
+ <entry><option>-XScopedTypeVariables</option></entry>
+ <entry>Enable <link linkend="scoped-type-variables">lexically-scoped type variables</link>.
+ Implied by <option>-fglasgow-exts</option>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoScopedTypeVariables</option></entry>
+ </row>
+ <row>
+ <entry><option>-XMonoLocalBinds</option></entry>
+ <entry>Enable <link linkend="mono-local-binds">do not generalise local bindings</link>.
+ </entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoMonoLocalBinds</option></entry>
+ </row>
+ <row>
+ <entry><option>-XTemplateHaskell</option></entry>
+ <entry>Enable <link linkend="template-haskell">Template Haskell</link>.
+ No longer implied by <option>-fglasgow-exts</option>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoTemplateHaskell</option></entry>
+ </row>
+ <row>
+ <entry><option>-XQuasiQuotes</option></entry>
+ <entry>Enable <link linkend="th-quasiquotation">quasiquotation</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoQuasiQuotes</option></entry>
+ </row>
+ <row>
+ <entry><option>-XBangPatterns</option></entry>
+ <entry>Enable <link linkend="bang-patterns">bang patterns</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoBangPatterns</option></entry>
+ </row>
+ <row>
+ <entry><option>-XCPP</option></entry>
+ <entry>Enable the <link linkend="c-pre-processor">C preprocessor</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoCPP</option></entry>
+ </row>
+ <row>
+ <entry><option>-XPatternGuards</option></entry>
+ <entry>Enable <link linkend="pattern-guards">pattern guards</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoPatternGuards</option></entry>
+ </row>
+ <row>
+ <entry><option>-XViewPatterns</option></entry>
+ <entry>Enable <link linkend="view-patterns">view patterns</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoViewPatterns</option></entry>
+ </row>
+ <row>
+ <entry><option>-XUnicodeSyntax</option></entry>
+ <entry>Enable <link linkend="unicode-syntax">unicode syntax</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoUnicodeSyntax</option></entry>
+ </row>
+ <row>
+ <entry><option>-XMagicHash</option></entry>
+ <entry>Allow "#" as a <link linkend="magic-hash">postfix modifier on identifiers</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoMagicHash</option></entry>
+ </row>
+ <row>
+ <entry><option>-XExplicitForAll</option></entry>
+ <entry>Enable <link linkend="explicit-foralls">explicit universal quantification</link>.
Implied by <option>-XScopedTypeVariables</option>,
- <option>-XLiberalTypeSynonyms</option>,
- <option>-XRank2Types</option>,
- <option>-XRankNTypes</option>,
- <option>-XPolymorphicComponents</option>,
- <option>-XExistentialQuantification</option>
- </entry>
- <entry>dynamic</entry>
- <entry><option>-XNoExplicitForAll</option></entry>
- </row>
- <row>
- <entry><option>-XPolymorphicComponents</option></entry>
- <entry>Enable <link linkend="universal-quantification">polymorphic components for data constructors</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoPolymorphicComponents</option></entry>
- </row>
- <row>
- <entry><option>-XRank2Types</option></entry>
- <entry>Enable <link linkend="universal-quantification">rank-2 types</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoRank2Types</option></entry>
- </row>
- <row>
- <entry><option>-XRankNTypes</option></entry>
- <entry>Enable <link linkend="universal-quantification">rank-N types</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoRankNTypes</option></entry>
- </row>
- <row>
- <entry><option>-XImpredicativeTypes</option></entry>
- <entry>Enable <link linkend="impredicative-polymorphism">impredicative types</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoImpredicativeTypes</option></entry>
- </row>
- <row>
- <entry><option>-XExistentialQuantification</option></entry>
- <entry>Enable <link linkend="existential-quantification">existential quantification</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoExistentialQuantification</option></entry>
- </row>
- <row>
- <entry><option>-XKindSignatures</option></entry>
- <entry>Enable <link linkend="kinding">kind signatures</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoKindSignatures</option></entry>
- </row>
- <row>
- <entry><option>-XEmptyDataDecls</option></entry>
- <entry>Enable empty data declarations.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoEmptyDataDecls</option></entry>
- </row>
- <row>
- <entry><option>-XParallelListComp</option></entry>
- <entry>Enable <link linkend="parallel-list-comprehensions">parallel list comprehensions</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoParallelListComp</option></entry>
- </row>
- <row>
- <entry><option>-XTransformListComp</option></entry>
- <entry>Enable <link linkend="generalised-list-comprehensions">generalised list comprehensions</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoTransformListComp</option></entry>
- </row>
- <row>
- <entry><option>-XMonadComprehensions</option></entry>
- <entry>Enable <link linkend="monad-comprehensions">monad comprehensions</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoMonadComprehensions</option></entry>
- </row>
- <row>
- <entry><option>-XUnliftedFFITypes</option></entry>
- <entry>Enable unlifted FFI types.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoUnliftedFFITypes</option></entry>
- </row>
- <row>
- <entry><option>-XInterruptibleFFI</option></entry>
- <entry>Enable interruptible FFI.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoInterruptibleFFI</option></entry>
- </row>
- <row>
- <entry><option>-XLiberalTypeSynonyms</option></entry>
- <entry>Enable <link linkend="type-synonyms">liberalised type synonyms</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoLiberalTypeSynonyms</option></entry>
- </row>
- <row>
- <entry><option>-XTypeOperators</option></entry>
- <entry>Enable type operators.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoTypeOperators</option></entry>
- </row>
- <row>
- <entry><option>-XDoRec</option></entry>
- <entry>Enable <link linkend="recursive-do-notation">recursive do notation</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoDoRec</option></entry>
- </row>
- <row>
- <entry><option>-XRecursiveDo</option></entry>
- <entry>Enable <link linkend="mdo-notation">recursive do (mdo) notation</link>. This is deprecated; please use <link linkend="recursive-do-notation">recursive do notation</link> instead.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoRecursiveDo</option></entry>
- </row>
- <row>
- <entry><option>-XParallelArrays</option></entry>
- <entry>Enable parallel arrays.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoParallelArrays</option></entry>
- </row>
- <row>
- <entry><option>-XRecordWildCards</option></entry>
- <entry>Enable <link linkend="record-wildcards">record wildcards</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoRecordWildCards</option></entry>
- </row>
- <row>
- <entry><option>-XNamedFieldPuns</option></entry>
- <entry>Enable <link linkend="record-puns">record puns</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoNamedFieldPuns</option></entry>
- </row>
- <row>
- <entry><option>-XDisambiguateRecordFields</option></entry>
- <entry>Enable <link linkend="disambiguate-fields">record field disambiguation</link>. </entry>
- <entry>dynamic</entry>
- <entry><option>-XNoDisambiguateRecordFields</option></entry>
- </row>
- <row>
- <entry><option>-XUnboxedTuples</option></entry>
- <entry>Enable <link linkend="unboxed-tuples">unboxed tuples</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoUnboxedTuples</option></entry>
- </row>
- <row>
- <entry><option>-XStandaloneDeriving</option></entry>
- <entry>Enable <link linkend="stand-alone-deriving">standalone deriving</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoStandaloneDeriving</option></entry>
- </row>
- <row>
- <entry><option>-XDeriveDataTypeable</option></entry>
- <entry>Enable <link linkend="deriving-typeable">deriving for the Data and Typeable classes</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoDeriveDataTypeable</option></entry>
- </row>
- <row>
- <entry><option>-XDeriveGeneric</option></entry>
- <entry>Enable <link linkend="deriving-typeable">deriving for the Generic class</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoDeriveGeneric</option></entry>
- </row>
- <row>
- <entry><option>-XGeneralizedNewtypeDeriving</option></entry>
- <entry>Enable <link linkend="newtype-deriving">newtype deriving</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoGeneralizedNewtypeDeriving</option></entry>
- </row>
- <row>
- <entry><option>-XTypeSynonymInstances</option></entry>
- <entry>Enable <link linkend="flexible-instance-head">type synonyms in instance heads</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoTypeSynonymInstances</option></entry>
- </row>
- <row>
- <entry><option>-XFlexibleContexts</option></entry>
- <entry>Enable <link linkend="flexible-contexts">flexible contexts</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoFlexibleContexts</option></entry>
- </row>
- <row>
- <entry><option>-XFlexibleInstances</option></entry>
- <entry>Enable <link linkend="instance-rules">flexible instances</link>.
+ <option>-XLiberalTypeSynonyms</option>,
+ <option>-XRank2Types</option>,
+ <option>-XRankNTypes</option>,
+ <option>-XPolymorphicComponents</option>,
+ <option>-XExistentialQuantification</option>
+ </entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoExplicitForAll</option></entry>
+ </row>
+ <row>
+ <entry><option>-XPolymorphicComponents</option></entry>
+ <entry>Enable <link linkend="universal-quantification">polymorphic components for data constructors</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoPolymorphicComponents</option></entry>
+ </row>
+ <row>
+ <entry><option>-XRank2Types</option></entry>
+ <entry>Enable <link linkend="universal-quantification">rank-2 types</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoRank2Types</option></entry>
+ </row>
+ <row>
+ <entry><option>-XRankNTypes</option></entry>
+ <entry>Enable <link linkend="universal-quantification">rank-N types</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoRankNTypes</option></entry>
+ </row>
+ <row>
+ <entry><option>-XImpredicativeTypes</option></entry>
+ <entry>Enable <link linkend="impredicative-polymorphism">impredicative types</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoImpredicativeTypes</option></entry>
+ </row>
+ <row>
+ <entry><option>-XExistentialQuantification</option></entry>
+ <entry>Enable <link linkend="existential-quantification">existential quantification</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoExistentialQuantification</option></entry>
+ </row>
+ <row>
+ <entry><option>-XKindSignatures</option></entry>
+ <entry>Enable <link linkend="kinding">kind signatures</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoKindSignatures</option></entry>
+ </row>
+ <row>
+ <entry><option>-XEmptyDataDecls</option></entry>
+ <entry>Enable empty data declarations.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoEmptyDataDecls</option></entry>
+ </row>
+ <row>
+ <entry><option>-XParallelListComp</option></entry>
+ <entry>Enable <link linkend="parallel-list-comprehensions">parallel list comprehensions</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoParallelListComp</option></entry>
+ </row>
+ <row>
+ <entry><option>-XTransformListComp</option></entry>
+ <entry>Enable <link linkend="generalised-list-comprehensions">generalised list comprehensions</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoTransformListComp</option></entry>
+ </row>
+ <row>
+ <entry><option>-XMonadComprehensions</option></entry>
+ <entry>Enable <link linkend="monad-comprehensions">monad comprehensions</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoMonadComprehensions</option></entry>
+ </row>
+ <row>
+ <entry><option>-XUnliftedFFITypes</option></entry>
+ <entry>Enable unlifted FFI types.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoUnliftedFFITypes</option></entry>
+ </row>
+ <row>
+ <entry><option>-XInterruptibleFFI</option></entry>
+ <entry>Enable interruptible FFI.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoInterruptibleFFI</option></entry>
+ </row>
+ <row>
+ <entry><option>-XLiberalTypeSynonyms</option></entry>
+ <entry>Enable <link linkend="type-synonyms">liberalised type synonyms</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoLiberalTypeSynonyms</option></entry>
+ </row>
+ <row>
+ <entry><option>-XTypeOperators</option></entry>
+ <entry>Enable type operators.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoTypeOperators</option></entry>
+ </row>
+ <row>
+ <entry><option>-XDoRec</option></entry>
+ <entry>Enable <link linkend="recursive-do-notation">recursive do notation</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoDoRec</option></entry>
+ </row>
+ <row>
+ <entry><option>-XRecursiveDo</option></entry>
+ <entry>Enable <link linkend="mdo-notation">recursive do (mdo) notation</link>. This is deprecated; please use <link linkend="recursive-do-notation">recursive do notation</link> instead.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoRecursiveDo</option></entry>
+ </row>
+ <row>
+ <entry><option>-XParallelArrays</option></entry>
+ <entry>Enable parallel arrays.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoParallelArrays</option></entry>
+ </row>
+ <row>
+ <entry><option>-XRecordWildCards</option></entry>
+ <entry>Enable <link linkend="record-wildcards">record wildcards</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoRecordWildCards</option></entry>
+ </row>
+ <row>
+ <entry><option>-XNamedFieldPuns</option></entry>
+ <entry>Enable <link linkend="record-puns">record puns</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoNamedFieldPuns</option></entry>
+ </row>
+ <row>
+ <entry><option>-XDisambiguateRecordFields</option></entry>
+ <entry>Enable <link linkend="disambiguate-fields">record field disambiguation</link>. </entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoDisambiguateRecordFields</option></entry>
+ </row>
+ <row>
+ <entry><option>-XUnboxedTuples</option></entry>
+ <entry>Enable <link linkend="unboxed-tuples">unboxed tuples</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoUnboxedTuples</option></entry>
+ </row>
+ <row>
+ <entry><option>-XStandaloneDeriving</option></entry>
+ <entry>Enable <link linkend="stand-alone-deriving">standalone deriving</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoStandaloneDeriving</option></entry>
+ </row>
+ <row>
+ <entry><option>-XDeriveDataTypeable</option></entry>
+ <entry>Enable <link linkend="deriving-typeable">deriving for the Data and Typeable classes</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoDeriveDataTypeable</option></entry>
+ </row>
+ <row>
+ <entry><option>-XDeriveGeneric</option></entry>
+ <entry>Enable <link linkend="deriving-typeable">deriving for the Generic class</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoDeriveGeneric</option></entry>
+ </row>
+ <row>
+ <entry><option>-XGeneralizedNewtypeDeriving</option></entry>
+ <entry>Enable <link linkend="newtype-deriving">newtype deriving</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoGeneralizedNewtypeDeriving</option></entry>
+ </row>
+ <row>
+ <entry><option>-XTypeSynonymInstances</option></entry>
+ <entry>Enable <link linkend="flexible-instance-head">type synonyms in instance heads</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoTypeSynonymInstances</option></entry>
+ </row>
+ <row>
+ <entry><option>-XFlexibleContexts</option></entry>
+ <entry>Enable <link linkend="flexible-contexts">flexible contexts</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoFlexibleContexts</option></entry>
+ </row>
+ <row>
+ <entry><option>-XFlexibleInstances</option></entry>
+ <entry>Enable <link linkend="instance-rules">flexible instances</link>.
Implies <option>-XTypeSynonymInstances</option> </entry>
- <entry>dynamic</entry>
- <entry><option>-XNoFlexibleInstances</option></entry>
- </row>
- <row>
- <entry><option>-XConstrainedClassMethods</option></entry>
- <entry>Enable <link linkend="class-method-types">constrained class methods</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoConstrainedClassMethods</option></entry>
- </row>
- <row>
- <entry><option>-XDefaultSignatures</option></entry>
- <entry>Enable <link linkend="class-default-signatures">default signatures</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoDefaultSignatures</option></entry>
- </row>
- <row>
- <entry><option>-XMultiParamTypeClasses</option></entry>
- <entry>Enable <link linkend="multi-param-type-classes">multi parameter type classes</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoMultiParamTypeClasses</option></entry>
- </row>
- <row>
- <entry><option>-XFunctionalDependencies</option></entry>
- <entry>Enable <link linkend="functional-dependencies">functional dependencies</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoFunctionalDependencies</option></entry>
- </row>
- <row>
- <entry><option>-XPackageImports</option></entry>
- <entry>Enable <link linkend="package-imports">package-qualified imports</link>.</entry>
- <entry>dynamic</entry>
- <entry><option>-XNoPackageImports</option></entry>
- </row>
- <row>
- <entry><option>-XSafe</option></entry>
- <entry>Enable the <link linkend="safe-haskell">Safe Haskell</link> Safe mode.</entry>
- <entry>dynamic</entry>
- <entry><option>-</option></entry>
- </row>
- <row>
- <entry><option>-XTrustworthy</option></entry>
- <entry>Enable the <link linkend="safe-haskell">Safe Haskell</link> Trustworthy mode.</entry>
- <entry>dynamic</entry>
- <entry><option>-</option></entry>
- </row>
- <row>
- <entry><option>-XUnsafe</option></entry>
- <entry>Enable <link linkend="safe-haskell">Safe Haskell</link> Unsafe mode.</entry>
- <entry>dynamic</entry>
- <entry><option>-</option></entry>
- </row>
- <row>
- <entry><option>-fpackage-trust</option></entry>
- <entry>Enable <link linkend="safe-haskell">Safe Haskell</link> trusted package requirement for trustworty modules.</entry>
- <entry>dynamic</entry>
- <entry><option>-</option></entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
-
- <sect2>
- <title>Warnings</title>
-
- <para><xref linkend="options-sanity"/></para>
+ <entry>dynamic</entry>
+ <entry><option>-XNoFlexibleInstances</option></entry>
+ </row>
+ <row>
+ <entry><option>-XConstrainedClassMethods</option></entry>
+ <entry>Enable <link linkend="class-method-types">constrained class methods</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoConstrainedClassMethods</option></entry>
+ </row>
+ <row>
+ <entry><option>-XDefaultSignatures</option></entry>
+ <entry>Enable <link linkend="class-default-signatures">default signatures</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoDefaultSignatures</option></entry>
+ </row>
+ <row>
+ <entry><option>-XMultiParamTypeClasses</option></entry>
+ <entry>Enable <link linkend="multi-param-type-classes">multi parameter type classes</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoMultiParamTypeClasses</option></entry>
+ </row>
+ <row>
+ <entry><option>-XFunctionalDependencies</option></entry>
+ <entry>Enable <link linkend="functional-dependencies">functional dependencies</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoFunctionalDependencies</option></entry>
+ </row>
+ <row>
+ <entry><option>-XPackageImports</option></entry>
+ <entry>Enable <link linkend="package-imports">package-qualified imports</link>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-XNoPackageImports</option></entry>
+ </row>
+ <row>
+ <entry><option>-XSafe</option></entry>
+ <entry>Enable the <link linkend="safe-haskell">Safe Haskell</link> Safe mode.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-</option></entry>
+ </row>
+ <row>
+ <entry><option>-XTrustworthy</option></entry>
+ <entry>Enable the <link linkend="safe-haskell">Safe Haskell</link> Trustworthy mode.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-</option></entry>
+ </row>
+ <row>
+ <entry><option>-XUnsafe</option></entry>
+ <entry>Enable <link linkend="safe-haskell">Safe Haskell</link> Unsafe mode.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-</option></entry>
+ </row>
+ <row>
+ <entry><option>-fpackage-trust</option></entry>
+ <entry>Enable <link linkend="safe-haskell">Safe Haskell</link> trusted package requirement for trustworty modules.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-</option></entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+
+ <sect2>
+ <title>Warnings</title>
+
+ <para><xref linkend="options-sanity"/></para>
<informaltable>
<tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-W</option></entry>
- <entry>enable normal warnings</entry>
- <entry>dynamic</entry>
- <entry><option>-w</option></entry>
- </row>
- <row>
- <entry><option>-w</option></entry>
- <entry>disable all warnings</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-Wall</option></entry>
- <entry>enable almost all warnings (details in <xref linkend="options-sanity"/>)</entry>
- <entry>dynamic</entry>
- <entry><option>-w</option></entry>
- </row>
- <row>
- <entry><option>-Werror</option></entry>
- <entry>make warnings fatal</entry>
- <entry>dynamic</entry>
- <entry>-Wwarn</entry>
- </row>
- <row>
- <entry><option>-Wwarn</option></entry>
- <entry>make warnings non-fatal</entry>
- <entry>dynamic</entry>
- <entry>-Werror</entry>
- </row>
-
- <row>
- <entry><option>-fdefer-type-errors</option></entry>
- <entry>Defer as many type errors as possible until runtime.</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-defer-type-errors</option></entry>
- </row>
-
- <row>
- <entry><option>-fhelpful-errors</option></entry>
- <entry>Make suggestions for mis-spelled names.</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-helpful-errors</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-deprecated-flags</option></entry>
- <entry>warn about uses of commandline flags that are deprecated</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-deprecated-flags</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-duplicate-exports</option></entry>
- <entry>warn when an entity is exported multiple times</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-duplicate-exports</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-hi-shadowing</option></entry>
- <entry>warn when a <literal>.hi</literal> file in the
- current directory shadows a library</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-hi-shadowing</option></entry>
- </row>
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-W</option></entry>
+ <entry>enable normal warnings</entry>
+ <entry>dynamic</entry>
+ <entry><option>-w</option></entry>
+ </row>
+ <row>
+ <entry><option>-w</option></entry>
+ <entry>disable all warnings</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-Wall</option></entry>
+ <entry>enable almost all warnings (details in <xref linkend="options-sanity"/>)</entry>
+ <entry>dynamic</entry>
+ <entry><option>-w</option></entry>
+ </row>
+ <row>
+ <entry><option>-Werror</option></entry>
+ <entry>make warnings fatal</entry>
+ <entry>dynamic</entry>
+ <entry>-Wwarn</entry>
+ </row>
+ <row>
+ <entry><option>-Wwarn</option></entry>
+ <entry>make warnings non-fatal</entry>
+ <entry>dynamic</entry>
+ <entry>-Werror</entry>
+ </row>
+
+ <row>
+ <entry><option>-fdefer-type-errors</option></entry>
+ <entry>Defer as many type errors as possible until runtime.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-defer-type-errors</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fhelpful-errors</option></entry>
+ <entry>Make suggestions for mis-spelled names.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-helpful-errors</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-deprecated-flags</option></entry>
+ <entry>warn about uses of commandline flags that are deprecated</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-deprecated-flags</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-duplicate-exports</option></entry>
+ <entry>warn when an entity is exported multiple times</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-duplicate-exports</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-hi-shadowing</option></entry>
+ <entry>warn when a <literal>.hi</literal> file in the
+ current directory shadows a library</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-hi-shadowing</option></entry>
+ </row>
<row>
<entry><option>-fwarn-identities</option></entry>
<entry>warn about uses of Prelude numeric conversions that are probably
- the identity (and hence could be omitted)</entry>
+ the identity (and hence could be omitted)</entry>
<entry>dynamic</entry>
<entry><option>-fno-warn-identities</option></entry>
</row>
@@ -1217,1622 +1217,1648 @@
<entry><option>-fno-warn-implicit-prelude</option></entry>
</row>
- <row>
- <entry><option>-fwarn-incomplete-patterns</option></entry>
- <entry>warn when a pattern match could fail</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-incomplete-patterns</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-incomplete-uni-patterns</option></entry>
- <entry>warn when a pattern match in a lambda expression or pattern binding could fail</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-incomplete-uni-patterns</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-incomplete-record-updates</option></entry>
- <entry>warn when a record update could fail</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-incomplete-record-updates</option></entry>
- </row>
-
- <row>
+ <row>
+ <entry><option>-fwarn-incomplete-patterns</option></entry>
+ <entry>warn when a pattern match could fail</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-incomplete-patterns</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-incomplete-uni-patterns</option></entry>
+ <entry>warn when a pattern match in a lambda expression or pattern binding could fail</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-incomplete-uni-patterns</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-incomplete-record-updates</option></entry>
+ <entry>warn when a record update could fail</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-incomplete-record-updates</option></entry>
+ </row>
+
+ <row>
<entry><option>-fwarn-lazy-unlifted-bindings</option></entry>
<entry>warn when a pattern binding looks lazy but must be strict</entry>
- <entry>dynamic</entry>
+ <entry>dynamic</entry>
<entry><option>-fno-warn-lazy-unlifted-bindings</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-missing-fields</option></entry>
- <entry>warn when fields of a record are uninitialised</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-missing-fields</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-missing-import-lists</option></entry>
- <entry>warn when an import declaration does not explicitly
- list all the names brought into scope</entry>
- <entry>dynamic</entry>
- <entry><option>-fnowarn-missing-import-lists</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-missing-methods</option></entry>
- <entry>warn when class methods are undefined</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-missing-methods</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-missing-signatures</option></entry>
- <entry>warn about top-level functions without signatures</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-missing-signatures</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-missing-local-sigs</option></entry>
- <entry>warn about polymorphic local bindings without signatures</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-missing-local-sigs</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-monomorphism-restriction</option></entry>
- <entry>warn when the Monomorphism Restriction is applied</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-monomorphism-restriction</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-name-shadowing</option></entry>
- <entry>warn when names are shadowed</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-name-shadowing</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-orphans</option></entry>
- <entry>warn when the module contains <link linkend="orphan-modules">orphan instance declarations
- or rewrite rules</link></entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-orphans</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-overlapping-patterns</option></entry>
- <entry>warn about overlapping patterns</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-overlapping-patterns</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-tabs</option></entry>
- <entry>warn if there are tabs in the source file</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-tabs</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-type-defaults</option></entry>
- <entry>warn when defaulting happens</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-type-defaults</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-unrecognised-pragmas</option></entry>
- <entry>warn about uses of pragmas that GHC doesn't recognise</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-unrecognised-pragmas</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-unused-binds</option></entry>
- <entry>warn about bindings that are unused</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-unused-binds</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-unused-imports</option></entry>
- <entry>warn about unnecessary imports</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-unused-imports</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-unused-matches</option></entry>
- <entry>warn about variables in patterns that aren't used</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-unused-matches</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-unused-do-bind</option></entry>
- <entry>warn about do bindings that appear to throw away values of types other than <literal>()</literal></entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-unused-do-bind</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-wrong-do-bind</option></entry>
- <entry>warn about do bindings that appear to throw away monadic values that you should have bound instead</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-wrong-do-bind</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-unsafe</option></entry>
- <entry>warn if the module being compiled is regarded to be unsafe.
- Should be used to check the safety status of modules when using safe
- inference.</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-unsafe</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-safe</option></entry>
- <entry>warn if the module being compiled is regarded to be safe.
- Should be used to check the safety status of modules when using safe
- inference.</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-safe</option></entry>
- </row>
-
- <row>
- <entry><option>-fwarn-warnings-deprecations</option></entry>
- <entry>warn about uses of functions &amp; types that have warnings or deprecated pragmas</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-warn-warnings-deprecations</option></entry>
- </row>
-
- </tbody>
- </tgroup>
- </informaltable>
-
- </sect2>
- <sect2>
- <title>Optimisation levels</title>
-
- <para><xref linkend="options-optimise"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-O</option></entry>
- <entry>Enable default optimisation (level 1)</entry>
- <entry>dynamic</entry>
- <entry><option>-O0</option></entry>
- </row>
- <row>
- <entry><option>-O</option><replaceable>n</replaceable></entry>
- <entry>Set optimisation level <replaceable>n</replaceable></entry>
- <entry>dynamic</entry>
- <entry><option>-O0</option></entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
-
- </sect2>
- <sect2>
- <title>Individual optimisations</title>
-
- <para><xref linkend="options-f"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-fcase-merge</option></entry>
- <entry>Enable case-merging. Implied by <option>-O</option>.</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-case-merge</option></entry>
- </row>
-
- <row>
- <entry><option>-fcse</option></entry>
- <entry>Turn on common sub-expression elimination. Implied by <option>-O</option>.</entry>
- <entry>dynamic</entry>
- <entry>-fno-cse</entry>
- </row>
-
- <row>
- <entry><option>-fdicts-strict</option></entry>
- <entry>Make dictionaries strict</entry>
- <entry>static</entry>
- <entry><option>-fno-dicts-strict</option></entry>
- </row>
-
- <row>
- <entry><option>-fdo-eta-reduction</option></entry>
- <entry>Enable eta-reduction. Implied by <option>-O</option>.</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-do-eta-reduction</option></entry>
- </row>
-
- <row>
- <entry><option>-fdo-lambda-eta-expansion</option></entry>
- <entry>Enable lambda eta-reduction</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-do-lambda-eta-expansion</option></entry>
- </row>
-
- <row>
- <entry><option>-feager-blackholing</option></entry>
- <entry>Turn on <link linkend="parallel-compile-options">eager blackholing</link></entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
-
- <row>
- <entry><option>-fenable-rewrite-rules</option></entry>
- <entry>Switch on all rewrite rules (including rules
- generated by automatic specialisation of overloaded functions).
- Implied by <option>-O</option>. </entry>
- <entry>dynamic</entry>
- <entry><option>-fno-enable-rewrite-rules</option></entry>
- </row>
-
- <row>
- <entry><option>-fexcess-precision</option></entry>
- <entry>Enable excess intermediate precision</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-excess-precision</option></entry>
- </row>
-
- <row>
- <entry><option>-ffloat-in</option></entry>
- <entry>Turn on the float-in transformation. Implied by <option>-O</option>.</entry>
- <entry>dynamic</entry>
- <entry>-fno-float-in</entry>
- </row>
-
- <row>
- <entry><option>-ffull-laziness</option></entry>
- <entry>Turn on full laziness (floating bindings outwards). Implied by <option>-O</option>.</entry>
- <entry>dynamic</entry>
- <entry>-fno-full-laziness</entry>
- </row>
-
- <row>
- <entry><option>-fignore-asserts</option></entry>
- <entry>Ignore assertions in the source</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-ignore-asserts</option></entry>
- </row>
-
- <row>
- <entry><option>-fignore-interface-pragmas</option></entry>
- <entry>Ignore pragmas in interface files</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-ignore-interface-pragmas</option></entry>
- </row>
-
- <row>
- <entry><option>-fliberate-case</option></entry>
- <entry>Turn on the liberate-case transformation. Implied by <option>-O2</option>.</entry>
- <entry>dynamic</entry>
- <entry>-fno-liberate-case</entry>
- </row>
-
- <row>
- <entry><option>-fliberate-case-threshold</option>=<replaceable>n</replaceable></entry>
- <entry>Set the size threshold for the liberate-case transformation to <replaceable>n</replaceable> (default: 200)</entry>
- <entry>static</entry>
- <entry><option>-fno-liberate-case-threshold</option></entry>
- </row>
-
- <row>
- <entry><option>-fmax-simplifier-iterations</option></entry>
- <entry>Set the max iterations for the simplifier</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
-
- <row>
- <entry><option>-fmax-worker-args</option></entry>
- <entry>If a worker has that many arguments, none will be
- unpacked anymore (default: 10)</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
-
- <row>
- <entry><option>-fno-opt-coercion</option></entry>
- <entry>Turn off the coercion optimiser</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
-
- <row>
- <entry><option>-fno-pre-inlining</option></entry>
- <entry>Turn off pre-inlining</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
-
- <row>
- <entry><option>-fno-state-hack</option></entry>
- <entry>Turn 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.</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
-
- <row>
- <entry><option>-fpedantic-bottoms</option></entry>
- <entry>Make GHC be more precise about its treatment of bottom (but see also
- <option>-fno-state-hack</option>). In particular, GHC will not
- eta-expand through a case expression.</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-pedantic-bottoms</option></entry>
- </row>
-
- <row>
- <entry><option>-fomit-interface-pragmas</option></entry>
- <entry>Don't generate interface pragmas</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-omit-interface-pragmas</option></entry>
- </row>
-
- <row>
- <entry><option>-fsimplifier-phases</option></entry>
- <entry>Set the number of phases for the simplifier (default 2).
+ </row>
+
+ <row>
+ <entry><option>-fwarn-missing-fields</option></entry>
+ <entry>warn when fields of a record are uninitialised</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-missing-fields</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-missing-import-lists</option></entry>
+ <entry>warn when an import declaration does not explicitly
+ list all the names brought into scope</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fnowarn-missing-import-lists</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-missing-methods</option></entry>
+ <entry>warn when class methods are undefined</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-missing-methods</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-missing-signatures</option></entry>
+ <entry>warn about top-level functions without signatures</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-missing-signatures</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-missing-local-sigs</option></entry>
+ <entry>warn about polymorphic local bindings without signatures</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-missing-local-sigs</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-monomorphism-restriction</option></entry>
+ <entry>warn when the Monomorphism Restriction is applied</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-monomorphism-restriction</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-name-shadowing</option></entry>
+ <entry>warn when names are shadowed</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-name-shadowing</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-orphans</option></entry>
+ <entry>warn when the module contains <link linkend="orphan-modules">orphan instance declarations
+ or rewrite rules</link></entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-orphans</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-overlapping-patterns</option></entry>
+ <entry>warn about overlapping patterns</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-overlapping-patterns</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-tabs</option></entry>
+ <entry>warn if there are tabs in the source file</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-tabs</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-type-defaults</option></entry>
+ <entry>warn when defaulting happens</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-type-defaults</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-unrecognised-pragmas</option></entry>
+ <entry>warn about uses of pragmas that GHC doesn't recognise</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-unrecognised-pragmas</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-unused-binds</option></entry>
+ <entry>warn about bindings that are unused</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-unused-binds</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-unused-imports</option></entry>
+ <entry>warn about unnecessary imports</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-unused-imports</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-unused-matches</option></entry>
+ <entry>warn about variables in patterns that aren't used</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-unused-matches</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-unused-do-bind</option></entry>
+ <entry>warn about do bindings that appear to throw away values of types other than <literal>()</literal></entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-unused-do-bind</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-wrong-do-bind</option></entry>
+ <entry>warn about do bindings that appear to throw away monadic values that you should have bound instead</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-wrong-do-bind</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-unsafe</option></entry>
+ <entry>warn if the module being compiled is regarded to be unsafe.
+ Should be used to check the safety status of modules when using safe
+ inference.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-unsafe</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-safe</option></entry>
+ <entry>warn if the module being compiled is regarded to be safe.
+ Should be used to check the safety status of modules when using safe
+ inference.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-safe</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fwarn-warnings-deprecations</option></entry>
+ <entry>warn about uses of functions &amp; types that have warnings or deprecated pragmas</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-warn-warnings-deprecations</option></entry>
+ </row>
+
+ </tbody>
+ </tgroup>
+ </informaltable>
+
+ </sect2>
+ <sect2>
+ <title>Optimisation levels</title>
+
+ <para><xref linkend="options-optimise"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-O</option></entry>
+ <entry>Enable default optimisation (level 1)</entry>
+ <entry>dynamic</entry>
+ <entry><option>-O0</option></entry>
+ </row>
+ <row>
+ <entry><option>-O</option><replaceable>n</replaceable></entry>
+ <entry>Set optimisation level <replaceable>n</replaceable></entry>
+ <entry>dynamic</entry>
+ <entry><option>-O0</option></entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+
+ </sect2>
+ <sect2>
+ <title>Individual optimisations</title>
+
+ <para><xref linkend="options-f"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-fcase-merge</option></entry>
+ <entry>Enable case-merging. Implied by <option>-O</option>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-case-merge</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fcse</option></entry>
+ <entry>Turn on common sub-expression elimination. Implied by <option>-O</option>.</entry>
+ <entry>dynamic</entry>
+ <entry>-fno-cse</entry>
+ </row>
+
+ <row>
+ <entry><option>-fdicts-strict</option></entry>
+ <entry>Make dictionaries strict</entry>
+ <entry>static</entry>
+ <entry><option>-fno-dicts-strict</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fdo-eta-reduction</option></entry>
+ <entry>Enable eta-reduction. Implied by <option>-O</option>.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-do-eta-reduction</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fdo-lambda-eta-expansion</option></entry>
+ <entry>Enable lambda eta-reduction</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-do-lambda-eta-expansion</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-feager-blackholing</option></entry>
+ <entry>Turn on <link linkend="parallel-compile-options">eager blackholing</link></entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+
+ <row>
+ <entry><option>-fenable-rewrite-rules</option></entry>
+ <entry>Switch on all rewrite rules (including rules
+ generated by automatic specialisation of overloaded functions).
+ Implied by <option>-O</option>. </entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-enable-rewrite-rules</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fexcess-precision</option></entry>
+ <entry>Enable excess intermediate precision</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-excess-precision</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-ffloat-in</option></entry>
+ <entry>Turn on the float-in transformation. Implied by <option>-O</option>.</entry>
+ <entry>dynamic</entry>
+ <entry>-fno-float-in</entry>
+ </row>
+
+ <row>
+ <entry><option>-ffull-laziness</option></entry>
+ <entry>Turn on full laziness (floating bindings outwards). Implied by <option>-O</option>.</entry>
+ <entry>dynamic</entry>
+ <entry>-fno-full-laziness</entry>
+ </row>
+
+ <row>
+ <entry><option>-fignore-asserts</option></entry>
+ <entry>Ignore assertions in the source</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-ignore-asserts</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fignore-interface-pragmas</option></entry>
+ <entry>Ignore pragmas in interface files</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-ignore-interface-pragmas</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fliberate-case</option></entry>
+ <entry>Turn on the liberate-case transformation. Implied by <option>-O2</option>.</entry>
+ <entry>dynamic</entry>
+ <entry>-fno-liberate-case</entry>
+ </row>
+
+ <row>
+ <entry><option>-fliberate-case-threshold</option>=<replaceable>n</replaceable></entry>
+ <entry>Set the size threshold for the liberate-case transformation to <replaceable>n</replaceable> (default: 200)</entry>
+ <entry>static</entry>
+ <entry><option>-fno-liberate-case-threshold</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fllvm-tbaa</option></entry>
+ <entry>Turn on Typed Based Alias Analysis information in the LLVM
+ backend. This enables more accurate and alias information in the LLVM
+ backend for better optimisation. (default: enabled)</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-llvm-tbaa</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fmax-simplifier-iterations</option></entry>
+ <entry>Set the max iterations for the simplifier</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+
+ <row>
+ <entry><option>-fmax-worker-args</option></entry>
+ <entry>If a worker has that many arguments, none will be
+ unpacked anymore (default: 10)</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+
+ <row>
+ <entry><option>-fno-opt-coercion</option></entry>
+ <entry>Turn off the coercion optimiser</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+
+ <row>
+ <entry><option>-fno-pre-inlining</option></entry>
+ <entry>Turn off pre-inlining</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+
+ <row>
+ <entry><option>-fno-state-hack</option></entry>
+ <entry>Turn 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.</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+
+ <row>
+ <entry><option>-fpedantic-bottoms</option></entry>
+ <entry>Make GHC be more precise about its treatment of bottom (but see also
+ <option>-fno-state-hack</option>). In particular, GHC will not
+ eta-expand through a case expression.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-pedantic-bottoms</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fomit-interface-pragmas</option></entry>
+ <entry>Don't generate interface pragmas</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-omit-interface-pragmas</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-freg-liveness</option></entry>
+ <entry>Track STG register liveness to avoid saving and restoring
+ dead registers, as well as freeing the dead ones for use in
+ intermediate code. (LLVM backend only, default: enabled).
+
+ Traditionally GHC has reserved a set of machine registers for the
+ exclusive use of storing a stack pointer, heap pointer and
+ general purpose function argument registers (these are the so
+ called STG registers). This optimisation tracks the liveness of
+ the machine registers the STG registers are mapped to so that the
+ machine register can be used for other purposes when the STG
+ register are dead.</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-reg-liveness</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fsimplifier-phases</option></entry>
+ <entry>Set the number of phases for the simplifier (default 2).
Ignored with <option>-O0</option>.</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
-
- <row>
- <entry><option>-fsimpl-tick-factor=<replaceable>n</replaceable></option></entry>
- <entry>Set the percentage factor for simplifier ticks (default 100)</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
-
- <row>
- <entry><option>-fspec-constr</option></entry>
- <entry>Turn on the SpecConstr transformation. Implied by <option>-O2</option>.</entry>
- <entry>dynamic</entry>
- <entry>-fno-spec-constr</entry>
- </row>
-
- <row>
- <entry><option>-fspec-constr-threshold</option>=<replaceable>n</replaceable></entry>
- <entry>Set the size threshold for the SpecConstr transformation to <replaceable>n</replaceable> (default: 200)</entry>
- <entry>static</entry>
- <entry><option>-fno-spec-constr-threshold</option></entry>
- </row>
-
- <row>
- <entry><option>-fspec-constr-count</option>=<replaceable>n</replaceable></entry>
- <entry>Set to <replaceable>n</replaceable> (default: 3) the maximum number of
- specialisations that will be created for any one function
- by the SpecConstr transformation</entry>
- <entry>static</entry>
- <entry><option>-fno-spec-constr-count</option></entry>
- </row>
-
- <row>
- <entry><option>-fspecialise</option></entry>
- <entry>Turn on specialisation of overloaded functions. Implied by <option>-O</option>.</entry>
- <entry>dynamic</entry>
- <entry>-fno-specialise</entry>
- </row>
-
- <row>
- <entry><option>-fstrictness</option></entry>
- <entry>Turn on strictness analysis. Implied by <option>-O</option>.</entry>
- <entry>dynamic</entry>
- <entry>-fno-strictness</entry>
- </row>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
- <row>
- <entry><option>-fstrictness=before</option>=<replaceable>n</replaceable></entry>
- <entry>Run an additional strictness analysis before simplifier
-phase <replaceable>n</replaceable></entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
+ <row>
+ <entry><option>-fsimpl-tick-factor=<replaceable>n</replaceable></option></entry>
+ <entry>Set the percentage factor for simplifier ticks (default 100)</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+
+ <row>
+ <entry><option>-fspec-constr</option></entry>
+ <entry>Turn on the SpecConstr transformation. Implied by <option>-O2</option>.</entry>
+ <entry>dynamic</entry>
+ <entry>-fno-spec-constr</entry>
+ </row>
+
+ <row>
+ <entry><option>-fspec-constr-threshold</option>=<replaceable>n</replaceable></entry>
+ <entry>Set the size threshold for the SpecConstr transformation to <replaceable>n</replaceable> (default: 200)</entry>
+ <entry>static</entry>
+ <entry><option>-fno-spec-constr-threshold</option></entry>
+ </row>
- <row>
- <entry><option>-fstatic-argument-transformation</option></entry>
- <entry>Turn on the static argument transformation. Implied by <option>-O2</option>.</entry>
- <entry>dynamic</entry>
- <entry>-fno-static-argument-transformation</entry>
- </row>
-
- <row>
- <entry><option>-funbox-strict-fields</option></entry>
- <entry>Flatten strict constructor fields</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-unbox-strict-fields</option></entry>
- </row>
-
- <row>
- <entry><option>-funfolding-creation-threshold</option></entry>
- <entry>Tweak unfolding settings</entry>
- <entry>static</entry>
- <entry><option>-fno-unfolding-creation-threshold</option></entry>
- </row>
-
- <row>
- <entry><option>-funfolding-fun-discount</option></entry>
- <entry>Tweak unfolding settings</entry>
- <entry>static</entry>
- <entry><option>-fno-unfolding-fun-discount</option></entry>
- </row>
-
- <row>
- <entry><option>-funfolding-keeness-factor</option></entry>
- <entry>Tweak unfolding settings</entry>
- <entry>static</entry>
- <entry><option>-fno-unfolding-keeness-factor</option></entry>
- </row>
-
- <row>
- <entry><option>-funfolding-use-threshold</option></entry>
- <entry>Tweak unfolding settings</entry>
- <entry>static</entry>
- <entry><option>-fno-unfolding-use-threshold</option></entry>
- </row>
-
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
-
- <sect2>
- <title>Profiling options</title>
-
- <para><xref linkend="profiling"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-prof</option></entry>
- <entry>Turn on profiling</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-fprof-auto</option></entry>
- <entry>Auto-add <literal>SCC</literal>s to all bindings
+ <row>
+ <entry><option>-fspec-constr-count</option>=<replaceable>n</replaceable></entry>
+ <entry>Set to <replaceable>n</replaceable> (default: 3) the maximum number of
+ specialisations that will be created for any one function
+ by the SpecConstr transformation</entry>
+ <entry>static</entry>
+ <entry><option>-fno-spec-constr-count</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-fspecialise</option></entry>
+ <entry>Turn on specialisation of overloaded functions. Implied by <option>-O</option>.</entry>
+ <entry>dynamic</entry>
+ <entry>-fno-specialise</entry>
+ </row>
+
+ <row>
+ <entry><option>-fstrictness</option></entry>
+ <entry>Turn on strictness analysis. Implied by <option>-O</option>.</entry>
+ <entry>dynamic</entry>
+ <entry>-fno-strictness</entry>
+ </row>
+
+ <row>
+ <entry><option>-fstrictness=before</option>=<replaceable>n</replaceable></entry>
+ <entry>Run an additional strictness analysis before simplifier
+ phase <replaceable>n</replaceable></entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+
+ <row>
+ <entry><option>-fstatic-argument-transformation</option></entry>
+ <entry>Turn on the static argument transformation. Implied by <option>-O2</option>.</entry>
+ <entry>dynamic</entry>
+ <entry>-fno-static-argument-transformation</entry>
+ </row>
+
+ <row>
+ <entry><option>-funbox-strict-fields</option></entry>
+ <entry>Flatten strict constructor fields</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-unbox-strict-fields</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-funfolding-creation-threshold</option></entry>
+ <entry>Tweak unfolding settings</entry>
+ <entry>static</entry>
+ <entry><option>-fno-unfolding-creation-threshold</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-funfolding-fun-discount</option></entry>
+ <entry>Tweak unfolding settings</entry>
+ <entry>static</entry>
+ <entry><option>-fno-unfolding-fun-discount</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-funfolding-keeness-factor</option></entry>
+ <entry>Tweak unfolding settings</entry>
+ <entry>static</entry>
+ <entry><option>-fno-unfolding-keeness-factor</option></entry>
+ </row>
+
+ <row>
+ <entry><option>-funfolding-use-threshold</option></entry>
+ <entry>Tweak unfolding settings</entry>
+ <entry>static</entry>
+ <entry><option>-fno-unfolding-use-threshold</option></entry>
+ </row>
+
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+
+ <sect2>
+ <title>Profiling options</title>
+
+ <para><xref linkend="profiling"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-prof</option></entry>
+ <entry>Turn on profiling</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-fprof-auto</option></entry>
+ <entry>Auto-add <literal>SCC</literal>s to all bindings
not marked INLINE</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-prof-auto</option></entry>
- </row>
- <row>
- <entry><option>-fprof-auto-top</option></entry>
- <entry>Auto-add <literal>SCC</literal>s to all top-level
+ <entry>dynamic</entry>
+ <entry><option>-fno-prof-auto</option></entry>
+ </row>
+ <row>
+ <entry><option>-fprof-auto-top</option></entry>
+ <entry>Auto-add <literal>SCC</literal>s to all top-level
bindings not marked INLINE</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-prof-auto</option></entry>
- </row>
- <row>
- <entry><option>-fprof-auto-exported</option></entry>
- <entry>Auto-add <literal>SCC</literal>s to all exported
+ <entry>dynamic</entry>
+ <entry><option>-fno-prof-auto</option></entry>
+ </row>
+ <row>
+ <entry><option>-fprof-auto-exported</option></entry>
+ <entry>Auto-add <literal>SCC</literal>s to all exported
bindings not marked INLINE</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-prof-auto</option></entry>
- </row>
- <row>
- <entry><option>-fprof-cafs</option></entry>
- <entry>Auto-add <literal>SCC</literal>s to all CAFs</entry>
- <entry>dynamic</entry>
- <entry><option>-fno-prof-cafs</option></entry>
- </row>
- <row>
- <entry><option>-fno-prof-count-entries</option></entry>
- <entry>Do not collect entry counts</entry>
- <entry>dynamic</entry>
- <entry><option>-fprof-count-entries</option></entry>
- </row>
- <row>
- <entry><option>-ticky</option></entry>
- <entry><link linkend="ticky-ticky">Turn on ticky-ticky profiling</link></entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
-
- <sect2>
- <title>Program coverage options</title>
-
- <para><xref linkend="hpc"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-fhpc</option></entry>
- <entry>Turn on Haskell program coverage instrumentation</entry>
- <entry>static</entry>
- <entry><option>-</option></entry>
- </row>
- <row>
- <entry><option>-hpcdir dir</option></entry>
- <entry>Directory to deposit .mix files during compilation (default is .hpc)</entry>
- <entry>dynamic</entry>
- <entry><option>-</option></entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
-
- <sect2>
- <title>Haskell pre-processor options</title>
-
- <para><xref linkend="pre-processor"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-F</option></entry>
- <entry>
- Enable the use of a pre-processor
- (set with <option>-pgmF</option>)
- </entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
-
- <sect2>
- <title>C pre-processor options</title>
-
- <para><xref linkend="c-pre-processor"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-cpp</option></entry>
- <entry>Run the C pre-processor on Haskell source files</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-D</option><replaceable>symbol</replaceable><optional>=<replaceable>value</replaceable></optional></entry>
- <entry>Define a symbol in the C pre-processor</entry>
- <entry>dynamic</entry>
- <entry><option>-U</option><replaceable>symbol</replaceable></entry>
- </row>
- <row>
- <entry><option>-U</option><replaceable>symbol</replaceable></entry>
- <entry>Undefine a symbol in the C pre-processor</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-I</option><replaceable>dir</replaceable></entry>
- <entry>Add <replaceable>dir</replaceable> to the
- directory search list for <literal>#include</literal> files</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
-
- <sect2>
- <title>Code generation options</title>
-
- <para><xref linkend="options-codegen"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-fasm</option></entry>
- <entry>Use the <link linkend="native-code-gen">native code
- generator</link></entry>
- <entry>dynamic</entry>
- <entry>-fllvm</entry>
- </row>
- <row>
- <entry><option>-fllvm</option></entry>
- <entry>Compile using the <link linkend="llvm-code-gen">LLVM code
- generator</link></entry>
- <entry>dynamic</entry>
- <entry>-fasm</entry>
- </row>
- <row>
- <entry><option>-fno-code</option></entry>
- <entry>Omit code generation</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-fbyte-code</option></entry>
- <entry>Generate byte-code</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-fobject-code</option></entry>
- <entry>Generate object code</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
-
- <sect2>
- <title>Linking options</title>
-
- <para><xref linkend="options-linker"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-shared</option></entry>
- <entry>Generate a shared library (as opposed to an executable)</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-fPIC</option></entry>
- <entry>Generate position-independent code (where available)</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dynamic</option></entry>
- <entry>Use dynamic Haskell libraries (if available)</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dynload</option></entry>
- <entry>Selects one of a number of modes for finding shared
- libraries at runtime.</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-framework</option> <replaceable>name</replaceable></entry>
- <entry>On Darwin/MacOS X only, link in the framework <replaceable>name</replaceable>.
- This option corresponds to the <option>-framework</option> option for Apple's Linker.</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-framework-path</option> <replaceable>name</replaceable></entry>
- <entry>On Darwin/MacOS X only, add <replaceable>dir</replaceable> to the list of
- directories searched for frameworks.
- This option corresponds to the <option>-F</option> option for Apple's Linker.</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-l</option><replaceable>lib</replaceable></entry>
- <entry>Link in library <replaceable>lib</replaceable></entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-L</option><replaceable>dir</replaceable></entry>
- <entry>Add <replaceable>dir</replaceable> to the list of
- directories searched for libraries</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-main-is</option></entry>
- <entry>Set main module and function</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>--mk-dll</option></entry>
- <entry>DLL-creation mode (Windows only)</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-no-hs-main</option></entry>
- <entry>Don't assume this program contains <literal>main</literal></entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-rtsopts</option>, <option>-rtsopts={none,some,all}</option></entry>
- <entry>Control whether the RTS behaviour can be tweaked via command-line
- flags and the <literal>GHCRTS</literal> environment
- variable. Using <literal>none</literal> means no RTS flags can be given; <literal>some</literal> means only a minimum of safe options can be given (the default), and <literal>all</literal> (or no argument at all) means that all RTS flags are permitted.</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-with-rtsopts=<replaceable>opts</replaceable></option></entry>
- <entry>Set the default RTS options to
- <replaceable>opts</replaceable>.</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-no-link</option></entry>
- <entry>Omit linking</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-split-objs</option></entry>
- <entry>Split objects (for libraries)</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-static</option></entry>
- <entry>Use static Haskell libraries</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-threaded</option></entry>
- <entry>Use the threaded runtime</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-debug</option></entry>
- <entry>Use the debugging runtime</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-eventlog</option></entry>
- <entry>Enable runtime event tracing</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-fno-gen-manifest</option></entry>
- <entry>Do not generate a manifest file (Windows only)</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-fno-embed-manifest</option></entry>
- <entry>Do not embed the manifest in the executable (Windows only)</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-fno-shared-implib</option></entry>
- <entry>Don't generate an import library for a DLL (Windows only)</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dylib-install-name</option> <replaceable>path</replaceable></entry>
- <entry>Set the install name (via <literal>-install_name</literal> passed to Apple's
+ <entry>dynamic</entry>
+ <entry><option>-fno-prof-auto</option></entry>
+ </row>
+ <row>
+ <entry><option>-fprof-cafs</option></entry>
+ <entry>Auto-add <literal>SCC</literal>s to all CAFs</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fno-prof-cafs</option></entry>
+ </row>
+ <row>
+ <entry><option>-fno-prof-count-entries</option></entry>
+ <entry>Do not collect entry counts</entry>
+ <entry>dynamic</entry>
+ <entry><option>-fprof-count-entries</option></entry>
+ </row>
+ <row>
+ <entry><option>-ticky</option></entry>
+ <entry><link linkend="ticky-ticky">Turn on ticky-ticky profiling</link></entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+
+ <sect2>
+ <title>Program coverage options</title>
+
+ <para><xref linkend="hpc"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-fhpc</option></entry>
+ <entry>Turn on Haskell program coverage instrumentation</entry>
+ <entry>static</entry>
+ <entry><option>-</option></entry>
+ </row>
+ <row>
+ <entry><option>-hpcdir dir</option></entry>
+ <entry>Directory to deposit .mix files during compilation (default is .hpc)</entry>
+ <entry>dynamic</entry>
+ <entry><option>-</option></entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+
+ <sect2>
+ <title>Haskell pre-processor options</title>
+
+ <para><xref linkend="pre-processor"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-F</option></entry>
+ <entry>
+ Enable the use of a pre-processor
+ (set with <option>-pgmF</option>)
+ </entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+
+ <sect2>
+ <title>C pre-processor options</title>
+
+ <para><xref linkend="c-pre-processor"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-cpp</option></entry>
+ <entry>Run the C pre-processor on Haskell source files</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-D</option><replaceable>symbol</replaceable><optional>=<replaceable>value</replaceable></optional></entry>
+ <entry>Define a symbol in the C pre-processor</entry>
+ <entry>dynamic</entry>
+ <entry><option>-U</option><replaceable>symbol</replaceable></entry>
+ </row>
+ <row>
+ <entry><option>-U</option><replaceable>symbol</replaceable></entry>
+ <entry>Undefine a symbol in the C pre-processor</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-I</option><replaceable>dir</replaceable></entry>
+ <entry>Add <replaceable>dir</replaceable> to the
+ directory search list for <literal>#include</literal> files</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+
+ <sect2>
+ <title>Code generation options</title>
+
+ <para><xref linkend="options-codegen"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-fasm</option></entry>
+ <entry>Use the <link linkend="native-code-gen">native code
+ generator</link></entry>
+ <entry>dynamic</entry>
+ <entry>-fllvm</entry>
+ </row>
+ <row>
+ <entry><option>-fllvm</option></entry>
+ <entry>Compile using the <link linkend="llvm-code-gen">LLVM code
+ generator</link></entry>
+ <entry>dynamic</entry>
+ <entry>-fasm</entry>
+ </row>
+ <row>
+ <entry><option>-fno-code</option></entry>
+ <entry>Omit code generation</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-fbyte-code</option></entry>
+ <entry>Generate byte-code</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-fobject-code</option></entry>
+ <entry>Generate object code</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+
+ <sect2>
+ <title>Linking options</title>
+
+ <para><xref linkend="options-linker"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-shared</option></entry>
+ <entry>Generate a shared library (as opposed to an executable)</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-fPIC</option></entry>
+ <entry>Generate position-independent code (where available)</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dynamic</option></entry>
+ <entry>Use dynamic Haskell libraries (if available)</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dynload</option></entry>
+ <entry>Selects one of a number of modes for finding shared
+ libraries at runtime.</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-framework</option> <replaceable>name</replaceable></entry>
+ <entry>On Darwin/MacOS X only, link in the framework <replaceable>name</replaceable>.
+ This option corresponds to the <option>-framework</option> option for Apple's Linker.</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-framework-path</option> <replaceable>name</replaceable></entry>
+ <entry>On Darwin/MacOS X only, add <replaceable>dir</replaceable> to the list of
+ directories searched for frameworks.
+ This option corresponds to the <option>-F</option> option for Apple's Linker.</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-l</option><replaceable>lib</replaceable></entry>
+ <entry>Link in library <replaceable>lib</replaceable></entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-L</option><replaceable>dir</replaceable></entry>
+ <entry>Add <replaceable>dir</replaceable> to the list of
+ directories searched for libraries</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-main-is</option></entry>
+ <entry>Set main module and function</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>--mk-dll</option></entry>
+ <entry>DLL-creation mode (Windows only)</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-no-hs-main</option></entry>
+ <entry>Don't assume this program contains <literal>main</literal></entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-rtsopts</option>, <option>-rtsopts={none,some,all}</option></entry>
+ <entry>Control whether the RTS behaviour can be tweaked via command-line
+ flags and the <literal>GHCRTS</literal> environment
+ variable. Using <literal>none</literal> means no RTS flags can be given; <literal>some</literal> means only a minimum of safe options can be given (the default), and <literal>all</literal> (or no argument at all) means that all RTS flags are permitted.</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-with-rtsopts=<replaceable>opts</replaceable></option></entry>
+ <entry>Set the default RTS options to
+ <replaceable>opts</replaceable>.</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-no-link</option></entry>
+ <entry>Omit linking</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-split-objs</option></entry>
+ <entry>Split objects (for libraries)</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-static</option></entry>
+ <entry>Use static Haskell libraries</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-threaded</option></entry>
+ <entry>Use the threaded runtime</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-debug</option></entry>
+ <entry>Use the debugging runtime</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-eventlog</option></entry>
+ <entry>Enable runtime event tracing</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-fno-gen-manifest</option></entry>
+ <entry>Do not generate a manifest file (Windows only)</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-fno-embed-manifest</option></entry>
+ <entry>Do not embed the manifest in the executable (Windows only)</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-fno-shared-implib</option></entry>
+ <entry>Don't generate an import library for a DLL (Windows only)</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dylib-install-name</option> <replaceable>path</replaceable></entry>
+ <entry>Set the install name (via <literal>-install_name</literal> 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/MacOS X only)</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
-
- <sect2>
- <title>Plugin options</title>
-
- <para><xref linkend="compiler-plugins"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-fplugin</option>=<replaceable>module</replaceable></entry>
- <entry>Load a plugin exported by a given module</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-fplugin-opt</option>=<replaceable>module:args</replaceable></entry>
- <entry>Give arguments to a plugin module; module must be specified with <option>-fplugin</option></entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
-
-
- <sect2>
- <title>Replacing phases</title>
-
- <para><xref linkend="replacing-phases"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-pgmL</option> <replaceable>cmd</replaceable></entry>
- <entry>Use <replaceable>cmd</replaceable> as the literate pre-processor</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-pgmP</option> <replaceable>cmd</replaceable></entry>
- <entry>Use <replaceable>cmd</replaceable> as the C
- pre-processor (with <option>-cpp</option> only)</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-pgmc</option> <replaceable>cmd</replaceable></entry>
- <entry>Use <replaceable>cmd</replaceable> as the C compiler</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- <row>
- <entry><option>-pgmlo</option> <replaceable>cmd</replaceable></entry>
- <entry>Use <replaceable>cmd</replaceable> as the LLVM optimiser</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-pgmlc</option> <replaceable>cmd</replaceable></entry>
- <entry>Use <replaceable>cmd</replaceable> as the LLVM compiler</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- </row>
- <row>
- <entry><option>-pgms</option> <replaceable>cmd</replaceable></entry>
- <entry>Use <replaceable>cmd</replaceable> as the splitter</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-pgma</option> <replaceable>cmd</replaceable></entry>
- <entry>Use <replaceable>cmd</replaceable> as the assembler</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-pgml</option> <replaceable>cmd</replaceable></entry>
- <entry>Use <replaceable>cmd</replaceable> as the linker</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-pgmdll</option> <replaceable>cmd</replaceable></entry>
- <entry>Use <replaceable>cmd</replaceable> as the DLL generator</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-pgmF</option> <replaceable>cmd</replaceable></entry>
- <entry>Use <replaceable>cmd</replaceable> as the pre-processor
- (with <option>-F</option> only)</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-pgmwindres</option> <replaceable>cmd</replaceable></entry>
- <entry>Use <replaceable>cmd</replaceable> as the program for
- embedding manifests on Windows.</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
- <indexterm><primary><option>-pgmL</option></primary></indexterm>
- <indexterm><primary><option>-pgmP</option></primary></indexterm>
- <indexterm><primary><option>-pgmc</option></primary></indexterm>
- <indexterm><primary><option>-pgmlo</option></primary></indexterm>
- <indexterm><primary><option>-pgmlc</option></primary></indexterm>
- <indexterm><primary><option>-pgma</option></primary></indexterm>
- <indexterm><primary><option>-pgml</option></primary></indexterm>
- <indexterm><primary><option>-pgmdll</option></primary></indexterm>
- <indexterm><primary><option>-pgmF</option></primary></indexterm>
-
- </sect2>
-
- <sect2>
- <title>Forcing options to particular phases</title>
-
- <para><xref linkend="forcing-options-through"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-optL</option> <replaceable>option</replaceable></entry>
- <entry>pass <replaceable>option</replaceable> to the literate pre-processor</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-optP</option> <replaceable>option</replaceable></entry>
- <entry>pass <replaceable>option</replaceable> to cpp (with
- <option>-cpp</option> only)</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-optF</option> <replaceable>option</replaceable></entry>
- <entry>pass <replaceable>option</replaceable> to the
- custom pre-processor</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-optc</option> <replaceable>option</replaceable></entry>
- <entry>pass <replaceable>option</replaceable> to the C compiler</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-optlo</option> <replaceable>option</replaceable></entry>
- <entry>pass <replaceable>option</replaceable> to the LLVM optimiser</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-optlc</option> <replaceable>option</replaceable></entry>
- <entry>pass <replaceable>option</replaceable> to the LLVM compiler</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-optm</option> <replaceable>option</replaceable></entry>
- <entry>pass <replaceable>option</replaceable> to the mangler</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-opta</option> <replaceable>option</replaceable></entry>
- <entry>pass <replaceable>option</replaceable> to the assembler</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-optl</option> <replaceable>option</replaceable></entry>
- <entry>pass <replaceable>option</replaceable> to the linker</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-optdll</option> <replaceable>option</replaceable></entry>
- <entry>pass <replaceable>option</replaceable> to the DLL generator</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-optwindres</option> <replaceable>option</replaceable></entry>
- <entry>pass <replaceable>option</replaceable> to <literal>windres</literal>.</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
-
- <sect2>
- <title>Platform-specific options</title>
-
- <para><xref linkend="options-platform"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+
+ <sect2>
+ <title>Plugin options</title>
+
+ <para><xref linkend="compiler-plugins"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-fplugin</option>=<replaceable>module</replaceable></entry>
+ <entry>Load a plugin exported by a given module</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-fplugin-opt</option>=<replaceable>module:args</replaceable></entry>
+ <entry>Give arguments to a plugin module; module must be specified with <option>-fplugin</option></entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+
+
+ <sect2>
+ <title>Replacing phases</title>
+
+ <para><xref linkend="replacing-phases"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-pgmL</option> <replaceable>cmd</replaceable></entry>
+ <entry>Use <replaceable>cmd</replaceable> as the literate pre-processor</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-pgmP</option> <replaceable>cmd</replaceable></entry>
+ <entry>Use <replaceable>cmd</replaceable> as the C
+ pre-processor (with <option>-cpp</option> only)</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-pgmc</option> <replaceable>cmd</replaceable></entry>
+ <entry>Use <replaceable>cmd</replaceable> as the C compiler</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ <row>
+ <entry><option>-pgmlo</option> <replaceable>cmd</replaceable></entry>
+ <entry>Use <replaceable>cmd</replaceable> as the LLVM optimiser</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
<row>
- <entry><option>-msse2</option></entry>
- <entry>(x86 only) Use SSE2 for floating point</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
+ <entry><option>-pgmlc</option> <replaceable>cmd</replaceable></entry>
+ <entry>Use <replaceable>cmd</replaceable> as the LLVM compiler</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
</row>
- </tbody>
- <tbody>
- <row>
- <entry><option>-monly-[432]-regs</option></entry>
- <entry>(x86 only) give some registers back to the C compiler</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
-
-
- <sect2>
- <title>External core file options</title>
-
- <para><xref linkend="ext-core"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-fext-core</option></entry>
- <entry>Generate <filename>.hcr</filename> external Core files</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
-
-
- <sect2>
- <title>Compiler debugging options</title>
-
- <para><xref linkend="options-debugging"/></para>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-dcore-lint</option></entry>
- <entry>Turn on internal sanity checking</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-to-file</option></entry>
- <entry>Dump to files instead of stdout</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-asm</option></entry>
- <entry>Dump assembly</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-bcos</option></entry>
- <entry>Dump interpreter byte code</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-cmm</option></entry>
- <entry>Dump C-- output</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-core-stats</option></entry>
- <entry>Print a one-line summary of the size of the Core program
- at the end of the optimisation pipeline </entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-cpranal</option></entry>
- <entry>Dump output from CPR analysis</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-cse</option></entry>
- <entry>Dump CSE output</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-deriv</option></entry>
- <entry>Dump deriving output</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-ds</option></entry>
- <entry>Dump desugarer output</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-flatC</option></entry>
- <entry>Dump &ldquo;flat&rdquo; C</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-foreign</option></entry>
- <entry>Dump <literal>foreign export</literal> stubs</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-hpc</option></entry>
- <entry>Dump after instrumentation for program coverage</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-inlinings</option></entry>
- <entry>Dump inlining info</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-llvm</option></entry>
- <entry>Dump LLVM intermediate code</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-occur-anal</option></entry>
- <entry>Dump occurrence analysis output</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-opt-cmm</option></entry>
- <entry>Dump the results of C-- to C-- optimising passes</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-parsed</option></entry>
- <entry>Dump parse tree</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-prep</option></entry>
- <entry>Dump prepared core</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-rn</option></entry>
- <entry>Dump renamer output</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-rule-firings</option></entry>
- <entry>Dump rule firing info</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-rule-rewrites</option></entry>
- <entry>Dump detailed rule firing info</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-rules</option></entry>
- <entry>Dump rules</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-vect</option></entry>
- <entry>Dump vectoriser input and output</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-simpl</option></entry>
- <entry>Dump final simplifier output</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-simpl-phases</option></entry>
- <entry>Dump output from each simplifier phase</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-simpl-iterations</option></entry>
- <entry>Dump output from each simplifier iteration</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-spec</option></entry>
- <entry>Dump specialiser output</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-splices</option></entry>
- <entry>Dump TH spliced expressions, and what they evaluate to</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-stg</option></entry>
- <entry>Dump final STG</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-stranal</option></entry>
- <entry>Dump strictness analyser output</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-tc</option></entry>
- <entry>Dump typechecker output</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-types</option></entry>
- <entry>Dump type signatures</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-worker-wrapper</option></entry>
- <entry>Dump worker-wrapper output</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-if-trace</option></entry>
- <entry>Trace interface files</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-tc-trace</option></entry>
- <entry>Trace typechecker</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-vt-trace</option></entry>
- <entry>Trace vectoriser</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-rn-trace</option></entry>
- <entry>Trace renamer</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-rn-stats</option></entry>
- <entry>Renamer stats</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-ddump-simpl-stats</option></entry>
- <entry>Dump simplifier stats</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dno-debug-output</option></entry>
- <entry>Suppress unsolicited debugging output</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dppr-debug</option></entry>
- <entry>Turn on debug printing (more verbose)</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dppr-noprags</option></entry>
- <entry>Don't output pragma info in dumps</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dppr-user-length</option></entry>
- <entry>Set the depth for printing expressions in error msgs</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dppr-colsNNN</option></entry>
- <entry>Set the width of debugging output. For example <option>-dppr-cols200</option></entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dppr-case-as-let</option></entry>
- <entry>Print single alternative case expressions as strict lets.</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dsuppress-all</option></entry>
- <entry>In core dumps, suppress everything that is suppressable.</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dsuppress-uniques</option></entry>
- <entry>Suppress the printing of uniques in debug output (easier to use <command>diff</command>)</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dsuppress-idinfo</option></entry>
- <entry>Suppress extended information about identifiers where they are bound</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dsuppress-module-prefixes</option></entry>
- <entry>Suppress the printing of module qualification prefixes</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dsuppress-type-signatures</option></entry>
- <entry>Suppress type signatures</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dsuppress-type-applications</option></entry>
- <entry>Suppress type applications</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dsuppress-coercions</option></entry>
- <entry>Suppress the printing of coercions in Core dumps to make them shorter</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dsource-stats</option></entry>
- <entry>Dump haskell source stats</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dcmm-lint</option></entry>
- <entry>C-- pass sanity checking</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dstg-lint</option></entry>
- <entry>STG pass sanity checking</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dstg-stats</option></entry>
- <entry>Dump STG stats</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dverbose-core2core</option></entry>
- <entry>Show output from each core-to-core pass</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dverbose-stg2stg</option></entry>
- <entry>Show output from each STG-to-STG pass</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dshow-passes</option></entry>
- <entry>Print out each pass name as it happens</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dfaststring-stats</option></entry>
- <entry>Show statistics for fast string usage when finished</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
-
- <sect2>
- <title>Misc compiler options</title>
-
- <informaltable>
- <tgroup cols="4" align="left" colsep="1" rowsep="1">
- <thead>
- <row>
- <entry>Flag</entry>
- <entry>Description</entry>
- <entry>Static/Dynamic</entry>
- <entry>Reverse</entry>
- </row>
- </thead>
- <tbody>
- <row>
- <entry><option>-fno-hi-version-check</option></entry>
- <entry>Don't complain about <literal>.hi</literal> file mismatches</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-dno-black-holing</option></entry>
- <entry>Turn off black holing (probably doesn't work)</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-fhistory-size</option></entry>
- <entry>Set simplification history size</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-funregisterised</option></entry>
- <entry><link linkend="unreg">Unregisterised</link> compilation (use <option>-unreg</option> instead)</entry>
- <entry>static</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-fno-ghci-history</option></entry>
- <entry>Do not use the load/store the GHCi command history from/to <literal>ghci_history</literal>.</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- <row>
- <entry><option>-fno-ghci-sandbox</option></entry>
- <entry>Turn off the GHCi sandbox. Means computations are run in the main thread, rather than a forked thread.</entry>
- <entry>dynamic</entry>
- <entry>-</entry>
- </row>
- </tbody>
- </tgroup>
- </informaltable>
- </sect2>
- </sect1>
+ </row>
+ <row>
+ <entry><option>-pgms</option> <replaceable>cmd</replaceable></entry>
+ <entry>Use <replaceable>cmd</replaceable> as the splitter</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-pgma</option> <replaceable>cmd</replaceable></entry>
+ <entry>Use <replaceable>cmd</replaceable> as the assembler</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-pgml</option> <replaceable>cmd</replaceable></entry>
+ <entry>Use <replaceable>cmd</replaceable> as the linker</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-pgmdll</option> <replaceable>cmd</replaceable></entry>
+ <entry>Use <replaceable>cmd</replaceable> as the DLL generator</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-pgmF</option> <replaceable>cmd</replaceable></entry>
+ <entry>Use <replaceable>cmd</replaceable> as the pre-processor
+ (with <option>-F</option> only)</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-pgmwindres</option> <replaceable>cmd</replaceable></entry>
+ <entry>Use <replaceable>cmd</replaceable> as the program for
+ embedding manifests on Windows.</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+ <indexterm><primary><option>-pgmL</option></primary></indexterm>
+ <indexterm><primary><option>-pgmP</option></primary></indexterm>
+ <indexterm><primary><option>-pgmc</option></primary></indexterm>
+ <indexterm><primary><option>-pgmlo</option></primary></indexterm>
+ <indexterm><primary><option>-pgmlc</option></primary></indexterm>
+ <indexterm><primary><option>-pgma</option></primary></indexterm>
+ <indexterm><primary><option>-pgml</option></primary></indexterm>
+ <indexterm><primary><option>-pgmdll</option></primary></indexterm>
+ <indexterm><primary><option>-pgmF</option></primary></indexterm>
+
+ </sect2>
+
+ <sect2>
+ <title>Forcing options to particular phases</title>
+
+ <para><xref linkend="forcing-options-through"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-optL</option> <replaceable>option</replaceable></entry>
+ <entry>pass <replaceable>option</replaceable> to the literate pre-processor</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-optP</option> <replaceable>option</replaceable></entry>
+ <entry>pass <replaceable>option</replaceable> to cpp (with
+ <option>-cpp</option> only)</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-optF</option> <replaceable>option</replaceable></entry>
+ <entry>pass <replaceable>option</replaceable> to the
+ custom pre-processor</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-optc</option> <replaceable>option</replaceable></entry>
+ <entry>pass <replaceable>option</replaceable> to the C compiler</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-optlo</option> <replaceable>option</replaceable></entry>
+ <entry>pass <replaceable>option</replaceable> to the LLVM optimiser</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-optlc</option> <replaceable>option</replaceable></entry>
+ <entry>pass <replaceable>option</replaceable> to the LLVM compiler</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-optm</option> <replaceable>option</replaceable></entry>
+ <entry>pass <replaceable>option</replaceable> to the mangler</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-opta</option> <replaceable>option</replaceable></entry>
+ <entry>pass <replaceable>option</replaceable> to the assembler</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-optl</option> <replaceable>option</replaceable></entry>
+ <entry>pass <replaceable>option</replaceable> to the linker</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-optdll</option> <replaceable>option</replaceable></entry>
+ <entry>pass <replaceable>option</replaceable> to the DLL generator</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-optwindres</option> <replaceable>option</replaceable></entry>
+ <entry>pass <replaceable>option</replaceable> to <literal>windres</literal>.</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+
+ <sect2>
+ <title>Platform-specific options</title>
+
+ <para><xref linkend="options-platform"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-msse2</option></entry>
+ <entry>(x86 only) Use SSE2 for floating point</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ </tbody>
+ <tbody>
+ <row>
+ <entry><option>-monly-[432]-regs</option></entry>
+ <entry>(x86 only) give some registers back to the C compiler</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+
+
+ <sect2>
+ <title>External core file options</title>
+
+ <para><xref linkend="ext-core"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-fext-core</option></entry>
+ <entry>Generate <filename>.hcr</filename> external Core files</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+
+
+ <sect2>
+ <title>Compiler debugging options</title>
+
+ <para><xref linkend="options-debugging"/></para>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-dcore-lint</option></entry>
+ <entry>Turn on internal sanity checking</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-to-file</option></entry>
+ <entry>Dump to files instead of stdout</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-asm</option></entry>
+ <entry>Dump assembly</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-bcos</option></entry>
+ <entry>Dump interpreter byte code</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-cmm</option></entry>
+ <entry>Dump C-- output</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-core-stats</option></entry>
+ <entry>Print a one-line summary of the size of the Core program
+ at the end of the optimisation pipeline </entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-cpranal</option></entry>
+ <entry>Dump output from CPR analysis</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-cse</option></entry>
+ <entry>Dump CSE output</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-deriv</option></entry>
+ <entry>Dump deriving output</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-ds</option></entry>
+ <entry>Dump desugarer output</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-flatC</option></entry>
+ <entry>Dump &ldquo;flat&rdquo; C</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-foreign</option></entry>
+ <entry>Dump <literal>foreign export</literal> stubs</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-hpc</option></entry>
+ <entry>Dump after instrumentation for program coverage</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-inlinings</option></entry>
+ <entry>Dump inlining info</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-llvm</option></entry>
+ <entry>Dump LLVM intermediate code</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-occur-anal</option></entry>
+ <entry>Dump occurrence analysis output</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-opt-cmm</option></entry>
+ <entry>Dump the results of C-- to C-- optimising passes</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-parsed</option></entry>
+ <entry>Dump parse tree</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-prep</option></entry>
+ <entry>Dump prepared core</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-rn</option></entry>
+ <entry>Dump renamer output</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-rule-firings</option></entry>
+ <entry>Dump rule firing info</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-rule-rewrites</option></entry>
+ <entry>Dump detailed rule firing info</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-rules</option></entry>
+ <entry>Dump rules</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-vect</option></entry>
+ <entry>Dump vectoriser input and output</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-simpl</option></entry>
+ <entry>Dump final simplifier output</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-simpl-phases</option></entry>
+ <entry>Dump output from each simplifier phase</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-simpl-iterations</option></entry>
+ <entry>Dump output from each simplifier iteration</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-spec</option></entry>
+ <entry>Dump specialiser output</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-splices</option></entry>
+ <entry>Dump TH spliced expressions, and what they evaluate to</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-stg</option></entry>
+ <entry>Dump final STG</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-stranal</option></entry>
+ <entry>Dump strictness analyser output</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-tc</option></entry>
+ <entry>Dump typechecker output</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-types</option></entry>
+ <entry>Dump type signatures</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-worker-wrapper</option></entry>
+ <entry>Dump worker-wrapper output</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-if-trace</option></entry>
+ <entry>Trace interface files</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-tc-trace</option></entry>
+ <entry>Trace typechecker</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-vt-trace</option></entry>
+ <entry>Trace vectoriser</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-rn-trace</option></entry>
+ <entry>Trace renamer</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-rn-stats</option></entry>
+ <entry>Renamer stats</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-ddump-simpl-stats</option></entry>
+ <entry>Dump simplifier stats</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dno-debug-output</option></entry>
+ <entry>Suppress unsolicited debugging output</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dppr-debug</option></entry>
+ <entry>Turn on debug printing (more verbose)</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dppr-noprags</option></entry>
+ <entry>Don't output pragma info in dumps</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dppr-user-length</option></entry>
+ <entry>Set the depth for printing expressions in error msgs</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dppr-colsNNN</option></entry>
+ <entry>Set the width of debugging output. For example <option>-dppr-cols200</option></entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dppr-case-as-let</option></entry>
+ <entry>Print single alternative case expressions as strict lets.</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dsuppress-all</option></entry>
+ <entry>In core dumps, suppress everything that is suppressable.</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dsuppress-uniques</option></entry>
+ <entry>Suppress the printing of uniques in debug output (easier to use <command>diff</command>)</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dsuppress-idinfo</option></entry>
+ <entry>Suppress extended information about identifiers where they are bound</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dsuppress-module-prefixes</option></entry>
+ <entry>Suppress the printing of module qualification prefixes</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dsuppress-type-signatures</option></entry>
+ <entry>Suppress type signatures</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dsuppress-type-applications</option></entry>
+ <entry>Suppress type applications</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dsuppress-coercions</option></entry>
+ <entry>Suppress the printing of coercions in Core dumps to make them shorter</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dsource-stats</option></entry>
+ <entry>Dump haskell source stats</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dcmm-lint</option></entry>
+ <entry>C-- pass sanity checking</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dstg-lint</option></entry>
+ <entry>STG pass sanity checking</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dstg-stats</option></entry>
+ <entry>Dump STG stats</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dverbose-core2core</option></entry>
+ <entry>Show output from each core-to-core pass</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dverbose-stg2stg</option></entry>
+ <entry>Show output from each STG-to-STG pass</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dshow-passes</option></entry>
+ <entry>Print out each pass name as it happens</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dfaststring-stats</option></entry>
+ <entry>Show statistics for fast string usage when finished</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+
+ <sect2>
+ <title>Misc compiler options</title>
+
+ <informaltable>
+ <tgroup cols="4" align="left" colsep="1" rowsep="1">
+ <thead>
+ <row>
+ <entry>Flag</entry>
+ <entry>Description</entry>
+ <entry>Static/Dynamic</entry>
+ <entry>Reverse</entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry><option>-fno-hi-version-check</option></entry>
+ <entry>Don't complain about <literal>.hi</literal> file mismatches</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-dno-black-holing</option></entry>
+ <entry>Turn off black holing (probably doesn't work)</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-fhistory-size</option></entry>
+ <entry>Set simplification history size</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-funregisterised</option></entry>
+ <entry><link linkend="unreg">Unregisterised</link> compilation (use <option>-unreg</option> instead)</entry>
+ <entry>static</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-fno-ghci-history</option></entry>
+ <entry>Do not use the load/store the GHCi command history from/to <literal>ghci_history</literal>.</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ <row>
+ <entry><option>-fno-ghci-sandbox</option></entry>
+ <entry>Turn off the GHCi sandbox. Means computations are run in the main thread, rather than a forked thread.</entry>
+ <entry>dynamic</entry>
+ <entry>-</entry>
+ </row>
+ </tbody>
+ </tgroup>
+ </informaltable>
+ </sect2>
+</sect1>
<!--
diff --git a/ghc.mk b/ghc.mk
index 1bd8976204..27066bcf00 100644
--- a/ghc.mk
+++ b/ghc.mk
@@ -1037,20 +1037,29 @@ publish-docs:
#
# Directory in which we're going to build the src dist
#
-SRC_DIST_NAME=ghc-$(ProjectVersion)
-SRC_DIST_DIR=$(SRC_DIST_NAME)
+SRC_DIST_ROOT = sdistprep
+SRC_DIST_BASE_NAME = ghc-$(ProjectVersion)
+
+SRC_DIST_GHC_NAME = ghc-$(ProjectVersion)
+SRC_DIST_GHC_ROOT = $(SRC_DIST_ROOT)/ghc
+SRC_DIST_GHC_DIR = $(SRC_DIST_GHC_ROOT)/$(SRC_DIST_BASE_NAME)
+SRC_DIST_GHC_TARBALL = $(SRC_DIST_ROOT)/$(SRC_DIST_GHC_NAME)-src.tar.bz2
+
+SRC_DIST_TESTSUITE_NAME = testsuite-ghc-$(ProjectVersion)
+SRC_DIST_TESTSUITE_ROOT = $(SRC_DIST_ROOT)/testsuite-ghc
+SRC_DIST_TESTSUITE_DIR = $(SRC_DIST_TESTSUITE_ROOT)/$(SRC_DIST_BASE_NAME)
+SRC_DIST_TESTSUITE_TARBALL = $(SRC_DIST_ROOT)/$(SRC_DIST_TESTSUITE_NAME)-src.tar.bz2
#
# Files to include in source distributions
#
-SRC_DIST_DIRS = mk rules docs distrib bindisttest libffi includes utils docs rts compiler ghc driver libraries ghc-tarballs
-SRC_DIST_FILES += \
- configure.ac config.guess config.sub configure \
- aclocal.m4 README ANNOUNCE HACKING LICENSE Makefile install-sh \
- ghc.spec.in ghc.spec settings.in VERSION \
- boot boot-pkgs packages ghc.mk
-
-SRC_DIST_TARBALL = $(SRC_DIST_NAME)-src.tar.bz2
+SRC_DIST_GHC_DIRS = mk rules docs distrib bindisttest libffi includes \
+ utils docs rts compiler ghc driver libraries ghc-tarballs
+SRC_DIST_GHC_FILES += \
+ configure.ac config.guess config.sub configure \
+ aclocal.m4 README ANNOUNCE HACKING LICENSE Makefile install-sh \
+ ghc.spec.in ghc.spec settings.in VERSION \
+ boot boot-pkgs packages ghc.mk
VERSION :
echo $(ProjectVersion) >VERSION
@@ -1058,50 +1067,66 @@ VERSION :
sdist : VERSION
# Use:
-# $(call sdist_file,compiler,stage2,cmm,Foo/Bar,CmmLex,x)
+# $(call sdist_ghc_file,compiler,stage2,cmm,Foo/Bar,CmmLex,x)
# to copy the generated file that replaces compiler/cmm/Foo/Bar/CmmLex.x, where
# "stage2" is the dist dir.
-define sdist_file
- "$(CP)" $1/$2/build/$4/$5.hs $(SRC_DIST_DIR)/$1/$3/$4
- mv $(SRC_DIST_DIR)/$1/$3/$4/$5.$6 $(SRC_DIST_DIR)/$1/$3/$4/$5.$6.source
+define sdist_ghc_file
+ "$(CP)" $1/$2/build/$4/$5.hs $(SRC_DIST_GHC_DIR)/$1/$3/$4
+ mv $(SRC_DIST_GHC_DIR)/$1/$3/$4/$5.$6 $(SRC_DIST_GHC_DIR)/$1/$3/$4/$5.$6.source
endef
-.PHONY: sdist-prep
-sdist-prep :
- $(call removeTrees,$(SRC_DIST_DIR))
- $(call removeFiles,$(SRC_DIST_TARBALL))
- mkdir $(SRC_DIST_DIR)
- cd $(SRC_DIST_DIR) && for i in $(SRC_DIST_DIRS); do mkdir $$i; ( cd $$i && lndir $(TOP)/$$i ); done
- cd $(SRC_DIST_DIR) && for i in $(SRC_DIST_FILES); do $(LN_S) $(TOP)/$$i .; done
- cd $(SRC_DIST_DIR) && $(MAKE) distclean
- $(call removeTrees,$(SRC_DIST_DIR)/libraries/tarballs/)
- $(call removeTrees,$(SRC_DIST_DIR)/libraries/stamp/)
- $(call sdist_file,compiler,stage2,cmm,,CmmLex,x)
- $(call sdist_file,compiler,stage2,cmm,,CmmParse,y)
- $(call sdist_file,compiler,stage2,parser,,Lexer,x)
- $(call sdist_file,compiler,stage2,parser,,Parser,y.pp)
- $(call sdist_file,compiler,stage2,parser,,ParserCore,y)
- $(call sdist_file,utils/hpc,dist-install,,,HpcParser,y)
- $(call sdist_file,utils/genprimopcode,dist,,,Lexer,x)
- $(call sdist_file,utils/genprimopcode,dist,,,Parser,y)
- $(call sdist_file,utils/haddock,dist,src,Haddock,Lex,x)
- $(call sdist_file,utils/haddock,dist,src,Haddock,Parse,y)
- cd $(SRC_DIST_DIR) && $(call removeTrees,compiler/stage[123] mk/build.mk)
- cd $(SRC_DIST_DIR) && "$(FIND)" $(SRC_DIST_DIRS) \( -name .git -o -name "autom4te*" -o -name "*~" -o -name "\#*" -o -name ".\#*" -o -name "log" -o -name "*-SAVE" -o -name "*.orig" -o -name "*.rej" \) -print | "$(XARGS)" $(XARGS_OPTS) "$(RM)" $(RM_OPTS_REC)
+.PHONY: sdist-ghc-prep
+sdist-ghc-prep :
+ $(call removeTrees,$(SRC_DIST_GHC_ROOT))
+ $(call removeFiles,$(SRC_DIST_GHC_TARBALL))
+ -mkdir $(SRC_DIST_ROOT)
+ mkdir $(SRC_DIST_GHC_ROOT)
+ mkdir $(SRC_DIST_GHC_DIR)
+ cd $(SRC_DIST_GHC_DIR) && for i in $(SRC_DIST_GHC_DIRS); do mkdir $$i; ( cd $$i && lndir $(TOP)/$$i ); done
+ cd $(SRC_DIST_GHC_DIR) && for i in $(SRC_DIST_GHC_FILES); do $(LN_S) $(TOP)/$$i .; done
+ cd $(SRC_DIST_GHC_DIR) && $(MAKE) distclean
+ $(call removeTrees,$(SRC_DIST_GHC_DIR)/libraries/tarballs/)
+ $(call removeTrees,$(SRC_DIST_GHC_DIR)/libraries/stamp/)
+ $(call removeTrees,$(SRC_DIST_GHC_DIR)/compiler/stage[123])
+ $(call removeFiles,$(SRC_DIST_GHC_DIR)/mk/build.mk)
+ $(call sdist_ghc_file,compiler,stage2,cmm,,CmmLex,x)
+ $(call sdist_ghc_file,compiler,stage2,cmm,,CmmParse,y)
+ $(call sdist_ghc_file,compiler,stage2,parser,,Lexer,x)
+ $(call sdist_ghc_file,compiler,stage2,parser,,Parser,y.pp)
+ $(call sdist_ghc_file,compiler,stage2,parser,,ParserCore,y)
+ $(call sdist_ghc_file,utils/hpc,dist-install,,,HpcParser,y)
+ $(call sdist_ghc_file,utils/genprimopcode,dist,,,Lexer,x)
+ $(call sdist_ghc_file,utils/genprimopcode,dist,,,Parser,y)
+ $(call sdist_ghc_file,utils/haddock,dist,src,Haddock,Lex,x)
+ $(call sdist_ghc_file,utils/haddock,dist,src,Haddock,Parse,y)
+ cd $(SRC_DIST_GHC_DIR) && "$(FIND)" $(SRC_DIST_GHC_DIRS) \( -name .git -o -name "autom4te*" -o -name "*~" -o -name "\#*" -o -name ".\#*" -o -name "log" -o -name "*-SAVE" -o -name "*.orig" -o -name "*.rej" \) -print | "$(XARGS)" $(XARGS_OPTS) "$(RM)" $(RM_OPTS_REC)
+
+.PHONY: sdist-testsuite-prep
+sdist-testsuite-prep :
+ $(call removeTrees,$(SRC_DIST_TESTSUITE_ROOT))
+ $(call removeFiles,$(SRC_DIST_TESTSUITE_TARBALL))
+ -mkdir $(SRC_DIST_ROOT)
+ mkdir $(SRC_DIST_TESTSUITE_ROOT)
+ mkdir $(SRC_DIST_TESTSUITE_DIR)
+ mkdir $(SRC_DIST_TESTSUITE_DIR)/testsuite
+ cd $(SRC_DIST_TESTSUITE_DIR)/testsuite && lndir $(TOP)/testsuite
+ $(call removeTrees,$(SRC_DIST_TESTSUITE_DIR)/testsuite/.git)
.PHONY: sdist
-sdist : sdist-prep
- "$(TAR_CMD)" chf - $(SRC_DIST_NAME) 2>src_log | bzip2 >$(TOP)/$(SRC_DIST_TARBALL)
+sdist : sdist-ghc-prep sdist-testsuite-prep
+ cd $(SRC_DIST_GHC_ROOT) && "$(TAR_CMD)" chf - $(SRC_DIST_BASE_NAME) 2> src_ghc_log | bzip2 > $(TOP)/$(SRC_DIST_GHC_TARBALL)
+ cd $(SRC_DIST_TESTSUITE_ROOT) && "$(TAR_CMD)" chf - $(SRC_DIST_BASE_NAME) 2> src_ghc_log | bzip2 > $(TOP)/$(SRC_DIST_TESTSUITE_TARBALL)
-sdist-manifest : $(SRC_DIST_TARBALL)
- tar tjf $(SRC_DIST_TARBALL) | sed "s|^ghc-$(ProjectVersion)/||" | sort >sdist-manifest
+sdist-manifest : $(SRC_DIST_GHC_TARBALL)
+ tar tjf $(SRC_DIST_GHC_TARBALL) | sed "s|^ghc-$(ProjectVersion)/||" | sort >sdist-manifest
# Upload the distribution(s)
# Retrying is to work around buggy firewalls that corrupt large file transfers
# over SSH.
ifneq "$(PublishLocation)" ""
publish-sdist :
- $(call try10Times,$(PublishCp) $(SRC_DIST_TARBALL) $(PublishLocation)/dist)
+ $(call try10Times,$(PublishCp) $(SRC_DIST_GHC_TARBALL) $(PublishLocation)/dist)
+ $(call try10Times,$(PublishCp) $(SRC_DIST_TESTSUITE_TARBALL) $(PublishLocation)/dist)
endif
ifeq "$(BootingFromHc)" "YES"