summaryrefslogtreecommitdiff
path: root/utils
diff options
context:
space:
mode:
Diffstat (limited to 'utils')
-rw-r--r--utils/ghc-cabal/Main.hs60
-rw-r--r--utils/ghc-pkg/Main.hs136
-rw-r--r--utils/ghc-pkg/ghc-pkg.cabal2
m---------utils/haddock0
-rw-r--r--utils/mkUserGuidePart/DList.hs13
-rw-r--r--utils/mkUserGuidePart/Main.hs151
-rw-r--r--utils/mkUserGuidePart/Options.hs66
-rw-r--r--utils/mkUserGuidePart/Options/CodeGen.hs35
-rw-r--r--utils/mkUserGuidePart/Options/CompilerDebugging.hs272
-rw-r--r--utils/mkUserGuidePart/Options/Cpp.hs25
-rw-r--r--utils/mkUserGuidePart/Options/FindingImports.hs15
-rw-r--r--utils/mkUserGuidePart/Options/Interactive.hs65
-rw-r--r--utils/mkUserGuidePart/Options/InterfaceFiles.hs23
-rw-r--r--utils/mkUserGuidePart/Options/KeepingIntermediates.hs23
-rw-r--r--utils/mkUserGuidePart/Options/Language.hs735
-rw-r--r--utils/mkUserGuidePart/Options/Linking.hs162
-rw-r--r--utils/mkUserGuidePart/Options/Misc.hs32
-rw-r--r--utils/mkUserGuidePart/Options/Modes.hs63
-rw-r--r--utils/mkUserGuidePart/Options/OptimizationLevels.hs29
-rw-r--r--utils/mkUserGuidePart/Options/Optimizations.hs344
-rw-r--r--utils/mkUserGuidePart/Options/Packages.hs67
-rw-r--r--utils/mkUserGuidePart/Options/PhasePrograms.hs58
-rw-r--r--utils/mkUserGuidePart/Options/PhaseSpecific.hs47
-rw-r--r--utils/mkUserGuidePart/Options/Phases.hs33
-rw-r--r--utils/mkUserGuidePart/Options/PlatformSpecific.hs15
-rw-r--r--utils/mkUserGuidePart/Options/Plugin.hs17
-rw-r--r--utils/mkUserGuidePart/Options/Profiling.hs44
-rw-r--r--utils/mkUserGuidePart/Options/ProgramCoverage.hs18
-rw-r--r--utils/mkUserGuidePart/Options/RecompilationChecking.hs15
-rw-r--r--utils/mkUserGuidePart/Options/RedirectingOutput.hs47
-rw-r--r--utils/mkUserGuidePart/Options/TemporaryFiles.hs11
-rw-r--r--utils/mkUserGuidePart/Options/Verbosity.hs58
-rw-r--r--utils/mkUserGuidePart/Options/Warnings.hs317
-rw-r--r--utils/mkUserGuidePart/Table.hs75
-rw-r--r--utils/mkUserGuidePart/Types.hs20
-rw-r--r--utils/mkUserGuidePart/ghc.mk40
-rw-r--r--utils/mkUserGuidePart/mkUserGuidePart.cabal31
-rwxr-xr-xutils/vagrant/bootstrap-rhel.sh2
38 files changed, 2987 insertions, 179 deletions
diff --git a/utils/ghc-cabal/Main.hs b/utils/ghc-cabal/Main.hs
index 206b676031..6e3e10cee7 100644
--- a/utils/ghc-cabal/Main.hs
+++ b/utils/ghc-cabal/Main.hs
@@ -229,12 +229,7 @@ doRegister directory distDir ghc ghcpkg topdir
let installedPkgs' = PackageIndex.fromList instInfos
let updateComponentConfig (cn, clbi, deps)
= (cn, updateComponentLocalBuildInfo clbi, deps)
- updateComponentLocalBuildInfo clbi
- = clbi {
- componentPackageDeps =
- [ (fixupPackageId instInfos ipid, pid)
- | (ipid,pid) <- componentPackageDeps clbi ]
- }
+ updateComponentLocalBuildInfo clbi = clbi -- TODO: remove
ccs' = map updateComponentConfig (componentsConfigs lbi)
lbi' = lbi {
componentsConfigs = ccs',
@@ -265,30 +260,6 @@ updateInstallDirTemplates relocatableBuild myPrefix myLibdir myDocdir idts
htmldir = toPathTemplate "$docdir"
}
--- The packages are built with the package ID ending in "-inplace", but
--- when they're installed they get the package hash appended. We need to
--- fix up the package deps so that they use the hash package IDs, not
--- the inplace package IDs.
-fixupPackageId :: [Installed.InstalledPackageInfo]
- -> InstalledPackageId
- -> InstalledPackageId
-fixupPackageId _ x@(InstalledPackageId ipi)
- | "builtin_" `isPrefixOf` ipi = x
-fixupPackageId ipinfos (InstalledPackageId ipi)
- = case stripPrefix (reverse "-inplace") $ reverse ipi of
- Nothing ->
- error ("Installed package ID doesn't end in -inplace: " ++ show ipi)
- Just x ->
- let ipi' = reverse ('-' : x)
- f (ipinfo : ipinfos') = case Installed.installedPackageId ipinfo of
- y@(InstalledPackageId ipinfoid)
- | ipi' `isPrefixOf` ipinfoid ->
- y
- _ ->
- f ipinfos'
- f [] = error ("Installed package ID not registered: " ++ show ipi)
- in f ipinfos
-
-- On Windows we need to split the ghc package into 2 pieces, or the
-- DLL that it makes contains too many symbols (#5987). There are
-- therefore 2 libraries, not just the 1 that Cabal assumes.
@@ -316,7 +287,7 @@ generate directory distdir dll0Modules config_args
-- XXX We shouldn't just configure with the default flags
-- XXX And this, and thus the "getPersistBuildConfig distdir" below,
-- aren't going to work when the deps aren't built yet
- withArgs (["configure", "--distdir", distdir] ++ config_args)
+ withArgs (["configure", "--distdir", distdir, "--ipid", "$pkg-$version"] ++ config_args)
runDefaultMain
lbi <- getPersistBuildConfig distdir
@@ -342,11 +313,12 @@ generate directory distdir dll0Modules config_args
-- generate inplace-pkg-config
withLibLBI pd lbi $ \lib clbi ->
do cwd <- getCurrentDirectory
- let ipid = InstalledPackageId (display (packageId pd) ++ "-inplace")
+ let ipid = ComponentId (display (packageId pd))
let installedPkgInfo = inplaceInstalledPackageInfo cwd distdir
- pd ipid lib lbi clbi
+ pd (Installed.AbiHash "") lib lbi clbi
final_ipi = mangleIPI directory distdir lbi $ installedPkgInfo {
- Installed.installedPackageId = ipid,
+ Installed.installedComponentId = ipid,
+ Installed.compatPackageKey = ipid,
Installed.haddockHTMLs = []
}
content = Installed.showInstalledPackageInfo final_ipi ++ "\n"
@@ -397,24 +369,24 @@ generate directory distdir dll0Modules config_args
dep_ids = map snd (externalPackageDeps lbi)
deps = map display dep_ids
dep_direct = map (fromMaybe (error "ghc-cabal: dep_keys failed")
- . PackageIndex.lookupInstalledPackageId
+ . PackageIndex.lookupComponentId
(installedPkgs lbi)
. fst)
. externalPackageDeps
$ lbi
- dep_ipids = map (display . Installed.installedPackageId) dep_direct
+ dep_ipids = map (display . Installed.installedComponentId) dep_direct
depLibNames
- | packageKeySupported comp
- = map (display . Installed.libraryName) dep_direct
+ | packageKeySupported comp = dep_ipids
| otherwise = deps
depNames = map (display . packageName) dep_ids
transitive_dep_ids = map Installed.sourcePackageId dep_pkgs
transitiveDeps = map display transitive_dep_ids
transitiveDepLibNames
- | packageKeySupported comp
- = map (display . Installed.libraryName) dep_pkgs
+ | packageKeySupported comp = map fixupRtsLibName transitiveDeps
| otherwise = transitiveDeps
+ fixupRtsLibName "rts-1.0" = "rts"
+ fixupRtsLibName x = x
transitiveDepNames = map (display . packageName) transitive_dep_ids
libraryDirs = forDeps Installed.libraryDirs
@@ -434,9 +406,9 @@ generate directory distdir dll0Modules config_args
allMods = mods ++ otherMods
let xs = [variablePrefix ++ "_VERSION = " ++ display (pkgVersion (package pd)),
-- TODO: move inside withLibLBI
- variablePrefix ++ "_PACKAGE_KEY = " ++ display (localPackageKey lbi),
+ variablePrefix ++ "_COMPONENT_ID = " ++ display (localCompatPackageKey lbi),
-- copied from mkComponentsLocalBuildInfo
- variablePrefix ++ "_LIB_NAME = " ++ display (localLibraryName lbi),
+ variablePrefix ++ "_COMPONENT_ID = " ++ display (localComponentId lbi),
variablePrefix ++ "_MODULES = " ++ unwords mods,
variablePrefix ++ "_HIDDEN_MODULES = " ++ unwords otherMods,
variablePrefix ++ "_SYNOPSIS =" ++ synopsis pd,
@@ -444,9 +416,9 @@ generate directory distdir dll0Modules config_args
variablePrefix ++ "_DEPS = " ++ unwords deps,
variablePrefix ++ "_DEP_IPIDS = " ++ unwords dep_ipids,
variablePrefix ++ "_DEP_NAMES = " ++ unwords depNames,
- variablePrefix ++ "_DEP_LIB_NAMES = " ++ unwords depLibNames,
+ variablePrefix ++ "_DEP_COMPONENT_IDS = " ++ unwords depLibNames,
variablePrefix ++ "_TRANSITIVE_DEPS = " ++ unwords transitiveDeps,
- variablePrefix ++ "_TRANSITIVE_DEP_LIB_NAMES = " ++ unwords transitiveDepLibNames,
+ variablePrefix ++ "_TRANSITIVE_DEP_COMPONENT_IDS = " ++ unwords transitiveDepLibNames,
variablePrefix ++ "_TRANSITIVE_DEP_NAMES = " ++ unwords transitiveDepNames,
variablePrefix ++ "_INCLUDE_DIRS = " ++ unwords (includeDirs bi),
variablePrefix ++ "_INCLUDES = " ++ unwords (includes bi),
diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs
index 4ee0d012f2..4bc603459a 100644
--- a/utils/ghc-pkg/Main.hs
+++ b/utils/ghc-pkg/Main.hs
@@ -19,7 +19,7 @@ import Distribution.ModuleName (ModuleName)
import Distribution.InstalledPackageInfo as Cabal
import Distribution.Compat.ReadP hiding (get)
import Distribution.ParseUtils
-import Distribution.Package hiding (installedPackageId)
+import Distribution.Package hiding (installedComponentId)
import Distribution.Text
import Distribution.Version
import Distribution.Simple.Utils (fromUTF8, toUTF8, writeUTF8File, readUTF8File)
@@ -136,8 +136,7 @@ data Flag
| FlagIgnoreCase
| FlagNoUserDb
| FlagVerbosity (Maybe String)
- | FlagIPId
- | FlagPackageKey
+ | FlagComponentId
deriving Eq
flags :: [OptDescr Flag]
@@ -180,10 +179,8 @@ flags = [
"only print package names, not versions; can only be used with list --simple-output",
Option [] ["ignore-case"] (NoArg FlagIgnoreCase)
"ignore case for substring matching",
- Option [] ["ipid"] (NoArg FlagIPId)
+ Option [] ["ipid", "package-key"] (NoArg FlagComponentId)
"interpret package arguments as installed package IDs",
- Option [] ["package-key"] (NoArg FlagPackageKey)
- "interpret package arguments as installed package keys",
Option ['v'] ["verbose"] (OptArg FlagVerbosity "Verbosity")
"verbosity level (0-2, default 1)"
]
@@ -322,8 +319,7 @@ data Force = NoForce | ForceFiles | ForceAll | CannotForce
-- | Enum flag representing argument type
data AsPackageArg
- = AsIpid
- | AsPackageKey
+ = AsComponentId
| AsDefault
-- | Represents how a package may be specified by a user on the command line.
@@ -332,10 +328,7 @@ data PackageArg
= Id PackageIdentifier
-- | An installed package ID foo-0.1-HASH. This is guaranteed to uniquely
-- match a single entry in the package database.
- | IPId InstalledPackageId
- -- | A package key foo_HASH. This is also guaranteed to uniquely match
- -- a single entry in the package database
- | PkgKey PackageKey
+ | ICId ComponentId
-- | A glob against the package name. The first string is the literal
-- glob, the second is a function which returns @True@ if the argument
-- matches.
@@ -350,8 +343,7 @@ runit verbosity cli nonopts = do
| FlagForce `elem` cli = ForceAll
| FlagForceFiles `elem` cli = ForceFiles
| otherwise = NoForce
- as_arg | FlagIPId `elem` cli = AsIpid
- | FlagPackageKey `elem` cli = AsPackageKey
+ as_arg | FlagComponentId `elem` cli = AsComponentId
| otherwise = AsDefault
multi_instance = FlagMultiInstance `elem` cli
expand_env_vars= FlagExpandEnvVars `elem` cli
@@ -504,10 +496,8 @@ parseGlobPackageId =
return (PackageIdentifier{ pkgName = n, pkgVersion = globVersion }))
readPackageArg :: AsPackageArg -> String -> IO PackageArg
-readPackageArg AsIpid str =
- parseCheck (IPId `fmap` parse) str "installed package id"
-readPackageArg AsPackageKey str =
- parseCheck (PkgKey `fmap` parse) str "package key"
+readPackageArg AsComponentId str =
+ parseCheck (ICId `fmap` parse) str "installed package id"
readPackageArg AsDefault str = Id `fmap` readGlobPkgId str
-- globVersion means "all versions"
@@ -1013,12 +1003,7 @@ parsePackageInfo str =
(Just l, s) -> die (show l ++ ": " ++ s)
mungePackageInfo :: InstalledPackageInfo -> InstalledPackageInfo
-mungePackageInfo ipi = ipi { packageKey = packageKey' }
- where
- packageKey'
- | OldPackageKey (PackageIdentifier (PackageName "") _) <- packageKey ipi
- = OldPackageKey (sourcePackageId ipi)
- | otherwise = packageKey ipi
+mungePackageInfo ipi = ipi
-- -----------------------------------------------------------------------------
-- Making changes to a package database
@@ -1038,7 +1023,7 @@ updateInternalDB :: PackageDB -> [DBOp] -> PackageDB
updateInternalDB db cmds = db{ packages = foldl do_cmd (packages db) cmds }
where
do_cmd pkgs (RemovePackage p) =
- filter ((/= installedPackageId p) . installedPackageId) pkgs
+ filter ((/= installedComponentId p) . installedComponentId) pkgs
do_cmd pkgs (AddPackage p) = p : pkgs
do_cmd pkgs (ModifyPackage p) =
do_cmd (do_cmd pkgs (RemovePackage p)) (AddPackage p)
@@ -1050,11 +1035,11 @@ changeDBDir verbosity cmds db = do
updateDBCache verbosity db
where
do_cmd (RemovePackage p) = do
- let file = location db </> display (installedPackageId p) <.> "conf"
+ let file = location db </> display (installedComponentId p) <.> "conf"
when (verbosity > Normal) $ infoLn ("removing " ++ file)
removeFileSafe file
do_cmd (AddPackage p) = do
- let file = location db </> display (installedPackageId p) <.> "conf"
+ let file = location db </> display (installedComponentId p) <.> "conf"
when (verbosity > Normal) $ infoLn ("writing " ++ file)
writeUTF8File file (showInstalledPackageInfo p)
do_cmd (ModifyPackage p) =
@@ -1091,18 +1076,20 @@ type PackageCacheFormat = GhcPkg.InstalledPackageInfo
String -- installed package id
String -- src package id
String -- package name
- String -- package key
+ String -- unit id
ModuleName -- module name
convertPackageInfoToCacheFormat :: InstalledPackageInfo -> PackageCacheFormat
convertPackageInfoToCacheFormat pkg =
GhcPkg.InstalledPackageInfo {
- GhcPkg.installedPackageId = display (installedPackageId pkg),
+ GhcPkg.componentId = display (installedComponentId pkg),
GhcPkg.sourcePackageId = display (sourcePackageId pkg),
GhcPkg.packageName = display (packageName pkg),
GhcPkg.packageVersion = packageVersion pkg,
- GhcPkg.packageKey = display (packageKey pkg),
+ GhcPkg.unitId = display (installedComponentId pkg),
GhcPkg.depends = map display (depends pkg),
+ GhcPkg.abiHash = let AbiHash abi = abiHash pkg
+ in abi,
GhcPkg.importDirs = importDirs pkg,
GhcPkg.hsLibraries = hsLibraries pkg,
GhcPkg.extraLibraries = extraLibraries pkg,
@@ -1174,9 +1161,9 @@ modifyPackage fn pkgarg verbosity my_flags force = do
db_name = location db
pkgs = packages db
- pks = map packageKey ps
+ pks = map installedComponentId ps
- cmds = [ fn pkg | pkg <- pkgs, packageKey pkg `elem` pks ]
+ cmds = [ fn pkg | pkg <- pkgs, installedComponentId pkg `elem` pks ]
new_db = updateInternalDB db cmds
-- ...but do consistency checks with regards to the full stack
@@ -1184,14 +1171,14 @@ modifyPackage fn pkgarg verbosity my_flags force = do
rest_of_stack = filter ((/= db_name) . location) db_stack
new_stack = new_db : rest_of_stack
new_broken = brokenPackages (allPackagesInStack new_stack)
- newly_broken = filter ((`notElem` map packageKey old_broken)
- . packageKey) new_broken
+ newly_broken = filter ((`notElem` map installedComponentId old_broken)
+ . installedComponentId) new_broken
--
let displayQualPkgId pkg
| [_] <- filter ((== pkgid) . sourcePackageId)
(allPackagesInStack db_stack)
= display pkgid
- | otherwise = display pkgid ++ "@" ++ display (packageKey pkg)
+ | otherwise = display pkgid ++ "@" ++ display (installedComponentId pkg)
where pkgid = sourcePackageId pkg
when (not (null newly_broken)) $
dieOrForceAll force ("unregistering would break the following packages: "
@@ -1242,7 +1229,7 @@ listPackages verbosity my_flags mPackageName mModuleName = do
EQ -> case pkgVersion p1 `compare` pkgVersion p2 of
LT -> LT
GT -> GT
- EQ -> packageKey pkg1 `compare` packageKey pkg2
+ EQ -> installedComponentId pkg1 `compare` installedComponentId pkg2
where (p1,p2) = (sourcePackageId pkg1, sourcePackageId pkg2)
stack = reverse db_stack_sorted
@@ -1250,7 +1237,7 @@ listPackages verbosity my_flags mPackageName mModuleName = do
match `exposedInPkg` pkg = any match (map display $ exposedModules pkg)
pkg_map = allPackagesInStack db_stack
- broken = map packageKey (brokenPackages pkg_map)
+ broken = map installedComponentId (brokenPackages pkg_map)
show_normal PackageDB{ location = db_name, packages = pkg_confs } =
do hPutStrLn stdout (db_name ++ ":")
@@ -1259,15 +1246,15 @@ listPackages verbosity my_flags mPackageName mModuleName = do
else hPutStrLn stdout $ unlines (map (" " ++) pp_pkgs)
where
-- Sort using instance Ord PackageId
- pp_pkgs = map pp_pkg . sortBy (comparing installedPackageId) $ pkg_confs
+ pp_pkgs = map pp_pkg . sortBy (comparing installedComponentId) $ pkg_confs
pp_pkg p
- | packageKey p `elem` broken = printf "{%s}" doc
+ | installedComponentId p `elem` broken = printf "{%s}" doc
| exposed p = doc
| otherwise = printf "(%s)" doc
- where doc | verbosity >= Verbose = printf "%s (%s)" pkg ipid
+ where doc | verbosity >= Verbose = printf "%s (%s)" pkg pk
| otherwise = pkg
where
- InstalledPackageId ipid = installedPackageId p
+ ComponentId pk = installedComponentId p
pkg = display (sourcePackageId p)
show_simple = simplePackageList my_flags . allPackagesInStack
@@ -1288,15 +1275,15 @@ listPackages verbosity my_flags mPackageName mModuleName = do
map (termText " " <#>) (map pp_pkg (packages db)))
where
pp_pkg p
- | packageKey p `elem` broken = withF Red doc
+ | installedComponentId p `elem` broken = withF Red doc
| exposed p = doc
| otherwise = withF Blue doc
where doc | verbosity >= Verbose
- = termText (printf "%s (%s)" pkg ipid)
+ = termText (printf "%s (%s)" pkg pk)
| otherwise
= termText pkg
where
- InstalledPackageId ipid = installedPackageId p
+ ComponentId pk = installedComponentId p
pkg = display (sourcePackageId p)
is_tty <- hIsTerminalDevice stdout
@@ -1332,8 +1319,8 @@ showPackageDot verbosity myflags = do
mapM_ putStrLn [ quote from ++ " -> " ++ quote to
| p <- all_pkgs,
let from = display (sourcePackageId p),
- depid <- depends p,
- Just dep <- [PackageIndex.lookupInstalledPackageId ipix depid],
+ key <- depends p,
+ Just dep <- [PackageIndex.lookupComponentId ipix key],
let to = display (sourcePackageId dep)
]
putStrLn "}"
@@ -1341,7 +1328,7 @@ showPackageDot verbosity myflags = do
-- -----------------------------------------------------------------------------
-- Prints the highest (hidden or exposed) version of a package
--- ToDo: This is no longer well-defined with package keys, because the
+-- ToDo: This is no longer well-defined with unit ids, because the
-- dependencies may be varying versions
latestPackage :: Verbosity -> [Flag] -> PackageIdentifier -> IO ()
latestPackage verbosity my_flags pkgid = do
@@ -1405,8 +1392,7 @@ findPackagesByDB db_stack pkgarg
ps -> return ps
where
pkg_msg (Id pkgid) = display pkgid
- pkg_msg (PkgKey pk) = display pk
- pkg_msg (IPId ipid) = display ipid
+ pkg_msg (ICId ipid) = display ipid
pkg_msg (Substring pkgpat _) = "matching " ++ pkgpat
matches :: PackageIdentifier -> PackageIdentifier -> Bool
@@ -1420,8 +1406,7 @@ realVersion pkgid = versionBranch (pkgVersion pkgid) /= []
matchesPkg :: PackageArg -> InstalledPackageInfo -> Bool
(Id pid) `matchesPkg` pkg = pid `matches` sourcePackageId pkg
-(PkgKey pk) `matchesPkg` pkg = pk == packageKey pkg
-(IPId ipid) `matchesPkg` pkg = ipid == installedPackageId pkg
+(ICId ipid) `matchesPkg` pkg = ipid == installedComponentId pkg
(Substring _ m) `matchesPkg` pkg = m (display (sourcePackageId pkg))
-- -----------------------------------------------------------------------------
@@ -1509,7 +1494,7 @@ closure pkgs db_stack = go pkgs db_stack
-> Bool
depsAvailable pkgs_ok pkg = null dangling
where dangling = filter (`notElem` pids) (depends pkg)
- pids = map installedPackageId pkgs_ok
+ pids = map installedComponentId pkgs_ok
-- we want mutually recursive groups of package to show up
-- as broken. (#1750)
@@ -1597,9 +1582,8 @@ checkPackageConfig :: InstalledPackageInfo
-> Validate ()
checkPackageConfig pkg verbosity db_stack
multi_instance update = do
- checkInstalledPackageId pkg db_stack update
checkPackageId pkg
- checkPackageKey pkg
+ checkComponentId pkg db_stack update
checkDuplicates db_stack pkg multi_instance update
mapM_ (checkDep db_stack) (depends pkg)
checkDuplicateDepends (depends pkg)
@@ -1617,18 +1601,6 @@ checkPackageConfig pkg verbosity db_stack
-- extra_libraries :: [String],
-- c_includes :: [String],
-checkInstalledPackageId :: InstalledPackageInfo -> PackageDBStack -> Bool
- -> Validate ()
-checkInstalledPackageId ipi db_stack update = do
- let ipid@(InstalledPackageId str) = installedPackageId ipi
- when (null str) $ verror CannotForce "missing id field"
- let dups = [ p | p <- allPackagesInStack db_stack,
- installedPackageId p == ipid ]
- when (not update && not (null dups)) $
- verror CannotForce $
- "package(s) with this id already exist: " ++
- unwords (map (display.packageId) dups)
-
-- When the package name and version are put together, sometimes we can
-- end up with a package id that cannot be parsed. This will lead to
-- difficulties when the user wants to refer to the package later, so
@@ -1641,13 +1613,17 @@ checkPackageId ipi =
[] -> verror CannotForce ("invalid package identifier: " ++ str)
_ -> verror CannotForce ("ambiguous package identifier: " ++ str)
-checkPackageKey :: InstalledPackageInfo -> Validate ()
-checkPackageKey ipi =
- let str = display (packageKey ipi) in
- case [ x :: PackageKey | (x,ys) <- readP_to_S parse str, all isSpace ys ] of
- [_] -> return ()
- [] -> verror CannotForce ("invalid package key: " ++ str)
- _ -> verror CannotForce ("ambiguous package key: " ++ str)
+checkComponentId :: InstalledPackageInfo -> PackageDBStack -> Bool
+ -> Validate ()
+checkComponentId ipi db_stack update = do
+ let pk@(ComponentId str) = installedComponentId ipi
+ when (null str) $ verror CannotForce "missing id field"
+ let dups = [ p | p <- allPackagesInStack db_stack,
+ installedComponentId p == pk ]
+ when (not update && not (null dups)) $
+ verror CannotForce $
+ "package(s) with this id already exist: " ++
+ unwords (map (display.installedComponentId) dups)
checkDuplicates :: PackageDBStack -> InstalledPackageInfo
-> Bool -> Bool-> Validate ()
@@ -1706,16 +1682,16 @@ checkPath url_ok is_dir warn_only thisfield d
then vwarn msg
else verror ForceFiles msg
-checkDep :: PackageDBStack -> InstalledPackageId -> Validate ()
+checkDep :: PackageDBStack -> ComponentId -> Validate ()
checkDep db_stack pkgid
| pkgid `elem` pkgids = return ()
| otherwise = verror ForceAll ("dependency \"" ++ display pkgid
++ "\" doesn't exist")
where
all_pkgs = allPackagesInStack db_stack
- pkgids = map installedPackageId all_pkgs
+ pkgids = map installedComponentId all_pkgs
-checkDuplicateDepends :: [InstalledPackageId] -> Validate ()
+checkDuplicateDepends :: [ComponentId] -> Validate ()
checkDuplicateDepends deps
| null dups = return ()
| otherwise = verror ForceAll ("package has duplicate dependencies: " ++
@@ -1799,9 +1775,9 @@ checkOriginalModule :: String
-> Validate ()
checkOriginalModule field_name db_stack pkg
(OriginalModule definingPkgId definingModule) =
- let mpkg = if definingPkgId == installedPackageId pkg
+ let mpkg = if definingPkgId == installedComponentId pkg
then Just pkg
- else PackageIndex.lookupInstalledPackageId ipix definingPkgId
+ else PackageIndex.lookupComponentId ipix definingPkgId
in case mpkg of
Nothing
-> verror ForceAll (field_name ++ " refers to a non-existent " ++
@@ -1810,7 +1786,7 @@ checkOriginalModule field_name db_stack pkg
Just definingPkg
| not (isIndirectDependency definingPkgId)
- -> verror ForceAll (field_name ++ " refers to a defining " ++
+ -> verror ForceAll (field_name ++ " refers to a defining " ++
"package that is not a direct (or indirect) " ++
"dependency of this package: " ++
display definingPkgId)
@@ -1835,7 +1811,7 @@ checkOriginalModule field_name db_stack pkg
ipix = PackageIndex.fromList all_pkgs
isIndirectDependency pkgid = fromMaybe False $ do
- thispkg <- graphVertex (installedPackageId pkg)
+ thispkg <- graphVertex (installedComponentId pkg)
otherpkg <- graphVertex pkgid
return (Graph.path depgraph thispkg otherpkg)
(depgraph, _, graphVertex) =
diff --git a/utils/ghc-pkg/ghc-pkg.cabal b/utils/ghc-pkg/ghc-pkg.cabal
index 317aab7cfa..742e2962ef 100644
--- a/utils/ghc-pkg/ghc-pkg.cabal
+++ b/utils/ghc-pkg/ghc-pkg.cabal
@@ -25,7 +25,7 @@ Executable ghc-pkg
filepath,
Cabal,
binary,
- bin-package-db,
+ ghc-boot,
bytestring
if !os(windows)
Build-Depends: unix,
diff --git a/utils/haddock b/utils/haddock
-Subproject f1befeaacc630ca9fa11d316b429ecae571f91c
+Subproject 4ad0043d43e97c0f59028e91a460d4d9abb90da
diff --git a/utils/mkUserGuidePart/DList.hs b/utils/mkUserGuidePart/DList.hs
new file mode 100644
index 0000000000..c4b9283e52
--- /dev/null
+++ b/utils/mkUserGuidePart/DList.hs
@@ -0,0 +1,13 @@
+module DList where
+
+newtype DList a = DList ([a] -> [a])
+
+snoc :: DList a -> a -> DList a
+DList f `snoc` x = DList (f . (x:))
+
+toList :: DList a -> [a]
+toList (DList f) = f []
+
+instance Monoid (DList a) where
+ mempty = DList id
+ DList a `mappend` DList b = DList (a . b)
diff --git a/utils/mkUserGuidePart/Main.hs b/utils/mkUserGuidePart/Main.hs
index c415eb4f49..9bc8caa216 100644
--- a/utils/mkUserGuidePart/Main.hs
+++ b/utils/mkUserGuidePart/Main.hs
@@ -1,62 +1,107 @@
-
module Main (main) where
import DynFlags
+import Data.List (stripPrefix)
+import Control.Monad (forM_)
+import Types hiding (flag)
+import Table
+import Options
-import Data.List
-import System.Environment
+-- | A ReStructuredText fragment
+type ReST = String
main :: IO ()
-main = do args <- getArgs
- case args of
- [] -> error "Need to give filename to generate as an argument"
- [f] ->
- case f of
- "docs/users_guide/users_guide.xml" ->
- writeFile f userGuideMain
- "docs/users_guide/what_glasgow_exts_does.gen.xml" ->
- writeFile f whatGlasgowExtsDoes
- _ ->
- error ("Don't know what to do for " ++ show f)
- _ -> error "Bad args"
-
--- Hack: dblatex normalises the name of the main input file using
--- os.path.realpath, which means that if we're in a linked build tree,
--- it find the real source files rather than the symlinks in our link
--- tree. This is fine for the static sources, but it means it can't
--- find the generated sources.
--- We therefore also generate the main input file, so that it really
--- is in the link tree, and thus dblatex can find everything.
-userGuideMain :: String
-userGuideMain = unlines [
- "<?xml version=\"1.0\" encoding=\"iso-8859-1\"?>",
- "<!DOCTYPE book PUBLIC \"-//OASIS//DTD DocBook XML V4.2//EN\"",
- " \"http://www.oasis-open.org/docbook/xml/4.2/docbookx.dtd\" [",
- "<!ENTITY % ug-ent SYSTEM \"ug-ent.xml\">",
- "%ug-ent;",
- "<!ENTITY ug-book SYSTEM \"ug-book.xml\">",
- "]>",
- "",
- "<book id=\"users-guide\">",
- "&ug-book;",
- "</book>"]
+main = do
+ -- users guide
+ writeRestFile (usersGuideFile "what_glasgow_exts_does.gen.rst")
+ $ whatGlasgowExtsDoes
+ forM_ groups $ \(Group name _ theFlags) ->
+ let fname = usersGuideFile $ "flags-"++name++".gen.rst"
+ in writeRestFile fname (flagsTable theFlags)
+
+ -- man page
+ writeRestFile (usersGuideFile "all-flags.gen.rst") (flagsList groups)
+
+usersGuideFile :: FilePath -> FilePath
+usersGuideFile fname = "docs/users_guide/"++fname
+
+writeRestFile :: FilePath -> ReST -> IO ()
+writeRestFile fname content =
+ writeFile fname $ unlines
+ [ ".. This file is generated by utils/mkUserGuidePart"
+ , ""
+ , content
+ ]
whatGlasgowExtsDoes :: String
-whatGlasgowExtsDoes = case maybeInitLast glasgowExtsFlags of
- Just (xs, x) ->
- let xs' = map mkInitLine xs
- x' = mkLastLine x
- in unlines (xs' ++ [x'])
- Nothing ->
- error "glasgowExtsFlags is empty?"
- where mkInitLine = mkLine ','
- mkLastLine = mkLine '.'
- mkLine c f = case stripPrefix "Opt_" (show f) of
- Just ext -> "<option>-X" ++ ext ++ "</option>" ++ [c]
- Nothing -> error ("Can't parse extension: " ++ show f)
-
-maybeInitLast :: [a] -> Maybe ([a], a)
-maybeInitLast xs = case reverse xs of
- (y : ys) -> Just (reverse ys, y)
- _ -> Nothing
+whatGlasgowExtsDoes = unlines
+ $ [ ".. hlist::", ""]
+ ++ map ((" * "++) . parseExt) glasgowExtsFlags
+ where
+ parseExt f
+ | Just ext <- stripPrefix "Opt_" (show f)
+ = inlineCode $ "-X" ++ ext
+ | otherwise
+ = error ("Can't parse extension: " ++ show f)
+
+-- | Generate a reference table of the given set of flags. This is used in
+-- the users guide.
+flagsTable :: [Flag] -> ReST
+flagsTable theFlags =
+ table [50, 100, 30, 50]
+ ["Flag", "Description", "Static/Dynamic", "Reverse"]
+ (map flagRow theFlags)
+ where
+ code "" = ""
+ code str = "``"++str++"``"
+ flagRow flag =
+ [ code (flagName flag)
+ , flagDescription flag
+ , type_
+ , code (flagReverse flag)
+ ]
+ where
+ type_ = case flagType flag of
+ StaticFlag -> "static"
+ DynamicFlag -> "dynamic"
+ DynamicSettableFlag -> "dynamic/``:set``"
+ ModeFlag -> "mode"
+
+-- | Place the given text in an ReST inline code element.
+inlineCode :: String -> ReST
+inlineCode s = "``" ++ s ++ "``"
+
+-- | Generate a ReST substitution definition.
+substitution :: String -> ReST -> ReST
+substitution substName content =
+ unlines [".. |" ++ substName ++ "| ", content]
+
+heading :: Char -> String -> ReST
+heading chr title = unlines
+ [ title
+ , replicate (length title) chr
+ , ""
+ ]
+
+-- | Generate a listing of all the flags known to GHC.
+-- Used in the man page.
+flagsList :: [Group] -> ReST
+flagsList grps = unlines $
+ map doGroup grps ++ map flagDescriptions grps
+ where
+ doGroup grp = unlines
+ [ grpTitle grp
+ , " " ++ unwords (map (inlineCode . flagName) (grpFlags grp))
+ , ""
+ ]
+-- | Generate a definition list of the known flags.
+-- Used in the man page.
+flagDescriptions :: Group -> ReST
+flagDescriptions (Group _ title fs) =
+ unlines $ [ heading '~' title ] ++ map doFlag fs
+ where
+ doFlag flag =
+ unlines $ [ inlineCode (flagName flag)
+ , " " ++ flagDescription flag
+ ]
diff --git a/utils/mkUserGuidePart/Options.hs b/utils/mkUserGuidePart/Options.hs
new file mode 100644
index 0000000000..ab1ab696fe
--- /dev/null
+++ b/utils/mkUserGuidePart/Options.hs
@@ -0,0 +1,66 @@
+module Options (Group(..), groups) where
+
+import Types
+
+import Options.CodeGen
+import Options.CompilerDebugging
+import Options.Cpp
+import Options.FindingImports
+import Options.Interactive
+import Options.InterfaceFiles
+import Options.KeepingIntermediates
+import Options.Language
+import Options.Linking
+import Options.Misc
+import Options.Modes
+import Options.Optimizations
+import Options.OptimizationLevels
+import Options.Packages
+import Options.Phases
+import Options.PhasePrograms
+import Options.PhaseSpecific
+import Options.PlatformSpecific
+import Options.Plugin
+import Options.Profiling
+import Options.ProgramCoverage
+import Options.RecompilationChecking
+import Options.RedirectingOutput
+import Options.TemporaryFiles
+import Options.Verbosity
+import Options.Warnings
+
+-- | A group of flags
+data Group = Group { grpName :: String -- ^ Internal name
+ , grpTitle :: String -- ^ Human-readable title
+ , grpFlags :: [Flag] -- ^ Flags in group
+ }
+
+groups :: [Group]
+groups =
+ [ Group "codegen" "Code generation" codegenOptions
+ , Group "compiler-debugging" "Debugging the compiler" compilerDebuggingOptions
+ , Group "cpp" "C pre-processor" cppOptions
+ , Group "finding-imports" "Finding imports" findingImportsOptions
+ , Group "interactive" "Interactive mode" interactiveOptions
+ , Group "interface-files" "Interface files" interfaceFilesOptions
+ , Group "keeping-intermediates" "Keeping intermediate files" keepingIntermediatesOptions
+ , Group "language" "Language options" languageOptions
+ , Group "linking" "Linking options" linkingOptions
+ , Group "misc" "Miscellaneous options" miscOptions
+ , Group "modes" "Modes of operation" modeOptions
+ , Group "optimization" "Individual optimizations " optimizationsOptions
+ , Group "optimization-levels" "Optimization levels" optimizationLevelsOptions
+ , Group "packages" "Package options" packagesOptions
+ , Group "phases" "Phases of compilation" phaseOptions
+ , Group "phase-programs" "Overriding external programs" phaseProgramsOptions
+ , Group "phase-specific" "Phase-specific options" phaseSpecificOptions
+ , Group "platform-specific" "Platform-specific options" platformSpecificOptions
+ , Group "plugin" "Compiler plugins" pluginOptions
+ , Group "profiling" "Profiling" profilingOptions
+ , Group "program-coverage" "Program coverage" programCoverageOptions
+ , Group "recompilation-checking" "Recompilation checking" recompilationCheckingOptions
+ , Group "redirecting-output" "Redirecting output" redirectingOutputOptions
+ , Group "temporary-files" "Temporary files" temporaryFilesOptions
+ , Group "verbosity" "Verbosity options" verbosityOptions
+ , Group "warnings" "Warnings" warningsOptions
+ ]
diff --git a/utils/mkUserGuidePart/Options/CodeGen.hs b/utils/mkUserGuidePart/Options/CodeGen.hs
new file mode 100644
index 0000000000..0d9cabb27d
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/CodeGen.hs
@@ -0,0 +1,35 @@
+module Options.CodeGen where
+
+import Types
+
+codegenOptions :: [Flag]
+codegenOptions =
+ [ flag { flagName = "-fasm"
+ , flagDescription =
+ "Use the :ref:`native code generator <native-code-gen>`"
+ , flagType = DynamicFlag
+ , flagReverse = "-fllvm"
+ }
+ , flag { flagName = "-fllvm"
+ , flagDescription =
+ "Compile using the :ref:`LLVM code generator <llvm-code-gen>`"
+ , flagType = DynamicFlag
+ , flagReverse = "-fasm"
+ }
+ , flag { flagName = "-fno-code"
+ , flagDescription = "Omit code generation"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fwrite-interface"
+ , flagDescription = "Always write interface files"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fbyte-code"
+ , flagDescription = "Generate byte-code"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fobject-code"
+ , flagDescription = "Generate object code"
+ , flagType = DynamicFlag
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/CompilerDebugging.hs b/utils/mkUserGuidePart/Options/CompilerDebugging.hs
new file mode 100644
index 0000000000..6160f01e8c
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/CompilerDebugging.hs
@@ -0,0 +1,272 @@
+module Options.CompilerDebugging where
+
+import Types
+
+compilerDebuggingOptions :: [Flag]
+compilerDebuggingOptions =
+ [ flag { flagName = "-dcore-lint"
+ , flagDescription = "Turn on internal sanity checking"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-to-file"
+ , flagDescription = "Dump to files instead of stdout"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-asm"
+ , flagDescription = "Dump assembly"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-bcos"
+ , flagDescription = "Dump interpreter byte code"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-cmm"
+ , flagDescription = "Dump C-- output"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-core-stats"
+ , flagDescription =
+ "Print a one-line summary of the size of the Core program at the "++
+ "end of the optimisation pipeline"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-cse"
+ , flagDescription = "Dump CSE output"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-deriv"
+ , flagDescription = "Dump deriving output"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-ds"
+ , flagDescription = "Dump desugarer output"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-foreign"
+ , flagDescription = "Dump ``foreign export`` stubs"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-hpc"
+ , flagDescription = "Dump after instrumentation for program coverage"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-inlinings"
+ , flagDescription = "Dump inlining info"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-llvm"
+ , flagDescription = "Dump LLVM intermediate code"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-occur-anal"
+ , flagDescription = "Dump occurrence analysis output"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-opt-cmm"
+ , flagDescription = "Dump the results of C-- to C-- optimising passes"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-parsed"
+ , flagDescription = "Dump parse tree"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-prep"
+ , flagDescription = "Dump prepared core"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-rn"
+ , flagDescription = "Dump renamer output"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-rule-firings"
+ , flagDescription = "Dump rule firing info"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-rule-rewrites"
+ , flagDescription = "Dump detailed rule firing info"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-rules"
+ , flagDescription = "Dump rules"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-vect"
+ , flagDescription = "Dump vectoriser input and output"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-simpl"
+ , flagDescription = "Dump final simplifier output"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-simpl-iterations"
+ , flagDescription = "Dump output from each simplifier iteration"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-spec"
+ , flagDescription = "Dump specialiser output"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-splices"
+ , flagDescription =
+ "Dump TH spliced expressions, and what they evaluate to"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-stg"
+ , flagDescription = "Dump final STG"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-stranal"
+ , flagDescription = "Dump strictness analyser output"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-strsigs"
+ , flagDescription = "Dump strictness signatures"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-tc"
+ , flagDescription = "Dump typechecker output"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dth-dec-file"
+ , flagDescription =
+ "Show evaluated TH declarations in a .th.hs file"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-types"
+ , flagDescription = "Dump type signatures"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-worker-wrapper"
+ , flagDescription = "Dump worker-wrapper output"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-if-trace"
+ , flagDescription = "Trace interface files"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-tc-trace"
+ , flagDescription = "Trace typechecker"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-vt-trace"
+ , flagDescription = "Trace vectoriser"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-rn-trace"
+ , flagDescription = "Trace renamer"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-rn-stats"
+ , flagDescription = "Renamer stats"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-simpl-stats"
+ , flagDescription = "Dump simplifier stats"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dno-debug-output"
+ , flagDescription = "Suppress unsolicited debugging output"
+ , flagType = StaticFlag
+ }
+ , flag { flagName = "-dppr-debug"
+ , flagDescription = "Turn on debug printing (more verbose)"
+ , flagType = StaticFlag
+ }
+ , flag { flagName = "-dppr-user-length"
+ , flagDescription =
+ "Set the depth for printing expressions in error msgs"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dppr-cols⟨N⟩"
+ , flagDescription =
+ "Set the width of debugging output. For example ``-dppr-cols200``"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dppr-case-as-let"
+ , flagDescription =
+ "Print single alternative case expressions as strict lets."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dsuppress-all"
+ , flagDescription =
+ "In core dumps, suppress everything (except for uniques) that is "++
+ "suppressible."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dsuppress-uniques"
+ , flagDescription =
+ "Suppress the printing of uniques in debug output (easier to use "++
+ "``diff``)"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dsuppress-idinfo"
+ , flagDescription =
+ "Suppress extended information about identifiers where they "++
+ "are bound"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dsuppress-unfoldings"
+ , flagDescription =
+ "Suppress the printing of the stable unfolding of a variable at "++
+ "its binding site"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dsuppress-module-prefixes"
+ , flagDescription =
+ "Suppress the printing of module qualification prefixes"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dsuppress-type-signatures"
+ , flagDescription = "Suppress type signatures"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dsuppress-type-applications"
+ , flagDescription = "Suppress type applications"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dsuppress-coercions"
+ , flagDescription =
+ "Suppress the printing of coercions in Core dumps to make them "++
+ "shorter"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dsource-stats"
+ , flagDescription = "Dump haskell source stats"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dcmm-lint"
+ , flagDescription = "C-- pass sanity checking"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dstg-lint"
+ , flagDescription = "STG pass sanity checking"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dstg-stats"
+ , flagDescription = "Dump STG stats"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dverbose-core2core"
+ , flagDescription = "Show output from each core-to-core pass"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dverbose-stg2stg"
+ , flagDescription = "Show output from each STG-to-STG pass"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dshow-passes"
+ , flagDescription = "Print out each pass name as it happens"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dfaststring-stats"
+ , flagDescription =
+ "Show statistics for fast string usage when finished"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-frule-check"
+ , flagDescription =
+ "Report sites with rules that could have fired but didn't. "++
+ "Takes a string argument."
+ , flagType = DynamicFlag
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/Cpp.hs b/utils/mkUserGuidePart/Options/Cpp.hs
new file mode 100644
index 0000000000..ae5b122bf9
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/Cpp.hs
@@ -0,0 +1,25 @@
+module Options.Cpp where
+
+import Types
+
+cppOptions :: [Flag]
+cppOptions =
+ [ flag { flagName = "-cpp"
+ , flagDescription = "Run the C pre-processor on Haskell source files"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-D⟨symbol⟩[=⟨value⟩]"
+ , flagDescription = "Define a symbol in the C pre-processor"
+ , flagType = DynamicFlag
+ , flagReverse = "-U⟨symbol⟩"
+ }
+ , flag { flagName = "-U⟨symbol⟩"
+ , flagDescription = "Undefine a symbol in the C pre-processor"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-I⟨dir⟩"
+ , flagDescription =
+ "Add ⟨dir⟩ to the directory search list for ``#include`` files"
+ , flagType = DynamicFlag
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/FindingImports.hs b/utils/mkUserGuidePart/Options/FindingImports.hs
new file mode 100644
index 0000000000..4302055c82
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/FindingImports.hs
@@ -0,0 +1,15 @@
+module Options.FindingImports where
+
+import Types
+
+findingImportsOptions :: [Flag]
+findingImportsOptions =
+ [ flag { flagName = "-i ⟨dir1⟩:⟨dir2⟩:..."
+ , flagDescription = "add ⟨dir⟩, ⟨dir2⟩, etc. to import path"
+ , flagType = DynamicSettableFlag
+ }
+ , flag { flagName = "-i"
+ , flagDescription = "Empty the import directory list"
+ , flagType = DynamicSettableFlag
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/Interactive.hs b/utils/mkUserGuidePart/Options/Interactive.hs
new file mode 100644
index 0000000000..142e207e67
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/Interactive.hs
@@ -0,0 +1,65 @@
+module Options.Interactive where
+
+import Types
+
+interactiveOptions :: [Flag]
+interactiveOptions =
+ [ flag { flagName = "-ignore-dot-ghci"
+ , flagDescription = "Disable reading of ``.ghci`` files"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ghci-script"
+ , flagDescription = "Read additional ``.ghci`` files"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fbreak-on-error"
+ , flagDescription =
+ ":ref:`Break on uncaught exceptions and errors " ++
+ "<ghci-debugger-exceptions>`"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-break-on-error"
+ }
+ , flag { flagName = "-fbreak-on-exception"
+ , flagDescription =
+ ":ref:`Break on any exception thrown <ghci-debugger-exceptions>`"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-break-on-exception"
+ }
+ , flag { flagName = "-fghci-hist-size=⟨n⟩"
+ , flagDescription =
+ "Set the number of entries GHCi keeps for ``:history``." ++
+ " See :ref:`ghci-debugger`."
+ , flagType = DynamicFlag
+ , flagReverse = "(default is 50)"
+ }
+ , flag { flagName = "-fprint-evld-with-show"
+ , flagDescription =
+ "Enable usage of ``Show`` instances in ``:print``. "++
+ "See :ref:`breakpoints`."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-print-evld-with-show"
+ }
+ , flag { flagName = "-fprint-bind-result"
+ , flagDescription =
+ ":ref:`Turn on printing of binding results in GHCi <ghci-stmts>`"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-print-bind-result"
+ }
+ , flag { flagName = "-fno-print-bind-contents"
+ , flagDescription =
+ ":ref:`Turn off printing of binding contents in GHCi <breakpoints>`"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fno-implicit-import-qualified"
+ , flagDescription =
+ ":ref:`Turn off implicit qualified import of everything in GHCi " ++
+ "<ghci-import-qualified>`"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-interactive-print"
+ , flagDescription =
+ ":ref:`Select the function to use for printing evaluated " ++
+ "expressions in GHCi <ghci-interactive-print>`"
+ , flagType = DynamicFlag
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/InterfaceFiles.hs b/utils/mkUserGuidePart/Options/InterfaceFiles.hs
new file mode 100644
index 0000000000..314e0ebb69
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/InterfaceFiles.hs
@@ -0,0 +1,23 @@
+module Options.InterfaceFiles where
+
+import Types
+
+interfaceFilesOptions :: [Flag]
+interfaceFilesOptions =
+ [ flag { flagName = "-ddump-hi"
+ , flagDescription = "Dump the new interface to stdout"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-hi-diffs"
+ , flagDescription = "Show the differences vs. the old interface"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ddump-minimal-imports"
+ , flagDescription = "Dump a minimal set of imports"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "--show-iface ⟨file⟩"
+ , flagDescription = "See :ref:`modes`."
+ , flagType = ModeFlag
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/KeepingIntermediates.hs b/utils/mkUserGuidePart/Options/KeepingIntermediates.hs
new file mode 100644
index 0000000000..9c93aedfeb
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/KeepingIntermediates.hs
@@ -0,0 +1,23 @@
+module Options.KeepingIntermediates where
+
+import Types
+
+keepingIntermediatesOptions :: [Flag]
+keepingIntermediatesOptions =
+ [ flag { flagName = "-keep-hc-file, -keep-hc-files"
+ , flagDescription = "retain intermediate ``.hc`` files"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-keep-llvm-file, -keep-llvm-files"
+ , flagDescription = "retain intermediate LLVM ``.ll`` files"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-keep-s-file, -keep-s-files"
+ , flagDescription = "retain intermediate ``.s`` files"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-keep-tmp-files"
+ , flagDescription = "retain all intermediate temporary files"
+ , flagType = DynamicFlag
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/Language.hs b/utils/mkUserGuidePart/Options/Language.hs
new file mode 100644
index 0000000000..17416ffbf1
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/Language.hs
@@ -0,0 +1,735 @@
+module Options.Language where
+
+import Types
+
+languageOptions :: [Flag]
+languageOptions =
+ [ flag { flagName = "-fconstraint-solver-iterations=⟨n⟩"
+ , flagDescription =
+ "*default: 4.* Set the iteration limit for the type-constraint "++
+ "solver. Typically one iteration suffices; so please "++
+ "yell if you find you need to set it higher than the default. "++
+ "Zero means infinity."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-freduction-depth=⟨n⟩"
+ , flagDescription =
+ "*default: 200.* Set the :ref:`limit for type simplification "++
+ "<undecidable-instances>`. Zero means infinity."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fcontext-stack=⟨n⟩"
+ , flagDescription =
+ "Deprecated. Use ``-freduction-depth=⟨n⟩`` instead."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fglasgow-exts"
+ , flagDescription =
+ "Deprecated. Enable most language extensions; "++
+ "see :ref:`options-language` for exactly which ones."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-glasgow-exts"
+ }
+ , flag { flagName = "-firrefutable-tuples"
+ , flagDescription = "Make tuple pattern matching irrefutable"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-irrefutable-tuples"
+ }
+ , flag { flagName = "-fpackage-trust"
+ , flagDescription =
+ "Enable :ref:`Safe Haskell <safe-haskell>` trusted package "++
+ "requirement for trustworthy modules."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ftype-function-depth=⟨n⟩"
+ , flagDescription = "Deprecated. Use ``-freduction-depth=⟨n⟩`` instead."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-XAllowAmbiguousTypes"
+ , flagDescription =
+ "Allow the user to write :ref:`ambiguous types <ambiguity>`, and "++
+ "the type inference engine to infer them."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoAllowAmbiguousTypes"
+ , flagSince = "7.8.1"
+ }
+ , flag { flagName = "-XArrows"
+ , flagDescription =
+ "Enable :ref:`arrow notation <arrow-notation>` extension"
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoArrows"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XApplicativeDo"
+ , flagDescription =
+ "Enable :ref:`Applicative do-notation desugaring <applicative-do>`"
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoApplicativeDo"
+ , flagSince = "7.12.1"
+ }
+ , flag { flagName = "-XAutoDeriveTypeable"
+ , flagDescription =
+ "As of GHC 7.10, this option is not needed, and should not be "++
+ "used. Previously this would automatically :ref:`derive Typeable "++
+ "instances for every datatype and type class declaration "++
+ "<deriving-typeable>`. Implies ``-XDeriveDataTypeable``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoAutoDeriveTypeable"
+ , flagSince = "7.8.1"
+ }
+ , flag { flagName = "-XBangPatterns"
+ , flagDescription = "Enable :ref:`bang patterns <bang-patterns>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoBangPatterns"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XBinaryLiterals"
+ , flagDescription =
+ "Enable support for :ref:`binary literals <binary-literals>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoBinaryLiterals"
+ , flagSince = "7.10.1"
+ }
+ , flag { flagName = "-XCApiFFI"
+ , flagDescription =
+ "Enable :ref:`the CAPI calling convention <ffi-capi>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoCAPIFFI"
+ , flagSince = "7.10.1"
+ }
+ , flag { flagName = "-XConstrainedClassMethods"
+ , flagDescription =
+ "Enable :ref:`constrained class methods <class-method-types>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoConstrainedClassMethods"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XConstraintKinds"
+ , flagDescription =
+ "Enable a :ref:`kind of constraints <constraint-kind>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoConstraintKinds"
+ , flagSince = "7.4.1"
+ }
+ , flag { flagName = "-XCPP"
+ , flagDescription =
+ "Enable the :ref:`C preprocessor <c-pre-processor>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoCPP"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XDataKinds"
+ , flagDescription = "Enable :ref:`datatype promotion <promotion>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoDataKinds"
+ , flagSince = "7.4.1"
+ }
+ , flag { flagName = "-XDefaultSignatures"
+ , flagDescription =
+ "Enable :ref:`default signatures <class-default-signatures>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoDefaultSignatures"
+ , flagSince = "7.2.1"
+ }
+ , flag { flagName = "-XDeriveAnyClass"
+ , flagDescription =
+ "Enable :ref:`deriving for any class <derive-any-class>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoDeriveAnyClass"
+ , flagSince = "7.10.1"
+ }
+ , flag { flagName = "-XDeriveDataTypeable"
+ , flagDescription =
+ "Enable ``deriving`` for the :ref:`Data class "++
+ "<deriving-typeable>`. Implied by ``-XAutoDeriveTypeable``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoDeriveDataTypeable"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XDeriveFunctor"
+ , flagDescription =
+ "Enable :ref:`deriving for the Functor class <deriving-extra>`. "++
+ "Implied by ``-XDeriveTraversable``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoDeriveFunctor"
+ , flagSince = "7.10.1"
+ }
+ , flag { flagName = "-XDeriveFoldable"
+ , flagDescription =
+ "Enable :ref:`deriving for the Foldable class <deriving-extra>`. "++
+ "Implied by ``-XDeriveTraversable``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoDeriveFoldable"
+ , flagSince = "7.10.1"
+ }
+ , flag { flagName = "-XDeriveGeneric"
+ , flagDescription =
+ "Enable :ref:`deriving for the Generic class <deriving-typeable>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoDeriveGeneric"
+ , flagSince = "7.2.1"
+ }
+ , flag { flagName = "-XDeriveGeneric"
+ , flagDescription =
+ "Enable :ref:`deriving for the Generic class <deriving-typeable>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoDeriveGeneric"
+ , flagSince = "7.2.1"
+ }
+ , flag { flagName = "-XDeriveLift"
+ , flagDescription =
+ "Enable :ref:`deriving for the Lift class <deriving-lift>`"
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoDeriveLift"
+ , flagSince = "7.2.1"
+ }
+ , flag { flagName = "-XDeriveTraversable"
+ , flagDescription =
+ "Enable :ref:`deriving for the Traversable class <deriving-extra>`. "++
+ "Implies ``-XDeriveFunctor`` and ``-XDeriveFoldable``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoDeriveTraversable"
+ , flagSince = "7.10.1"
+ }
+ , flag { flagName = "-XDisambiguateRecordFields"
+ , flagDescription =
+ "Enable :ref:`record field disambiguation <disambiguate-fields>`. "++
+ "Implied by ``-XRecordWildCards``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoDisambiguateRecordFields"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XEmptyCase"
+ , flagDescription =
+ "Allow :ref:`empty case alternatives <empty-case>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoEmptyCase"
+ , flagSince = "7.8.1"
+ }
+ , flag { flagName = "-XEmptyDataDecls"
+ , flagDescription = "Enable empty data declarations."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoEmptyDataDecls"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XExistentialQuantification"
+ , flagDescription =
+ "Enable :ref:`existential quantification <existential-quantification>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoExistentialQuantification"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XExplicitForAll"
+ , flagDescription =
+ "Enable :ref:`explicit universal quantification <explicit-foralls>`."++
+ " Implied by ``-XScopedTypeVariables``, ``-XLiberalTypeSynonyms``,"++
+ " ``-XRankNTypes`` and ``-XExistentialQuantification``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoExplicitForAll"
+ , flagSince = "6.12.1"
+ }
+ , flag { flagName = "-XExplicitNamespaces"
+ , flagDescription =
+ "Enable using the keyword ``type`` to specify the namespace of "++
+ "entries in imports and exports (:ref:`explicit-namespaces`). "++
+ "Implied by ``-XTypeOperators`` and ``-XTypeFamilies``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoExplicitNamespaces"
+ , flagSince = "7.6.1"
+ }
+ , flag { flagName = "-XExtendedDefaultRules"
+ , flagDescription =
+ "Use GHCi's :ref:`extended default rules <extended-default-rules>` "++
+ "in a normal module."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoExtendedDefaultRules"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XFlexibleContexts"
+ , flagDescription =
+ "Enable :ref:`flexible contexts <flexible-contexts>`. Implied by "++
+ "``-XImplicitParams``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoFlexibleContexts"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XFlexibleInstances"
+ , flagDescription =
+ "Enable :ref:`flexible instances <instance-rules>`. "++
+ "Implies ``-XTypeSynonymInstances``. "++
+ "Implied by ``-XImplicitParams``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoFlexibleInstances"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XForeignFunctionInterface"
+ , flagDescription =
+ "Enable :ref:`foreign function interface <ffi>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoForeignFunctionInterface"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XFunctionalDependencies"
+ , flagDescription =
+ "Enable :ref:`functional dependencies <functional-dependencies>`. "++
+ "Implies ``-XMultiParamTypeClasses``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoFunctionalDependencies"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XGADTs"
+ , flagDescription =
+ "Enable :ref:`generalised algebraic data types <gadt>`. "++
+ "Implies ``-XGADTSyntax`` and ``-XMonoLocalBinds``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoGADTs"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XGADTSyntax"
+ , flagDescription =
+ "Enable :ref:`generalised algebraic data type syntax <gadt-style>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoGADTSyntax"
+ , flagSince = "7.2.1"
+ }
+ , flag { flagName = "-XGeneralizedNewtypeDeriving"
+ , flagDescription =
+ "Enable :ref:`newtype deriving <newtype-deriving>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoGeneralizedNewtypeDeriving"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XGenerics"
+ , flagDescription =
+ "Deprecated, does nothing. No longer enables "++
+ ":ref:`generic classes <generic-classes>`. See also GHC's support "++
+ "for :ref:`generic programming <generic-programming>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoGenerics"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XImplicitParams"
+ , flagDescription =
+ "Enable :ref:`Implicit Parameters <implicit-parameters>`. "++
+ "Implies ``-XFlexibleContexts`` and ``-XFlexibleInstances``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoImplicitParams"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XNoImplicitPrelude"
+ , flagDescription =
+ "Don't implicitly ``import Prelude``. "++
+ "Implied by ``-XRebindableSyntax``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XImplicitPrelude"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XImpredicativeTypes"
+ , flagDescription =
+ "Enable :ref:`impredicative types <impredicative-polymorphism>`. "++
+ "Implies ``-XRankNTypes``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoImpredicativeTypes"
+ , flagSince = "6.10.1"
+ }
+ , flag { flagName = "-XIncoherentInstances"
+ , flagDescription =
+ "Enable :ref:`incoherent instances <instance-overlap>`. "++
+ "Implies ``-XOverlappingInstances``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoIncoherentInstances"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XInstanceSigs"
+ , flagDescription =
+ "Enable :ref:`instance signatures <instance-sigs>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoInstanceSigs"
+ , flagSince = "7.10.1"
+ }
+ , flag { flagName = "-XInterruptibleFFI"
+ , flagDescription = "Enable interruptible FFI."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoInterruptibleFFI"
+ , flagSince = "7.2.1"
+ }
+ , flag { flagName = "-XKindSignatures"
+ , flagDescription =
+ "Enable :ref:`kind signatures <kinding>`. "++
+ "Implied by ``-XTypeFamilies`` and ``-XPolyKinds``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoKindSignatures"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XLambdaCase"
+ , flagDescription =
+ "Enable :ref:`lambda-case expressions <lambda-case>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoLambdaCase"
+ , flagSince = "7.6.1"
+ }
+ , flag { flagName = "-XLiberalTypeSynonyms"
+ , flagDescription =
+ "Enable :ref:`liberalised type synonyms <type-synonyms>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoLiberalTypeSynonyms"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XMagicHash"
+ , flagDescription =
+ "Allow ``#`` as a :ref:`postfix modifier on identifiers <magic-hash>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoMagicHash"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XMonadComprehensions"
+ , flagDescription =
+ "Enable :ref:`monad comprehensions <monad-comprehensions>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoMonadComprehensions"
+ , flagSince = "7.2.1"
+ }
+ , flag { flagName = "-XMonoLocalBinds"
+ , flagDescription =
+ "Enable :ref:`do not generalise local bindings <mono-local-binds>`. "++
+ "Implied by ``-XTypeFamilies`` and ``-XGADTs``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoMonoLocalBinds"
+ , flagSince = "6.12.1"
+ }
+ , flag { flagName = "-XNoMonomorphismRestriction"
+ , flagDescription =
+ "Disable the :ref:`monomorphism restriction <monomorphism>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XMonomorphismRestriction"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XMultiParamTypeClasses"
+ , flagDescription =
+ "Enable :ref:`multi parameter type classes "++
+ "<multi-param-type-classes>`. Implied by "++
+ "``-XFunctionalDependencies``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoMultiParamTypeClasses"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XMultiWayIf"
+ , flagDescription =
+ "Enable :ref:`multi-way if-expressions <multi-way-if>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoMultiWayIf"
+ , flagSince = "7.6.1"
+ }
+ , flag { flagName = "-XNamedFieldPuns"
+ , flagDescription = "Enable :ref:`record puns <record-puns>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoNamedFieldPuns"
+ , flagSince = "6.10.1"
+ }
+ , flag { flagName = "-XNamedWildCards"
+ , flagDescription = "Enable :ref:`named wildcards <named-wildcards>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoNamedWildCards"
+ , flagSince = "7.10.1"
+ }
+ , flag { flagName = "-XNegativeLiterals"
+ , flagDescription =
+ "Enable support for :ref:`negative literals <negative-literals>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoNegativeLiterals"
+ , flagSince = "7.8.1"
+ }
+ , flag { flagName = "-XNoNPlusKPatterns"
+ , flagDescription = "Disable support for ``n+k`` patterns."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNPlusKPatterns"
+ , flagSince = "6.12.1"
+ }
+ , flag { flagName = "-XNullaryTypeClasses"
+ , flagDescription =
+ "Deprecated, does nothing. :ref:`nullary (no parameter) type "++
+ "classes <nullary-type-classes>` are now enabled using "++
+ "``-XMultiParamTypeClasses``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoNullaryTypeClasses"
+ , flagSince = "7.8.1"
+ }
+ , flag { flagName = "-XNumDecimals"
+ , flagDescription =
+ "Enable support for 'fractional' integer literals."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoNumDecimals"
+ , flagSince = "7.8.1"
+ }
+ , flag { flagName = "-XOverlappingInstances"
+ , flagDescription =
+ "Enable :ref:`overlapping instances <instance-overlap>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoOverlappingInstances"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XOverloadedLists"
+ , flagDescription =
+ "Enable :ref:`overloaded lists <overloaded-lists>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoOverloadedLists"
+ , flagSince = "7.8.1"
+ }
+ , flag { flagName = "-XOverloadedStrings"
+ , flagDescription =
+ "Enable :ref:`overloaded string literals <overloaded-strings>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoOverloadedStrings"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XPackageImports"
+ , flagDescription =
+ "Enable :ref:`package-qualified imports <package-imports>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoPackageImports"
+ , flagSince = "6.10.1"
+ }
+ , flag { flagName = "-XParallelArrays"
+ , flagDescription =
+ "Enable parallel arrays. Implies ``-XParallelListComp``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoParallelArrays"
+ , flagSince = "7.4.1"
+ }
+ , flag { flagName = "-XParallelListComp"
+ , flagDescription =
+ "Enable :ref:`parallel list comprehensions "++
+ "<parallel-list-comprehensions>`. "++
+ "Implied by ``-XParallelArrays``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoParallelListComp"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XPartialTypeSignatures"
+ , flagDescription =
+ "Enable :ref:`partial type signatures <partial-type-signatures>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoPartialTypeSignatures"
+ , flagSince = "7.10.1"
+ }
+ , flag { flagName = "-XPatternGuards"
+ , flagDescription = "Enable :ref:`pattern guards <pattern-guards>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoPatternGuards"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XPatternSynonyms"
+ , flagDescription =
+ "Enable :ref:`pattern synonyms <pattern-synonyms>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoPatternSynonyms"
+ , flagSince = "7.10.1"
+ }
+ , flag { flagName = "-XPolyKinds"
+ , flagDescription =
+ "Enable :ref:`kind polymorphism <kind-polymorphism>`. "++
+ "Implies ``-XKindSignatures``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoPolyKinds"
+ , flagSince = "7.4.1"
+ }
+ , flag { flagName = "-XPolymorphicComponents"
+ , flagDescription =
+ "Enable :ref:`polymorphic components for data constructors "++
+ "<universal-quantification>`. Synonym for ``-XRankNTypes``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoPolymorphicComponents"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XPostfixOperators"
+ , flagDescription =
+ "Enable :ref:`postfix operators <postfix-operators>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoPostfixOperators"
+ , flagSince = "7.10.1"
+ }
+ , flag { flagName = "-XQuasiQuotes"
+ , flagDescription = "Enable :ref:`quasiquotation <th-quasiquotation>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoQuasiQuotes"
+ , flagSince = "6.10.1"
+ }
+ , flag { flagName = "-XRank2Types"
+ , flagDescription =
+ "Enable :ref:`rank-2 types <universal-quantification>`. "++
+ "Synonym for ``-XRankNTypes``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoRank2Types"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XRankNTypes"
+ , flagDescription =
+ "Enable :ref:`rank-N types <universal-quantification>`. "++
+ "Implied by ``-XImpredicativeTypes``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoRankNTypes"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XRebindableSyntax"
+ , flagDescription =
+ "Employ :ref:`rebindable syntax <rebindable-syntax>`. "++
+ "Implies ``-XNoImplicitPrelude``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoRebindableSyntax"
+ , flagSince = "7.0.1"
+ }
+ , flag { flagName = "-XRecordWildCards"
+ , flagDescription =
+ "Enable :ref:`record wildcards <record-wildcards>`. "++
+ "Implies ``-XDisambiguateRecordFields``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoRecordWildCards"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XRecursiveDo"
+ , flagDescription =
+ "Enable :ref:`recursive do (mdo) notation <recursive-do-notation>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoRecursiveDo"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XRelaxedPolyRec"
+ , flagDescription =
+ "*(deprecated)* Relaxed checking for :ref:`mutually-recursive "++
+ "polymorphic functions <typing-binds>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoRelaxedPolyRec"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XRoleAnnotations"
+ , flagDescription =
+ "Enable :ref:`role annotations <role-annotations>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoRoleAnnotations"
+ , flagSince = "7.10.1"
+ }
+ , flag { flagName = "-XSafe"
+ , flagDescription =
+ "Enable the :ref:`Safe Haskell <safe-haskell>` Safe mode."
+ , flagType = DynamicFlag
+ , flagSince = "7.2.1"
+ }
+ , flag { flagName = "-XScopedTypeVariables"
+ , flagDescription =
+ "Enable :ref:`lexically-scoped type variables "++
+ "<scoped-type-variables>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoScopedTypeVariables"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XStandaloneDeriving"
+ , flagDescription =
+ "Enable :ref:`standalone deriving <stand-alone-deriving>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoStandaloneDeriving"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XStrictData"
+ , flagDescription =
+ "Enable :ref:`default strict datatype fields <strict-data>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoStrictData"
+ }
+ , flag { flagName = "-XTemplateHaskell"
+ , flagDescription =
+ "Enable :ref:`Template Haskell <template-haskell>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoTemplateHaskell"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XNoTraditionalRecordSyntax"
+ , flagDescription =
+ "Disable support for traditional record syntax "++
+ "(as supported by Haskell 98) ``C {f = x}``"
+ , flagType = DynamicFlag
+ , flagReverse = "-XTraditionalRecordSyntax"
+ , flagSince = "7.4.1"
+ }
+ , flag { flagName = "-XTransformListComp"
+ , flagDescription =
+ "Enable :ref:`generalised list comprehensions "++
+ "<generalised-list-comprehensions>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoTransformListComp"
+ , flagSince = "6.10.1"
+ }
+ , flag { flagName = "-XTrustworthy"
+ , flagDescription =
+ "Enable the :ref:`Safe Haskell <safe-haskell>` Trustworthy mode."
+ , flagType = DynamicFlag
+ , flagSince = "7.2.1"
+ }
+ , flag { flagName = "-XTupleSections"
+ , flagDescription = "Enable :ref:`tuple sections <tuple-sections>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoTupleSections"
+ , flagSince = "7.10.1"
+ }
+ , flag { flagName = "-XTypeFamilies"
+ , flagDescription =
+ "Enable :ref:`type families <type-families>`. "++
+ "Implies ``-XExplicitNamespaces``, ``-XKindSignatures``, "++
+ "and ``-XMonoLocalBinds``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoTypeFamilies"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XTypeOperators"
+ , flagDescription =
+ "Enable :ref:`type operators <type-operators>`. "++
+ "Implies ``-XExplicitNamespaces``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoTypeOperators"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XTypeSynonymInstances"
+ , flagDescription =
+ "Enable :ref:`type synonyms in instance heads "++
+ "<flexible-instance-head>`. Implied by ``-XFlexibleInstances``."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoTypeSynonymInstances"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XUnboxedTuples"
+ , flagDescription = "Enable :ref:`unboxed tuples <unboxed-tuples>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoUnboxedTuples"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XUndecidableInstances"
+ , flagDescription =
+ "Enable :ref:`undecidable instances <undecidable-instances>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoUndecidableInstances"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XUnicodeSyntax"
+ , flagDescription = "Enable :ref:`unicode syntax <unicode-syntax>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoUnicodeSyntax"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XUnliftedFFITypes"
+ , flagDescription = "Enable unlifted FFI types."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoUnliftedFFITypes"
+ , flagSince = "6.8.1"
+ }
+ , flag { flagName = "-XUnsafe"
+ , flagDescription =
+ "Enable :ref:`Safe Haskell <safe-haskell>` Unsafe mode."
+ , flagType = DynamicFlag
+ , flagSince = "7.4.1"
+ }
+ , flag { flagName = "-XViewPatterns"
+ , flagDescription = "Enable :ref:`view patterns <view-patterns>`."
+ , flagType = DynamicFlag
+ , flagReverse = "-XNoViewPatterns"
+ , flagSince = "6.10.1"
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/Linking.hs b/utils/mkUserGuidePart/Options/Linking.hs
new file mode 100644
index 0000000000..cc42db80ff
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/Linking.hs
@@ -0,0 +1,162 @@
+module Options.Linking where
+
+import Types
+
+linkingOptions :: [Flag]
+linkingOptions =
+ [ flag { flagName = "-shared"
+ , flagDescription =
+ "Generate a shared library (as opposed to an executable)"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-staticlib"
+ , flagDescription =
+ "On Darwin/OS X/iOS only, generate a standalone static library " ++
+ "(as opposed to an executable). This is the usual way to " ++
+ "compile for iOS."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fPIC"
+ , flagDescription =
+ "Generate position-independent code (where available)"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dynamic"
+ , flagDescription = "Use dynamic Haskell libraries (if available)"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dynamic-too"
+ , flagDescription =
+ "Build dynamic object files *as well as* static object files " ++
+ "during compilation"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dyno"
+ , flagDescription =
+ "Set the output path for the *dynamically* linked objects"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dynosuf"
+ , flagDescription = "Set the output suffix for dynamic object files"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dynload"
+ , flagDescription =
+ "Selects one of a number of modes for finding shared libraries at runtime."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-framework⟨name⟩"
+ , flagDescription =
+ "On Darwin/OS X/iOS only, link in the framework ⟨name⟩. This " ++
+ "option corresponds to the ``-framework`` option for Apple's Linker."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-framework-path⟨name⟩"
+ , flagDescription =
+ "On Darwin/OS X/iOS only, add ⟨dir⟩ to the list of directories " ++
+ "searched for frameworks. This option corresponds to the ``-F`` "++
+ "option for Apple's Linker."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-l⟨lib⟩"
+ , flagDescription = "Link in library ⟨lib⟩"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-L⟨dir⟩"
+ , flagDescription =
+ "Add ⟨dir⟩ to the list of directories searched for libraries"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-main-is"
+ , flagDescription = "Set main module and function"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "--mk-dll"
+ , flagDescription = "DLL-creation mode (Windows only)"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-no-hs-main"
+ , flagDescription = "Don't assume this program contains ``main``"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-rtsopts,-rtsopts={none,some,all}"
+ , flagDescription =
+ "Control whether the RTS behaviour can be tweaked via command-line"++
+ "flags and the ``GHCRTS`` environment variable. Using ``none`` " ++
+ "means no RTS flags can be given; ``some`` means only a minimum " ++
+ "of safe options can be given (the default), and ``all`` (or no " ++
+ "argument at all) means that all RTS flags are permitted."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-with-rtsopts=opts"
+ , flagDescription = "Set the default RTS options to ⟨opts⟩."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-no-rtsopts-suggestions"
+ , flagDescription =
+ "Don't print RTS suggestions about linking with ``-rtsopts``."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-no-link"
+ , flagDescription = "Omit linking"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-split-objs"
+ , flagDescription = "Split objects (for libraries)"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-static"
+ , flagDescription = "Use static Haskell libraries"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-threaded"
+ , flagDescription = "Use the threaded runtime"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-debug"
+ , flagDescription = "Use the debugging runtime"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ticky"
+ , flagDescription =
+ "For linking, this simply implies ``-debug``; "++
+ "see :ref:`ticky-ticky`."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-eventlog"
+ , flagDescription = "Enable runtime event tracing"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fno-gen-manifest"
+ , flagDescription = "Do not generate a manifest file (Windows only)"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fno-embed-manifest"
+ , flagDescription =
+ "Do not embed the manifest in the executable (Windows only)"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fno-shared-implib"
+ , flagDescription =
+ "Don't generate an import library for a DLL (Windows only)"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dylib-install-name ⟨path⟩"
+ , flagDescription =
+ "Set the install name (via ``-install_name`` passed to Apple's " ++
+ "linker), specifying the full install path of the library file. " ++
+ "Any libraries or executables that link with it later will pick " ++
+ "up that path as their runtime search location for it. " ++
+ "(Darwin/OS X only)"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-rdynamic"
+ , flagDescription =
+ "This instructs the linker to add all symbols, not only used " ++
+ "ones, to the dynamic symbol table. Currently Linux and " ++
+ "Windows/MinGW32 only. This is equivalent to using " ++
+ "``-optl -rdynamic`` on Linux, and ``-optl -export-all-symbols`` " ++
+ "on Windows."
+ , flagType = DynamicFlag
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/Misc.hs b/utils/mkUserGuidePart/Options/Misc.hs
new file mode 100644
index 0000000000..d6a4c4eaec
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/Misc.hs
@@ -0,0 +1,32 @@
+module Options.Misc where
+
+import Types
+
+miscOptions :: [Flag]
+miscOptions =
+ [ flag { flagName = "-jN"
+ , flagDescription =
+ "When compiling with ``--make``, compile ⟨N⟩ modules in parallel."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fno-hi-version-check"
+ , flagDescription = "Don't complain about ``.hi`` file mismatches"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fhistory-size"
+ , flagDescription = "Set simplification history size"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fno-ghci-history"
+ , flagDescription =
+ "Do not use the load/store the GHCi command history from/to "++
+ "``ghci_history``."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fno-ghci-sandbox"
+ , flagDescription =
+ "Turn off the GHCi sandbox. Means computations are run in "++
+ "the main thread, rather than a forked thread."
+ , flagType = DynamicFlag
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/Modes.hs b/utils/mkUserGuidePart/Options/Modes.hs
new file mode 100644
index 0000000000..57aaef26f2
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/Modes.hs
@@ -0,0 +1,63 @@
+module Options.Modes where
+
+import Types
+
+modeOptions :: [Flag]
+modeOptions =
+ [ flag { flagName = "--help,-?"
+ , flagDescription = "Display help"
+ , flagType = ModeFlag
+ }
+ , flag { flagName = "--interactive"
+ , flagDescription =
+ "Interactive mode - normally used by just running ``ghci``; "++
+ "see :ref:`ghci` for details."
+ , flagType = ModeFlag
+ }
+ , flag { flagName = "--make"
+ , flagDescription =
+ "Build a multi-module Haskell program, automatically figuring out "++
+ "dependencies. Likely to be much easier, and faster, than using "++
+ "``make``; see :ref:`make-mode` for details."
+ , flagType = ModeFlag
+ }
+ , flag { flagName = "-e expr"
+ , flagDescription =
+ "Evaluate ``expr``; see :ref:`eval-mode` for details."
+ , flagType = ModeFlag
+ }
+ , flag { flagName = "--show-iface"
+ , flagDescription = "display the contents of an interface file."
+ , flagType = ModeFlag
+ }
+ , flag { flagName = "-M"
+ , flagDescription =
+ "denerate dependency information suitable for use in a "++
+ "``Makefile``; see :ref:`makefile-dependencies` for details."
+ , flagType = ModeFlag
+ }
+ , flag { flagName = "--supported-extensions, --supported-languages"
+ , flagDescription = "display the supported language extensions"
+ , flagType = ModeFlag
+ }
+ , flag { flagName = "--show-options"
+ , flagDescription = "display the supported command line options"
+ , flagType = ModeFlag
+ }
+ , flag { flagName = "--info"
+ , flagDescription = "display information about the compiler"
+ , flagType = ModeFlag
+ }
+ , flag { flagName = "--version, -V"
+ , flagDescription = "display GHC version"
+ , flagType = ModeFlag
+ }
+ , flag { flagName = "--numeric-version"
+ , flagDescription = "display GHC version (numeric only)"
+ , flagType = ModeFlag
+ }
+ , flag { flagName = "--print-libdir"
+ , flagDescription = "display GHC library directory"
+ , flagType = ModeFlag
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/OptimizationLevels.hs b/utils/mkUserGuidePart/Options/OptimizationLevels.hs
new file mode 100644
index 0000000000..a57fc5291b
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/OptimizationLevels.hs
@@ -0,0 +1,29 @@
+module Options.OptimizationLevels where
+
+import Types
+
+optimizationLevelsOptions :: [Flag]
+optimizationLevelsOptions =
+ [ flag { flagName = "-O0"
+ , flagDescription = "Disable optimisations (default)"
+ , flagType = DynamicFlag
+ , flagReverse = "-O"
+ }
+ , flag { flagName = "-O, -O1"
+ , flagDescription = "Enable level 1 optimisations"
+ , flagType = DynamicFlag
+ , flagReverse = "-O0"
+ }
+ , flag { flagName = "-O2"
+ , flagDescription = "Enable level 2 optimisations"
+ , flagType = DynamicFlag
+ , flagReverse = "-O0"
+ }
+ , flag { flagName = "-Odph"
+ , flagDescription =
+ "Enable level 2 optimisations, set "++
+ "``-fmax-simplifier-iterations=20`` "++
+ "and ``-fsimplifier-phases=3``."
+ , flagType = DynamicFlag
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/Optimizations.hs b/utils/mkUserGuidePart/Options/Optimizations.hs
new file mode 100644
index 0000000000..0082a210fb
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/Optimizations.hs
@@ -0,0 +1,344 @@
+module Options.Optimizations where
+
+import Types
+
+optimizationsOptions :: [Flag]
+optimizationsOptions =
+ [ flag { flagName = "-fcall-arity"
+ , flagDescription =
+ "Enable call-arity optimisation. Implied by ``-O``."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-call-arity"
+ }
+ , flag { flagName = "-fcase-merge"
+ , flagDescription = "Enable case-merging. Implied by ``-O``."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-case-merge"
+ }
+ , flag { flagName = "-fcmm-elim-common-blocks"
+ , flagDescription =
+ "Enable Cmm common block elimination. Implied by ``-O``."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-cmm-elim-common-blocks"
+ }
+ , flag { flagName = "-fcmm-sink"
+ , flagDescription = "Enable Cmm sinking. Implied by ``-O``."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-cmm-sink"
+ }
+ , flag { flagName = "-fcpr-anal"
+ , flagDescription =
+ "Turn on CPR analysis in the demand analyser. Implied by ``-O``."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-cpr-anal"
+ }
+ , flag { flagName = "-fcse"
+ , flagDescription =
+ "Enable common sub-expression elimination. Implied by ``-O``."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-cse"
+ }
+ , flag { flagName = "-fdicts-cheap"
+ , flagDescription =
+ "Make dictionary-valued expressions seem cheap to the optimiser."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-dicts-cheap"
+ }
+ , flag { flagName = "-fdicts-strict"
+ , flagDescription = "Make dictionaries strict"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-dicts-strict"
+ }
+ , flag { flagName = "-fdmd-tx-dict-sel"
+ , flagDescription =
+ "Use a special demand transformer for dictionary selectors. "++
+ "Always enabled by default."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-dmd-tx-dict-sel"
+ }
+ , flag { flagName = "-fdo-eta-reduction"
+ , flagDescription = "Enable eta-reduction. Implied by ``-O``."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-do-eta-reduction"
+ }
+ , flag { flagName = "-fdo-lambda-eta-expansion"
+ , flagDescription =
+ "Enable lambda eta-expansion. Always enabled by default."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-do-lambda-eta-expansion"
+ }
+ , flag { flagName = "-feager-blackholing"
+ , flagDescription =
+ "Turn on :ref:`eager blackholing <parallel-compile-options>`"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fenable-rewrite-rules"
+ , flagDescription =
+ "Switch on all rewrite rules (including rules generated by "++
+ "automatic specialisation of overloaded functions). Implied by "++
+ "``-O``."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-enable-rewrite-rules"
+ }
+ , flag { flagName = "-fexcess-precision"
+ , flagDescription = "Enable excess intermediate precision"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-excess-precision"
+ }
+ , flag { flagName = "-fexpose-all-unfoldings"
+ , flagDescription =
+ "Expose all unfoldings, even for very large or recursive functions."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-expose-all-unfoldings"
+ }
+ , flag { flagName = "-ffloat-in"
+ , flagDescription =
+ "Turn on the float-in transformation. Implied by ``-O``."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-float-in"
+ }
+ , flag { flagName = "-ffull-laziness"
+ , flagDescription =
+ "Turn on full laziness (floating bindings outwards). "++
+ "Implied by ``-O``."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-full-laziness"
+ }
+ , flag { flagName = "-ffun-to-thunk"
+ , flagDescription =
+ "Allow worker-wrapper to convert a function closure into a thunk "++
+ "if the function does not use any of its arguments. Off by default."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-fun-to-thunk"
+ }
+ , flag { flagName = "-fignore-asserts"
+ , flagDescription =
+ "Ignore assertions in the source. Implied by ``-O``."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-ignore-asserts"
+ }
+ , flag { flagName = "-fignore-interface-pragmas"
+ , flagDescription =
+ "Ignore pragmas in interface files. Implied by ``-O0`` only."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-ignore-interface-pragmas"
+ }
+ , flag { flagName = "-flate-dmd-anal"
+ , flagDescription =
+ "Run demand analysis again, at the end of the "++
+ "simplification pipeline"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-late-dmd-anal"
+ }
+ , flag { flagName = "-fliberate-case"
+ , flagDescription =
+ "Turn on the liberate-case transformation. Implied by ``-O2``."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-liberate-case"
+ }
+ , flag { flagName = "-fliberate-case-threshold=⟨n⟩"
+ , flagDescription =
+ "*default: 2000.* Set the size threshold for the liberate-case "++
+ "transformation to ⟨n⟩"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-liberate-case-threshold"
+ }
+ , flag { flagName = "-floopification"
+ , flagDescription =
+ "Turn saturated self-recursive tail-calls into local jumps in the "++
+ "generated assembly. Implied by ``-O``."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-loopification"
+ }
+ , flag { flagName = "-fmax-inline-alloc-size=⟨n⟩"
+ , flagDescription =
+ "*default: 128.* Set the maximum size of inline array allocations "++
+ "to ⟨n⟩ bytes (default: 128). GHC will allocate non-pinned arrays "++
+ "of statically known size in the current nursery block if they're "++
+ "no bigger than ⟨n⟩ bytes, ignoring GC overheap. This value should "++
+ "be quite a bit smaller than the block size (typically: 4096)."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fmax-inline-memcpy-insns=⟨n⟩"
+ , flagDescription =
+ "*default: 32.* Inline ``memcpy`` calls if they would generate no "++
+ "more than ⟨n⟩ pseudo instructions."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fmax-inline-memset-insns=⟨n⟩"
+ , flagDescription =
+ "*default: 32.* Inline ``memset`` calls if they would generate no "++
+ "more than ⟨n⟩ pseudo instructions"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fmax-relevant-binds=⟨n⟩"
+ , flagDescription =
+ "*default: 6.* Set the maximum number of bindings to display in "++
+ "type error messages."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-max-relevant-bindings"
+ }
+ , flag { flagName = "-fmax-simplifier-iterations=⟨n⟩"
+ , flagDescription =
+ "*default: 4.* Set the max iterations for the simplifier."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fmax-worker-args=⟨n⟩"
+ , flagDescription =
+ "*default: 10.* If a worker has that many arguments, none will "++
+ "be unpacked anymore."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fno-opt-coercion"
+ , flagDescription = "Turn off the coercion optimiser"
+ , flagType = StaticFlag
+ }
+ , flag { flagName = "-fno-pre-inlining"
+ , flagDescription = "Turn off pre-inlining"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fno-state-hack"
+ , flagDescription =
+ "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."
+ , flagType = StaticFlag
+ }
+ , flag { flagName = "-fomit-interface-pragmas"
+ , flagDescription =
+ "Don't generate interface pragmas. Implied by ``-O0`` only."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-omit-interface-pragmas"
+ }
+ , flag { flagName = "-fomit-yields"
+ , flagDescription =
+ "Omit heap checks when no allocation is being performed."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-omit-yields"
+ }
+ , flag { flagName = "-fpedantic-bottoms"
+ , flagDescription =
+ "Make GHC be more precise about its treatment of bottom (but see "++
+ "also ``-fno-state-hack``). In particular, GHC will not "++
+ "eta-expand through a case expression."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-pedantic-bottoms"
+ }
+ , flag { flagName = "-fregs-graph"
+ , flagDescription =
+ "Use the graph colouring register allocator for register "++
+ "allocation in the native code generator. Implied by ``-O2``."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-regs-graph"
+ }
+ , flag { flagName = "-fregs-iterative"
+ , flagDescription =
+ "Use the iterative coalescing graph colouring register allocator "++
+ "in the native code generator."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-regs-iterative"
+ }
+ , flag { flagName = "-fsimplifier-phases=⟨n⟩"
+ , flagDescription =
+ "*default: 2.* Set the number of phases for the simplifier. "++
+ "Ignored with ``-O0``."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fsimpl-tick-factor=⟨n⟩"
+ , flagDescription =
+ "*default: 100.* Set the percentage factor for simplifier ticks."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fspec-constr"
+ , flagDescription =
+ "Turn on the SpecConstr transformation. Implied by ``-O2``."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-spec-constr"
+ }
+ , flag { flagName = "-fspec-constr-count=⟨n⟩"
+ , flagDescription =
+ "default: 3.* Set to ⟨n⟩ the maximum number of specialisations that"++
+ " will be created for any one function by the SpecConstr "++
+ "transformation."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-spec-constr-count"
+ }
+ , flag { flagName = "-fspec-constr-threshold=⟨n⟩"
+ , flagDescription =
+ "*default: 2000.* Set the size threshold for the SpecConstr "++
+ "transformation to ⟨n⟩."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-spec-constr-threshold"
+ }
+ , flag { flagName = "-fspecialise"
+ , flagDescription =
+ "Turn on specialisation of overloaded functions. Implied by ``-O``."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-specialise"
+ }
+ , flag { flagName = "-fcross-module-specialise"
+ , flagDescription =
+ "Turn on specialisation of overloaded functions imported from "++
+ "other modules."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-cross-module-specialise"
+ }
+ , flag { flagName = "-fstatic-argument-transformation"
+ , flagDescription = "Turn on the static argument transformation."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-static-argument-transformation"
+ }
+ , flag { flagName = "-fstrictness"
+ , flagDescription = "Turn on strictness analysis. Implied by ``-O``."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-strictness"
+ }
+ , flag { flagName = "-fstrictness-before=⟨n⟩"
+ , flagDescription =
+ "Run an additional strictness analysis before simplifier phase ⟨n⟩"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-funbox-small-strict-fields"
+ , flagDescription =
+ "Flatten strict constructor fields with a pointer-sized "++
+ "representation. Implied by ``-O``."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-unbox-small-strict-fields"
+ }
+ , flag { flagName = "-funbox-strict-fields"
+ , flagDescription = "Flatten strict constructor fields"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-unbox-strict-fields"
+ }
+ , flag { flagName = "-funfolding-creation-threshold=⟨n⟩"
+ , flagDescription = "*default: 750.* Tweak unfolding settings."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-funfolding-dict-discount=⟨n⟩"
+ , flagDescription = "*default: 30.* Tweak unfolding settings."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-funfolding-fun-discount=⟨n⟩"
+ , flagDescription = "*default: 60.* Tweak unfolding settings."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-funfolding-keeness-factor=⟨n⟩"
+ , flagDescription = "*default: 1.5.* Tweak unfolding settings."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-funfolding-use-threshold=⟨n⟩"
+ , flagDescription = "*default: 60.* Tweak unfolding settings."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fvectorisation-avoidance"
+ , flagDescription =
+ "Enable vectorisation avoidance. Always enabled by default."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-vectorisation-avoidance"
+ }
+ , flag { flagName = "-fvectorise"
+ , flagDescription = "Enable vectorisation of nested data parallelism"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-vectorise"
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/Packages.hs b/utils/mkUserGuidePart/Options/Packages.hs
new file mode 100644
index 0000000000..c6dfa0b86f
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/Packages.hs
@@ -0,0 +1,67 @@
+module Options.Packages where
+
+import Types
+
+packagesOptions :: [Flag]
+packagesOptions =
+ [ flag { flagName = "-this-package-key⟨P⟩"
+ , flagDescription = "Compile to be part of package ⟨P⟩"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-package⟨P⟩"
+ , flagDescription = "Expose package ⟨P⟩"
+ , flagType = DynamicSettableFlag
+ }
+ , flag { flagName = "-hide-all-packages"
+ , flagDescription = "Hide all packages by default"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-hide-package⟨name⟩"
+ , flagDescription = "Hide package ⟨P⟩"
+ , flagType = DynamicSettableFlag
+ }
+ , flag { flagName = "-ignore-package⟨name⟩"
+ , flagDescription = "Ignore package ⟨P⟩"
+ , flagType = DynamicSettableFlag
+ }
+ , flag { flagName = "-package-db⟨file⟩"
+ , flagDescription = "Add ⟨file⟩ to the package db stack."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-clear-package-db"
+ , flagDescription = "Clear the package db stack."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-no-global-package-db"
+ , flagDescription = "Remove the global package db from the stack."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-global-package-db"
+ , flagDescription = "Add the global package db to the stack."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-no-user-package-db"
+ , flagDescription = "Remove the user's package db from the stack."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-user-package-db"
+ , flagDescription = "Add the user's package db to the stack."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-no-auto-link-packages"
+ , flagDescription = "Don't automatically link in the base and rts packages."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-trust⟨P⟩"
+ , flagDescription = "Expose package ⟨P⟩ and set it to be trusted"
+ , flagType = DynamicSettableFlag
+ }
+ , flag { flagName = "-distrust⟨P⟩"
+ , flagDescription = "Expose package ⟨P⟩ and set it to be distrusted"
+ , flagType = DynamicSettableFlag
+ }
+ , flag { flagName = "-distrust-all"
+ , flagDescription = "Distrust all packages by default"
+ , flagType = DynamicSettableFlag
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/PhasePrograms.hs b/utils/mkUserGuidePart/Options/PhasePrograms.hs
new file mode 100644
index 0000000000..65ead95178
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/PhasePrograms.hs
@@ -0,0 +1,58 @@
+module Options.PhasePrograms where
+
+import Types
+
+phaseProgramsOptions :: [Flag]
+phaseProgramsOptions =
+ [ flag { flagName = "-pgmL⟨cmd⟩"
+ , flagDescription = "Use ⟨cmd⟩ as the literate pre-processor"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-pgmP⟨cmd⟩"
+ , flagDescription =
+ "Use ⟨cmd⟩ as the C pre-processor (with ``-cpp`` only)"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-pgmc⟨cmd⟩"
+ , flagDescription = "Use ⟨cmd⟩ as the C compiler"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-pgmlo⟨cmd⟩"
+ , flagDescription = "Use ⟨cmd⟩ as the LLVM optimiser"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-pgmlc⟨cmd⟩"
+ , flagDescription = "Use ⟨cmd⟩ as the LLVM compiler"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-pgms⟨cmd⟩"
+ , flagDescription = "Use ⟨cmd⟩ as the splitter"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-pgma⟨cmd⟩"
+ , flagDescription = "Use ⟨cmd⟩ as the assembler"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-pgml⟨cmd⟩"
+ , flagDescription = "Use ⟨cmd⟩ as the linker"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-pgmdll⟨cmd⟩"
+ , flagDescription = "Use ⟨cmd⟩ as the DLL generator"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-pgmF⟨cmd⟩"
+ , flagDescription = "Use ⟨cmd⟩ as the pre-processor (with ``-F`` only)"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-pgmwindres⟨cmd⟩"
+ , flagDescription =
+ "Use ⟨cmd⟩ as the program for embedding manifests on Windows."
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-pgmlibtool⟨cmd⟩"
+ , flagDescription =
+ "Use ⟨cmd⟩ as the command for libtool (with ``-staticlib`` only)."
+ , flagType = DynamicFlag
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/PhaseSpecific.hs b/utils/mkUserGuidePart/Options/PhaseSpecific.hs
new file mode 100644
index 0000000000..cbd79f18a4
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/PhaseSpecific.hs
@@ -0,0 +1,47 @@
+module Options.PhaseSpecific where
+
+import Types
+
+phaseSpecificOptions :: [Flag]
+phaseSpecificOptions =
+ [ flag { flagName = "-optL⟨option⟩"
+ , flagDescription = "pass ⟨option⟩ to the literate pre-processor"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-optP⟨option⟩"
+ , flagDescription = "pass ⟨option⟩ to cpp (with ``-cpp`` only)"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-optF⟨option⟩"
+ , flagDescription = "pass ⟨option⟩ to the custom pre-processor"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-optc⟨option⟩"
+ , flagDescription = "pass ⟨option⟩ to the C compiler"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-optlo⟨option⟩"
+ , flagDescription = "pass ⟨option⟩ to the LLVM optimiser"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-optlc⟨option⟩"
+ , flagDescription = "pass ⟨option⟩ to the LLVM compiler"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-opta⟨option⟩"
+ , flagDescription = "pass ⟨option⟩ to the assembler"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-optl⟨option⟩"
+ , flagDescription = "pass ⟨option⟩ to the linker"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-optdll⟨option⟩"
+ , flagDescription = "pass ⟨option⟩ to the DLL generator"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-optwindres⟨option⟩"
+ , flagDescription = "pass ⟨option⟩ to ``windres``."
+ , flagType = DynamicFlag
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/Phases.hs b/utils/mkUserGuidePart/Options/Phases.hs
new file mode 100644
index 0000000000..230eda1495
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/Phases.hs
@@ -0,0 +1,33 @@
+module Options.Phases where
+
+import Types
+
+phaseOptions :: [Flag]
+phaseOptions =
+ [ flag { flagName = "-F"
+ , flagDescription =
+ "Enable the use of a :ref:`pre-processor <pre-processor>` "++
+ "(set with ``-pgmF``)"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-E"
+ , flagDescription = "Stop after preprocessing (``.hspp`` file)"
+ , flagType = ModeFlag
+ }
+ , flag { flagName = "-C"
+ , flagDescription = "Stop after generating C (``.hc`` file)"
+ , flagType = ModeFlag
+ }
+ , flag { flagName = "-S"
+ , flagDescription = "Stop after generating assembly (``.s`` file)"
+ , flagType = ModeFlag
+ }
+ , flag { flagName = "-c"
+ , flagDescription = "Stop after generating object (``.o``) file"
+ , flagType = ModeFlag
+ }
+ , flag { flagName = "-x⟨suffix⟩"
+ , flagDescription = "Override default behaviour for source files"
+ , flagType = DynamicFlag
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/PlatformSpecific.hs b/utils/mkUserGuidePart/Options/PlatformSpecific.hs
new file mode 100644
index 0000000000..8d43665ea9
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/PlatformSpecific.hs
@@ -0,0 +1,15 @@
+module Options.PlatformSpecific where
+
+import Types
+
+platformSpecificOptions :: [Flag]
+platformSpecificOptions =
+ [ flag { flagName = "-msse2"
+ , flagDescription = "(x86 only) Use SSE2 for floating-point operations"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-msse4.2"
+ , flagDescription = "(x86 only) Use SSE4.2 for floating-point operations"
+ , flagType = DynamicFlag
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/Plugin.hs b/utils/mkUserGuidePart/Options/Plugin.hs
new file mode 100644
index 0000000000..1ae7d6e536
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/Plugin.hs
@@ -0,0 +1,17 @@
+module Options.Plugin where
+
+import Types
+
+pluginOptions :: [Flag]
+pluginOptions =
+ [ flag { flagName = "-fplugin=⟨module⟩"
+ , flagDescription = "Load a plugin exported by a given module"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fplugin-opt=⟨module:args⟩"
+ , flagDescription =
+ "Give arguments to a plugin module; module must be specified with "++
+ "``-fplugin``"
+ , flagType = DynamicFlag
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/Profiling.hs b/utils/mkUserGuidePart/Options/Profiling.hs
new file mode 100644
index 0000000000..af3853fafc
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/Profiling.hs
@@ -0,0 +1,44 @@
+module Options.Profiling where
+
+import Types
+
+profilingOptions :: [Flag]
+profilingOptions =
+ [ flag { flagName = "-prof"
+ , flagDescription = "Turn on profiling"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-fprof-auto"
+ , flagDescription =
+ "Auto-add ``SCC``\\ s to all bindings not marked INLINE"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-prof-auto"
+ }
+ , flag { flagName = "-fprof-auto-top"
+ , flagDescription =
+ "Auto-add ``SCC``\\ s to all top-level bindings not marked INLINE"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-prof-auto"
+ }
+ , flag { flagName = "-fprof-auto-exported"
+ , flagDescription =
+ "Auto-add ``SCC``\\ s to all exported bindings not marked INLINE"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-prof-auto"
+ }
+ , flag { flagName = "-fprof-cafs"
+ , flagDescription = "Auto-add ``SCC``\\ s to all CAFs"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-prof-cafs"
+ }
+ , flag { flagName = "-fno-prof-count-entries"
+ , flagDescription = "Do not collect entry counts"
+ , flagType = DynamicFlag
+ , flagReverse = "-fprof-count-entries"
+ }
+ , flag { flagName = "-ticky"
+ , flagDescription =
+ ":ref:`Turn on ticky-ticky profiling <ticky-ticky>`"
+ , flagType = DynamicFlag
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/ProgramCoverage.hs b/utils/mkUserGuidePart/Options/ProgramCoverage.hs
new file mode 100644
index 0000000000..c7b2894668
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/ProgramCoverage.hs
@@ -0,0 +1,18 @@
+module Options.ProgramCoverage where
+
+import Types
+
+programCoverageOptions :: [Flag]
+programCoverageOptions =
+ [ flag { flagName = "-fhpc"
+ , flagDescription =
+ "Turn on Haskell program coverage instrumentation"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-hpcdir dir"
+ , flagDescription =
+ "Directory to deposit ``.mix`` files during compilation "++
+ "(default is ``.hpc``)"
+ , flagType = DynamicFlag
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/RecompilationChecking.hs b/utils/mkUserGuidePart/Options/RecompilationChecking.hs
new file mode 100644
index 0000000000..1dec661f40
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/RecompilationChecking.hs
@@ -0,0 +1,15 @@
+module Options.RecompilationChecking where
+
+import Types
+
+recompilationCheckingOptions :: [Flag]
+recompilationCheckingOptions =
+ [ flag { flagName = "-fforce-recomp"
+ , flagDescription =
+ "Turn off recompilation checking. This is implied by any " ++
+ "``-ddump-X`` option when compiling a single file " ++
+ "(i.e. when using ``-c``)."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-force-recomp"
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/RedirectingOutput.hs b/utils/mkUserGuidePart/Options/RedirectingOutput.hs
new file mode 100644
index 0000000000..9435e26668
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/RedirectingOutput.hs
@@ -0,0 +1,47 @@
+module Options.RedirectingOutput where
+
+import Types
+
+redirectingOutputOptions :: [Flag]
+redirectingOutputOptions =
+ [ flag { flagName = "-hcsuf ⟨suffix⟩"
+ , flagDescription = "set the suffix to use for intermediate C files"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-hidir ⟨dir⟩"
+ , flagDescription = "set directory for interface files"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-hisuf ⟨suffix⟩"
+ , flagDescription = "set the suffix to use for interface files"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-o ⟨filename⟩"
+ , flagDescription = "set output filename"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-odir ⟨dir⟩"
+ , flagDescription = "set directory for object files"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-ohi ⟨filename⟩"
+ , flagDescription = "set the filename in which to put the interface"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-osuf ⟨suffix⟩"
+ , flagDescription = "set the output file suffix"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-stubdir ⟨dir⟩"
+ , flagDescription = "redirect FFI stub files"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-dumpdir ⟨dir⟩"
+ , flagDescription = "redirect dump files"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-outputdir ⟨dir⟩"
+ , flagDescription = "set output directory"
+ , flagType = DynamicFlag
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/TemporaryFiles.hs b/utils/mkUserGuidePart/Options/TemporaryFiles.hs
new file mode 100644
index 0000000000..a66ca3b967
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/TemporaryFiles.hs
@@ -0,0 +1,11 @@
+module Options.TemporaryFiles where
+
+import Types
+
+temporaryFilesOptions :: [Flag]
+temporaryFilesOptions =
+ [ flag { flagName = "-tmpdir ⟨dir⟩"
+ , flagDescription = "set the directory for temporary files"
+ , flagType = DynamicFlag
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/Verbosity.hs b/utils/mkUserGuidePart/Options/Verbosity.hs
new file mode 100644
index 0000000000..723e5596fb
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/Verbosity.hs
@@ -0,0 +1,58 @@
+module Options.Verbosity where
+
+import Types
+
+verbosityOptions :: [Flag]
+verbosityOptions =
+ [ flag { flagName = "-v"
+ , flagDescription = "verbose mode (equivalent to ``-v3``)"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-v⟨n⟩"
+ , flagDescription = "set verbosity level"
+ , flagType = DynamicFlag
+ , flagReverse = ""
+ }
+ , flag { flagName = "-fprint-potential-instances"
+ , flagDescription =
+ "display all available instances in type error messages"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-print-potential-instances"
+ }
+ , flag { flagName = "-fprint-explicit-foralls"
+ , flagDescription =
+ "Print explicit ``forall`` quantification in types. " ++
+ "See also ``-XExplicitForAll``"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-print-explicit-foralls"
+ }
+ , flag { flagName = "-fprint-explicit-kinds"
+ , flagDescription =
+ "Print explicit kind foralls and kind arguments in types. " ++
+ "See also ``-XKindSignature``"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-print-explicit-kinds"
+ }
+ , flag { flagName = "-fprint-unicode-syntax"
+ , flagDescription =
+ "Use unicode syntax when printing expressions, types and kinds. " ++
+ "See also ``-XUnicodeSyntax``"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-print-unicode-syntax"
+ }
+ , flag { flagName = "-fprint-expanded-synonyms"
+ , flagDescription =
+ "In type errors, also print type-synonym-expanded types."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-print-expanded-synonyms"
+ }
+ , flag { flagName = "-ferror-spans"
+ , flagDescription = "Output full span in error messages"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-Rghc-timing"
+ , flagDescription =
+ "Summarise timing stats for GHC (same as ``+RTS -tstderr``)."
+ , flagType = DynamicFlag
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Options/Warnings.hs b/utils/mkUserGuidePart/Options/Warnings.hs
new file mode 100644
index 0000000000..688a7e691b
--- /dev/null
+++ b/utils/mkUserGuidePart/Options/Warnings.hs
@@ -0,0 +1,317 @@
+module Options.Warnings where
+
+import Types
+
+warningsOptions :: [Flag]
+warningsOptions =
+ [ flag { flagName = "-W"
+ , flagDescription = "enable normal warnings"
+ , flagType = DynamicFlag
+ , flagReverse = "-w"
+ }
+ , flag { flagName = "-w"
+ , flagDescription = "disable all warnings"
+ , flagType = DynamicFlag
+ }
+ , flag { flagName = "-Wall"
+ , flagDescription =
+ "enable almost all warnings (details in :ref:`options-sanity`)"
+ , flagType = DynamicFlag
+ , flagReverse = "-w"
+ }
+ , flag { flagName = "-Werror"
+ , flagDescription = "make warnings fatal"
+ , flagType = DynamicFlag
+ , flagReverse = "-Wwarn"
+ }
+ , flag { flagName = "-Wwarn"
+ , flagDescription = "make warnings non-fatal"
+ , flagType = DynamicFlag
+ , flagReverse = "-Werror"
+ }
+ , flag { flagName = "-fdefer-type-errors"
+ , flagDescription =
+ "Turn type errors into warnings, :ref:`deferring the error until "++
+ "runtime <defer-type-errors>`. Implies ``-fdefer-typed-holes``. "++
+ "See also ``-fwarn-deferred-type-errors``"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-defer-type-errors"
+ }
+ , flag { flagName = "-fdefer-typed-holes"
+ , flagDescription =
+ "Convert :ref:`typed hole <typed-holes>` errors into warnings, "++
+ ":ref:`deferring the error until runtime <defer-type-errors>`. "++
+ "Implied by ``-fdefer-type-errors``. "++
+ "See also ``-fwarn-typed-holes``."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-defer-typed-holes"
+ }
+ , flag { flagName = "-fhelpful-errors"
+ , flagDescription = "Make suggestions for mis-spelled names."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-helpful-errors"
+ }
+ , flag { flagName = "-fwarn-deprecated-flags"
+ , flagDescription =
+ "warn about uses of commandline flags that are deprecated"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-deprecated-flags"
+ }
+ , flag { flagName = "-fwarn-duplicate-constraints"
+ , flagDescription =
+ "warn when a constraint appears duplicated in a type signature"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-duplicate-constraints"
+ }
+ , flag { flagName = "-fwarn-duplicate-exports"
+ , flagDescription = "warn when an entity is exported multiple times"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-duplicate-exports"
+ }
+ , flag { flagName = "-fwarn-hi-shadowing"
+ , flagDescription =
+ "warn when a ``.hi`` file in the current directory shadows a library"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-hi-shadowing"
+ }
+ , flag { flagName = "-fwarn-identities"
+ , flagDescription =
+ "warn about uses of Prelude numeric conversions that are probably "++
+ "the identity (and hence could be omitted)"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-identities"
+ }
+ , flag { flagName = "-fwarn-implicit-prelude"
+ , flagDescription = "warn when the Prelude is implicitly imported"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-implicit-prelude"
+ }
+ , flag { flagName = "-fwarn-incomplete-patterns"
+ , flagDescription = "warn when a pattern match could fail"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-incomplete-patterns"
+ }
+ , flag { flagName = "-fwarn-incomplete-uni-patterns"
+ , flagDescription =
+ "warn when a pattern match in a lambda expression or "++
+ "pattern binding could fail"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-incomplete-uni-patterns"
+ }
+ , flag { flagName = "-fwarn-incomplete-record-updates"
+ , flagDescription = "warn when a record update could fail"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-incomplete-record-updates"
+ }
+ , flag { flagName = "-fwarn-lazy-unlifted-bindings"
+ , flagDescription =
+ "*(deprecated)* warn when a pattern binding looks lazy but "++
+ "must be strict"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-lazy-unlifted-bindings"
+ }
+ , flag { flagName = "-fwarn-missing-fields"
+ , flagDescription = "warn when fields of a record are uninitialised"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-missing-fields"
+ }
+ , flag { flagName = "-fwarn-missing-import-lists"
+ , flagDescription =
+ "warn when an import declaration does not explicitly list all the"++
+ "names brought into scope"
+ , flagType = DynamicFlag
+ , flagReverse = "-fnowarn-missing-import-lists"
+ }
+ , flag { flagName = "-fwarn-missing-methods"
+ , flagDescription = "warn when class methods are undefined"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-missing-methods"
+ }
+ , flag { flagName = "-fwarn-missing-signatures"
+ , flagDescription = "warn about top-level functions without signatures"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-missing-signatures"
+ }
+ , flag { flagName = "-fwarn-missing-exported-sigs"
+ , flagDescription =
+ "warn about top-level functions without signatures, only if they "++
+ "are exported. takes precedence over -fwarn-missing-signatures"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-missing-exported-sigs"
+ }
+ , flag { flagName = "-fwarn-missing-local-sigs"
+ , flagDescription =
+ "warn about polymorphic local bindings without signatures"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-missing-local-sigs"
+ }
+ , flag { flagName = "-fwarn-monomorphism-restriction"
+ , flagDescription = "warn when the Monomorphism Restriction is applied"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-monomorphism-restriction"
+ }
+ , flag { flagName = "-fwarn-name-shadowing"
+ , flagDescription = "warn when names are shadowed"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-name-shadowing"
+ }
+ , flag { flagName = "-fwarn-orphans"
+ , flagDescription =
+ "warn when the module contains :ref:`orphan instance declarations "++
+ "or rewrite rules <orphan-modules>`"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-orphans"
+ }
+ , flag { flagName = "-fwarn-overlapping-patterns"
+ , flagDescription = "warn about overlapping patterns"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-overlapping-patterns"
+ }
+ , flag { flagName = "-fwarn-tabs"
+ , flagDescription = "warn if there are tabs in the source file"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-tabs"
+ }
+ , flag { flagName = "-fwarn-type-defaults"
+ , flagDescription = "warn when defaulting happens"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-type-defaults"
+ }
+ , flag { flagName = "-fwarn-unrecognised-pragmas"
+ , flagDescription =
+ "warn about uses of pragmas that GHC doesn't recognise"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-unrecognised-pragmas"
+ }
+ , flag { flagName = "-fwarn-unticked-promoted-constructors"
+ , flagDescription = "warn if promoted constructors are not ticked"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-unticked-promoted-constructors"
+ }
+ , flag { flagName = "-fwarn-unused-binds"
+ , flagDescription =
+ "warn about bindings that are unused. Alias for "++
+ "``-fwarn-unused-top-binds``, ``-fwarn-unused-local-binds`` and "++
+ "``-fwarn-unused-pattern-binds``"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-unused-binds"
+ }
+ , flag { flagName = "-fwarn-unused-top-binds"
+ , flagDescription = "warn about top-level bindings that are unused"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-unused-top-binds"
+ }
+ , flag { flagName = "-fwarn-unused-local-binds"
+ , flagDescription = "warn about local bindings that are unused"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-unused-local-binds"
+ }
+ , flag { flagName = "-fwarn-unused-pattern-binds"
+ , flagDescription = "warn about pattern match bindings that are unused"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-unused-pattern-binds"
+ }
+ , flag { flagName = "-fwarn-unused-imports"
+ , flagDescription = "warn about unnecessary imports"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-unused-imports"
+ }
+ , flag { flagName = "-fwarn-unused-matches"
+ , flagDescription = "warn about variables in patterns that aren't used"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-unused-matches"
+ }
+ , flag { flagName = "-fwarn-unused-do-bind"
+ , flagDescription =
+ "warn about do bindings that appear to throw away values of types "++
+ "other than ``()``"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-unused-do-bind"
+ }
+ , flag { flagName = "-fwarn-wrong-do-bind"
+ , flagDescription =
+ "warn about do bindings that appear to throw away monadic values "++
+ "that you should have bound instead"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-wrong-do-bind"
+ }
+ , flag { flagName = "-fwarn-unsafe"
+ , flagDescription =
+ "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. Works on all module types, even those using "++
+ "explicit :ref:`Safe Haskell <safe-haskell>` modes (such as "++
+ "``-XTrustworthy``) and so can be used to have the compiler check "++
+ "any assumptions made."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-unsafe"
+ }
+ , flag { flagName = "-fwarn-safe"
+ , flagDescription =
+ "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. Works on all module types, even those using explicit "++
+ ":ref:`Safe Haskell <safe-haskell>` modes (such as "++
+ "``-XTrustworthy``) and so can be used to have the compiler check "++
+ "any assumptions made."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-safe"
+ }
+ , flag { flagName = "-fwarn-trustworthy-safe"
+ , flagDescription =
+ "warn if the module being compiled is marked as ``-XTrustworthy`` "++
+ "but it could instead be marked as ``-XSafe``, a more informative "++
+ "bound. Can be used to detect once a Safe Haskell bound can be "++
+ "improved as dependencies are updated."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-safe"
+ }
+ , flag { flagName = "-fwarn-warnings-deprecations"
+ , flagDescription =
+ "warn about uses of functions & types that have warnings or "++
+ "deprecated pragmas"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-warnings-deprecations"
+ }
+ , flag { flagName = "-fwarn-amp"
+ , flagDescription =
+ "*(deprecated)* warn on definitions conflicting with the "++
+ "Applicative-Monad Proposal (AMP)"
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-amp"
+ }
+ , flag { flagName = "-fwarn-deferred-type-errors"
+ , flagDescription =
+ "Report warnings when :ref:`deferred type errors "++
+ "<defer-type-errors>` are enabled. This option is enabled by "++
+ "default. See ``-fdefer-type-errors``."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-deferred-type-errors"
+ }
+ , flag { flagName = "-fwarn-typed-holes"
+ , flagDescription =
+ "Report warnings when :ref:`typed hole <typed-holes>` errors are "++
+ ":ref:`deferred until runtime <defer-type-errors>`. See "++
+ "``-fdefer-typed-holes``."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-typed-holes"
+ }
+ , flag { flagName = "-fwarn-partial-type-signatures"
+ , flagDescription =
+ "warn about holes in partial type signatures when "++
+ "``-XPartialTypeSignatures`` is enabled. Not applicable when "++
+ "``-XPartialTypesignatures`` is not enabled, in which case errors "++
+ "are generated for such holes. See :ref:`partial-type-signatures`."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-partial-type-signatures"
+ }
+ , flag { flagName = "-fwarn-deriving-typeable"
+ , flagDescription =
+ "warn when encountering a request to derive an instance of class "++
+ "``Typeable``. As of GHC 7.10, such declarations are unnecessary "++
+ "and are ignored by the compiler because GHC has a custom solver "++
+ "for discharging this type of constraint."
+ , flagType = DynamicFlag
+ , flagReverse = "-fno-warn-deriving-typeable"
+ }
+ ]
diff --git a/utils/mkUserGuidePart/Table.hs b/utils/mkUserGuidePart/Table.hs
new file mode 100644
index 0000000000..eeff8205cb
--- /dev/null
+++ b/utils/mkUserGuidePart/Table.hs
@@ -0,0 +1,75 @@
+module Table where
+
+import Data.Char
+import Data.List
+import Data.Maybe (isJust, fromMaybe)
+import qualified DList
+
+type Row = [String]
+
+type ColWidth = Int
+
+type WrappedString = [String]
+
+-- | Wrap a string to lines of at most the given length on whitespace
+-- if possible.
+wrapAt :: Int -> String -> WrappedString
+wrapAt width = wrapLine
+ where
+ wrapLine :: String -> WrappedString
+ wrapLine s =
+ go width mempty (take width s : wrapLine (drop width s)) s
+
+ go :: Int -- ^ remaining width
+ -> DList.DList Char -- ^ accumulator
+ -> WrappedString -- ^ last good wrapping
+ -> String -- ^ remaining string
+ -> WrappedString
+ go 0 _ back _ = back
+ go n accum _ (c:rest)
+ | breakable c = go (n-1) accum'
+ (DList.toList accum' : wrapLine rest) rest
+ where accum' = accum `DList.snoc` c
+ go n accum back (c:rest) = go (n-1) (accum `DList.snoc` c) back rest
+ go _ accum _ [] = [DList.toList accum]
+
+ breakable = isSpace
+
+transpose' :: [[a]] -> [[Maybe a]]
+transpose' = goRow
+ where
+ peel :: [a] -> (Maybe a, [a])
+ peel (x:xs) = (Just x, xs)
+ peel [] = (Nothing, [])
+
+ goRow xs =
+ case unzip $ map peel xs of
+ (xs', ys)
+ | any isJust xs' -> xs' : goRow ys
+ | otherwise -> []
+
+table :: [ColWidth] -> Row -> [Row] -> String
+table widths hdr rows = unlines $
+ [rule '-'] ++
+ [formatRow hdr] ++
+ [rule '='] ++
+ intersperse (rule '-') (map formatRow rows) ++
+ [rule '-']
+ where
+ formatRow :: Row -> String
+ formatRow cols =
+ intercalate "\n"
+ $ map (rawRow . map (fromMaybe ""))
+ $ transpose'
+ $ zipWith wrapAt (map (subtract 4) widths) cols
+
+ rawRow :: Row -> String
+ rawRow cols = "| " ++ intercalate " | " (zipWith padTo widths cols) ++ " |"
+ padTo width content = take width $ content ++ repeat ' '
+
+ rule :: Char -> String
+ rule lineChar =
+ ['+',lineChar]
+ ++intercalate [lineChar,'+',lineChar]
+ (map (\n -> replicate n lineChar) widths)
+ ++[lineChar,'+']
diff --git a/utils/mkUserGuidePart/Types.hs b/utils/mkUserGuidePart/Types.hs
new file mode 100644
index 0000000000..33474dae73
--- /dev/null
+++ b/utils/mkUserGuidePart/Types.hs
@@ -0,0 +1,20 @@
+module Types where
+
+data FlagType = StaticFlag
+ -- ^ Static flag
+ | DynamicFlag
+ -- ^ Dynamic flag
+ | DynamicSettableFlag
+ -- ^ Dynamic flag on which @:set@ can be used in GHCi
+ | ModeFlag
+ -- ^ A mode of execution (e.g. @--mode@)
+
+data Flag = Flag { flagName :: String
+ , flagDescription :: String
+ , flagType :: FlagType
+ , flagReverse :: String
+ , flagSince :: String
+ }
+
+flag :: Flag
+flag = Flag "" "" DynamicFlag "" ""
diff --git a/utils/mkUserGuidePart/ghc.mk b/utils/mkUserGuidePart/ghc.mk
index 30b050e305..87c9d6552b 100644
--- a/utils/mkUserGuidePart/ghc.mk
+++ b/utils/mkUserGuidePart/ghc.mk
@@ -10,9 +10,49 @@
#
# -----------------------------------------------------------------------------
+utils/mkUserGuidePart_GENERATED_FLAGS_SETS := \
+ codegen \
+ compiler-debugging \
+ cpp \
+ finding-imports \
+ interactive \
+ interface-files \
+ keeping-intermediates \
+ language \
+ linking \
+ misc \
+ modes \
+ optimization \
+ optimization-levels \
+ packages \
+ phase-programs \
+ phases \
+ phase-specific \
+ platform-specific \
+ plugin \
+ profiling \
+ program-coverage \
+ recompilating-checking \
+ recompilation-checking \
+ redirecting-output \
+ temporary-files \
+ verbosity \
+ warnings
+
+utils/mkUserGuidePart_GENERATED_RST_SOURCES := \
+ $(addprefix docs/users_guide/flags-,$(addsuffix .gen.rst,$(utils/mkUserGuidePart_GENERATED_FLAGS_SETS))) \
+ docs/users_guide/what_glasgow_exts_does.gen.rst \
+ docs/man/all-flags.gen.rst
+
utils/mkUserGuidePart_USES_CABAL = YES
utils/mkUserGuidePart_PACKAGE = mkUserGuidePart
utils/mkUserGuidePart_dist_PROGNAME = mkUserGuidePart
utils/mkUserGuidePart_dist_INSTALL_INPLACE = YES
$(eval $(call build-prog,utils/mkUserGuidePart,dist,2))
+$(eval $(call clean-target,utils/mkUserGuidePart,gen,$(utils/mkUserGuidePart_GENERATED_RST_SOURCES)))
+
+$(utils/mkUserGuidePart_GENERATED_RST_SOURCES) : $(mkUserGuidePart_INPLACE)
+ $(mkUserGuidePart_INPLACE)
+
+all_utils/mkUserGuidePart: $(mkUserGuidePart_INPLACE)
diff --git a/utils/mkUserGuidePart/mkUserGuidePart.cabal b/utils/mkUserGuidePart/mkUserGuidePart.cabal
index 112bbf6a81..5b185ee30d 100644
--- a/utils/mkUserGuidePart/mkUserGuidePart.cabal
+++ b/utils/mkUserGuidePart/mkUserGuidePart.cabal
@@ -14,6 +14,37 @@ cabal-version: >=1.10
Executable mkUserGuidePart
Default-Language: Haskell2010
Main-Is: Main.hs
+ Other-Modules:
+ Types
+ DList
+ Table
+ Options
+ Options.CodeGen
+ Options.CompilerDebugging
+ Options.Cpp
+ Options.FindingImports
+ Options.Interactive
+ Options.InterfaceFiles
+ Options.KeepingIntermediates
+ Options.Language
+ Options.Linking
+ Options.Misc
+ Options.Modes
+ Options.OptimizationLevels
+ Options.Optimizations
+ Options.Packages
+ Options.PhasePrograms
+ Options.Phases
+ Options.PhaseSpecific
+ Options.PlatformSpecific
+ Options.Plugin
+ Options.Profiling
+ Options.ProgramCoverage
+ Options.RecompilationChecking
+ Options.RedirectingOutput
+ Options.TemporaryFiles
+ Options.Verbosity
+ Options.Warnings
Build-Depends: base >= 3 && < 5,
ghc
diff --git a/utils/vagrant/bootstrap-rhel.sh b/utils/vagrant/bootstrap-rhel.sh
index 5086279dc6..52cc5fca93 100755
--- a/utils/vagrant/bootstrap-rhel.sh
+++ b/utils/vagrant/bootstrap-rhel.sh
@@ -1,4 +1,4 @@
#!/bin/sh
yum update -y
yum install -y glibc-devel ncurses-devel gmp-devel autoconf automake libtool \
- gcc make perl python ghc git docbook-utils docbook-utils-pdf docbook-style-xsl
+ gcc make perl python ghc git