| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Distribution.Simple.Program.GHC
Synopsis
- data GhcOptions = GhcOptions {
- ghcOptMode :: Flag GhcMode
- ghcOptExtra :: [String]
- ghcOptExtraDefault :: [String]
- ghcOptInputFiles :: NubListR (SymbolicPath Pkg 'File)
- ghcOptInputScripts :: NubListR (SymbolicPath Pkg 'File)
- ghcOptInputModules :: NubListR ModuleName
- ghcOptOutputFile :: Flag (SymbolicPath Pkg 'File)
- ghcOptOutputDynFile :: Flag FilePath
- ghcOptSourcePathClear :: Flag Bool
- ghcOptSourcePath :: NubListR (SymbolicPath Pkg ('Dir Source))
- ghcOptThisUnitId :: Flag String
- ghcOptThisComponentId :: Flag ComponentId
- ghcOptInstantiatedWith :: [(ModuleName, OpenModule)]
- ghcOptNoCode :: Flag Bool
- ghcOptPackageDBs :: PackageDBStack
- ghcOptPackages :: NubListR (OpenUnitId, ModuleRenaming)
- ghcOptHideAllPackages :: Flag Bool
- ghcOptWarnMissingHomeModules :: Flag Bool
- ghcOptNoAutoLinkPackages :: Flag Bool
- ghcOptLinkLibs :: [FilePath]
- ghcOptLinkLibPath :: NubListR (SymbolicPath Pkg ('Dir Lib))
- ghcOptLinkOptions :: [String]
- ghcOptLinkFrameworks :: NubListR String
- ghcOptLinkFrameworkDirs :: NubListR (SymbolicPath Pkg ('Dir Framework))
- ghcOptLinkRts :: Flag Bool
- ghcOptNoLink :: Flag Bool
- ghcOptLinkNoHsMain :: Flag Bool
- ghcOptLinkModDefFiles :: NubListR FilePath
- ghcOptCcOptions :: [String]
- ghcOptCxxOptions :: [String]
- ghcOptAsmOptions :: [String]
- ghcOptCppOptions :: [String]
- ghcOptCppIncludePath :: NubListR (SymbolicPath Pkg ('Dir Include))
- ghcOptCppIncludes :: NubListR (SymbolicPath Pkg 'File)
- ghcOptFfiIncludes :: NubListR FilePath
- ghcOptCcProgram :: Flag FilePath
- ghcOptLanguage :: Flag Language
- ghcOptExtensions :: NubListR Extension
- ghcOptExtensionMap :: Map Extension (Maybe CompilerFlag)
- ghcOptOptimisation :: Flag GhcOptimisation
- ghcOptDebugInfo :: Flag DebugInfoLevel
- ghcOptProfilingMode :: Flag Bool
- ghcOptProfilingAuto :: Flag GhcProfAuto
- ghcOptSplitSections :: Flag Bool
- ghcOptSplitObjs :: Flag Bool
- ghcOptNumJobs :: Flag ParStrat
- ghcOptHPCDir :: Flag (SymbolicPath Pkg ('Dir Mix))
- ghcOptGHCiScripts :: [FilePath]
- ghcOptHiSuffix :: Flag String
- ghcOptObjSuffix :: Flag String
- ghcOptDynHiSuffix :: Flag String
- ghcOptDynObjSuffix :: Flag String
- ghcOptHiDir :: Flag (SymbolicPath Pkg ('Dir Artifacts))
- ghcOptHieDir :: Flag (SymbolicPath Pkg ('Dir Artifacts))
- ghcOptObjDir :: Flag (SymbolicPath Pkg ('Dir Artifacts))
- ghcOptOutputDir :: Flag (SymbolicPath Pkg ('Dir Artifacts))
- ghcOptStubDir :: Flag (SymbolicPath Pkg ('Dir Artifacts))
- ghcOptDynLinkMode :: Flag GhcDynLinkMode
- ghcOptStaticLib :: Flag Bool
- ghcOptShared :: Flag Bool
- ghcOptFPic :: Flag Bool
- ghcOptDylibName :: Flag String
- ghcOptRPaths :: NubListR FilePath
- ghcOptVerbosity :: Flag Verbosity
- ghcOptExtraPath :: NubListR (SymbolicPath Pkg ('Dir Build))
- ghcOptCabal :: Flag Bool
- data GhcMode
- data GhcOptimisation
- data GhcDynLinkMode
- data GhcProfAuto
- ghcInvocation :: Verbosity -> ConfiguredProgram -> Compiler -> Platform -> Maybe (SymbolicPath CWD ('Dir Pkg)) -> GhcOptions -> IO ProgramInvocation
- renderGhcOptions :: Compiler -> Platform -> GhcOptions -> [String]
- runGHC :: Verbosity -> ConfiguredProgram -> Compiler -> Platform -> Maybe (SymbolicPath CWD ('Dir Pkg)) -> GhcOptions -> IO ()
- packageDbArgsDb :: PackageDBStackCWD -> [String]
- normaliseGhcArgs :: Maybe Version -> PackageDescription -> [String] -> [String]
Documentation
data GhcOptions Source #
A structured set of GHC options/flags
Note that options containing lists fall into two categories:
- options that can be safely deduplicated, e.g. input modules or enabled extensions;
- options that cannot be deduplicated in general without changing semantics, e.g. extra ghc options or linking options.
Constructors
Fields
- ghcOptMode :: Flag GhcMode
The major mode for the ghc invocation.
- ghcOptExtra :: [String]
Any extra options to pass directly to ghc. These go at the end and hence override other stuff.
- ghcOptExtraDefault :: [String]
Extra default flags to pass directly to ghc. These go at the beginning and so can be overridden by other stuff.
- ghcOptInputFiles :: NubListR (SymbolicPath Pkg 'File)
The main input files; could be .hs, .hi, .c, .o, depending on mode.
- ghcOptInputScripts :: NubListR (SymbolicPath Pkg 'File)
Script files with irregular extensions that need -x hs.
- ghcOptInputModules :: NubListR ModuleName
The names of input Haskell modules, mainly for
--makemode. - ghcOptOutputFile :: Flag (SymbolicPath Pkg 'File)
Location for output file; the
ghc -oflag. - ghcOptOutputDynFile :: Flag FilePath
Location for dynamic output file in
GhcStaticAndDynamicmode; theghc -dynoflag. - ghcOptSourcePathClear :: Flag Bool
Start with an empty search path for Haskell source files; the
ghc -iflag (-ion its own with no path argument). - ghcOptSourcePath :: NubListR (SymbolicPath Pkg ('Dir Source))
Search path for Haskell source files; the
ghc -iflag. - ghcOptThisUnitId :: Flag String
The unit ID the modules will belong to; the
ghc -this-unit-idflag (or-this-package-keyor-package-nameon older versions of GHC). This is aStringbecause we assume you've already figured out what the correct format for this string is (we need to handle backwards compatibility.) - ghcOptThisComponentId :: Flag ComponentId
GHC doesn't make any assumptions about the format of definite unit ids, so when we are instantiating a package it needs to be told explicitly what the component being instantiated is. This only gets set when
ghcOptInstantiatedWithis non-empty - ghcOptInstantiatedWith :: [(ModuleName, OpenModule)]
How the requirements of the package being compiled are to be filled. When typechecking an indefinite package, the
OpenModuleis always aOpenModuleVar; otherwise, it specifies the installed module that instantiates a package. - ghcOptNoCode :: Flag Bool
No code? (But we turn on interface writing
- ghcOptPackageDBs :: PackageDBStack
GHC package databases to use, the
ghc -package-confflag. - ghcOptPackages :: NubListR (OpenUnitId, ModuleRenaming)
The GHC packages to bring into scope when compiling, the
ghc -package-idflags. - ghcOptHideAllPackages :: Flag Bool
Start with a clean package set; the
ghc -hide-all-packagesflag - ghcOptWarnMissingHomeModules :: Flag Bool
Warn about modules, not listed in command line
- ghcOptNoAutoLinkPackages :: Flag Bool
Don't automatically link in Haskell98 etc; the
ghc -no-auto-link-packagesflag. - ghcOptLinkLibs :: [FilePath]
Names of libraries to link in; the
ghc -lflag. - ghcOptLinkLibPath :: NubListR (SymbolicPath Pkg ('Dir Lib))
Search path for libraries to link in; the
ghc -Lflag. - ghcOptLinkOptions :: [String]
Options to pass through to the linker; the
ghc -optlflag. - ghcOptLinkFrameworks :: NubListR String
OSX only: frameworks to link in; the
ghc -frameworkflag. - ghcOptLinkFrameworkDirs :: NubListR (SymbolicPath Pkg ('Dir Framework))
OSX only: Search path for frameworks to link in; the
ghc -framework-pathflag. - ghcOptLinkRts :: Flag Bool
Instruct GHC to link against
libHSrtswhen producing a shared library. - ghcOptNoLink :: Flag Bool
Don't do the link step, useful in make mode; the
ghc -no-linkflag. - ghcOptLinkNoHsMain :: Flag Bool
Don't link in the normal RTS
mainentry point; theghc -no-hs-mainflag. - ghcOptLinkModDefFiles :: NubListR FilePath
Module definition files (Windows specific)
- ghcOptCcOptions :: [String]
Options to pass through to the C compiler; the
ghc -optcflag. - ghcOptCxxOptions :: [String]
Options to pass through to the C++ compiler.
- ghcOptAsmOptions :: [String]
Options to pass through to the Assembler.
- ghcOptCppOptions :: [String]
Options to pass through to CPP; the
ghc -optPflag. - ghcOptCppIncludePath :: NubListR (SymbolicPath Pkg ('Dir Include))
Search path for CPP includes like header files; the
ghc -Iflag. - ghcOptCppIncludes :: NubListR (SymbolicPath Pkg 'File)
Extra header files to include at CPP stage; the
ghc -optP-includeflag. - ghcOptFfiIncludes :: NubListR FilePath
Extra header files to include for old-style FFI; the
ghc -#includeflag. - ghcOptCcProgram :: Flag FilePath
Program to use for the C and C++ compiler; the
ghc -pgmcflag. - ghcOptLanguage :: Flag Language
The base language; the
ghc -XHaskell98or-XHaskell2010flag. - ghcOptExtensions :: NubListR Extension
The language extensions; the
ghc -Xflag. - ghcOptExtensionMap :: Map Extension (Maybe CompilerFlag)
A GHC version-dependent mapping of extensions to flags. This must be set to be able to make use of the
ghcOptExtensions. - ghcOptOptimisation :: Flag GhcOptimisation
What optimisation level to use; the
ghc -Oflag. - ghcOptDebugInfo :: Flag DebugInfoLevel
Emit debug info; the
ghc -gflag. - ghcOptProfilingMode :: Flag Bool
Compile in profiling mode; the
ghc -profflag. - ghcOptProfilingAuto :: Flag GhcProfAuto
Automatically add profiling cost centers; the
ghc -fprof-auto*flags. - ghcOptSplitSections :: Flag Bool
Use the "split sections" feature; the
ghc -split-sectionsflag. - ghcOptSplitObjs :: Flag Bool
Use the "split object files" feature; the
ghc -split-objsflag. - ghcOptNumJobs :: Flag ParStrat
Run N jobs simultaneously (if possible).
- ghcOptHPCDir :: Flag (SymbolicPath Pkg ('Dir Mix))
Enable coverage analysis; the
ghc -fhpc -hpcdirflags. - ghcOptGHCiScripts :: [FilePath]
Extra GHCi startup scripts; the
-ghci-scriptflag - ghcOptHiSuffix :: Flag String
- ghcOptObjSuffix :: Flag String
- ghcOptDynHiSuffix :: Flag String
only in
GhcStaticAndDynamicmode - ghcOptDynObjSuffix :: Flag String
only in
GhcStaticAndDynamicmode - ghcOptHiDir :: Flag (SymbolicPath Pkg ('Dir Artifacts))
- ghcOptHieDir :: Flag (SymbolicPath Pkg ('Dir Artifacts))
- ghcOptObjDir :: Flag (SymbolicPath Pkg ('Dir Artifacts))
- ghcOptOutputDir :: Flag (SymbolicPath Pkg ('Dir Artifacts))
- ghcOptStubDir :: Flag (SymbolicPath Pkg ('Dir Artifacts))
- ghcOptDynLinkMode :: Flag GhcDynLinkMode
- ghcOptStaticLib :: Flag Bool
- ghcOptShared :: Flag Bool
- ghcOptFPic :: Flag Bool
- ghcOptDylibName :: Flag String
- ghcOptRPaths :: NubListR FilePath
- ghcOptVerbosity :: Flag Verbosity
Get GHC to be quiet or verbose with what it's doing; the
ghc -vflag. - ghcOptExtraPath :: NubListR (SymbolicPath Pkg ('Dir Build))
Put the extra folders in the PATH environment variable we invoke GHC with
- ghcOptCabal :: Flag Bool
Let GHC know that it is Cabal that's calling it. Modifies some of the GHC error messages.
Instances
Instances details
Instance details
Defined in Distribution.Simple.Program.GHC
Methods
mempty :: GhcOptions #
mappend :: GhcOptions -> GhcOptions -> GhcOptions #
mconcat :: [GhcOptions] -> GhcOptions #
Instance details
Defined in Distribution.Simple.Program.GHC
Methods
(<>) :: GhcOptions -> GhcOptions -> GhcOptions #
sconcat :: NonEmpty GhcOptions -> GhcOptions #
stimes :: Integral b => b -> GhcOptions -> GhcOptions #
Instance details
Defined in Distribution.Simple.Program.GHC
Associated Types
Instance details
Defined in Distribution.Simple.Program.GHC
Instance details
Defined in Distribution.Simple.Program.GHC
Methods
showsPrec :: Int -> GhcOptions -> ShowS #
show :: GhcOptions -> String #
showList :: [GhcOptions] -> ShowS #
Instance details
Defined in Distribution.Simple.Program.GHC
Constructors
ghc -c
ghc
ghc --make
ghci / ghc --interactive
ghc --abi-hash
| GhcModeDepAnalysis -- ^ ghc -M
| GhcModeEvaluate -- ^ ghc -e
Instances
Instances details
data GhcOptimisation Source #
Constructors
Instances
Instances details
Instance details
Defined in Distribution.Simple.Program.GHC
Methods
showsPrec :: Int -> GhcOptimisation -> ShowS #
show :: GhcOptimisation -> String #
showList :: [GhcOptimisation] -> ShowS #
Instance details
Defined in Distribution.Simple.Program.GHC
Methods
(==) :: GhcOptimisation -> GhcOptimisation -> Bool #
(/=) :: GhcOptimisation -> GhcOptimisation -> Bool #
data GhcDynLinkMode Source #
Instances
Instances details
Instance details
Defined in Distribution.Simple.Program.GHC
Methods
showsPrec :: Int -> GhcDynLinkMode -> ShowS #
show :: GhcDynLinkMode -> String #
showList :: [GhcDynLinkMode] -> ShowS #
Instance details
Defined in Distribution.Simple.Program.GHC
Methods
(==) :: GhcDynLinkMode -> GhcDynLinkMode -> Bool #
(/=) :: GhcDynLinkMode -> GhcDynLinkMode -> Bool #
data GhcProfAuto Source #
Constructors
-fprof-auto
-fprof-auto-top
-fprof-auto-exported
@-fprof-late
Instances
Instances details
Instance details
Defined in Distribution.Simple.Program.GHC
Methods
showsPrec :: Int -> GhcProfAuto -> ShowS #
show :: GhcProfAuto -> String #
showList :: [GhcProfAuto] -> ShowS #
Instance details
Defined in Distribution.Simple.Program.GHC
ghcInvocation :: Verbosity -> ConfiguredProgram -> Compiler -> Platform -> Maybe (SymbolicPath CWD ('Dir Pkg)) -> GhcOptions -> IO ProgramInvocation Source #
renderGhcOptions :: Compiler -> Platform -> GhcOptions -> [String] Source #
runGHC :: Verbosity -> ConfiguredProgram -> Compiler -> Platform -> Maybe (SymbolicPath CWD ('Dir Pkg)) -> GhcOptions -> IO () Source #
packageDbArgsDb :: PackageDBStackCWD -> [String] Source #
GHC >= 7.6 uses the '-package-db' flag. See https://gitlab.haskell.org/ghc/ghc/-/issues/5977.
normaliseGhcArgs :: Maybe Version -> PackageDescription -> [String] -> [String] Source #