| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Distribution.Simple.Program.GHC
Synopsis
- data GhcOptions = GhcOptions {
- ghcOptMode :: Flag GhcMode
 - ghcOptExtra :: [String]
 - ghcOptExtraDefault :: [String]
 - ghcOptInputFiles :: NubListR FilePath
 - ghcOptInputModules :: NubListR ModuleName
 - ghcOptOutputFile :: Flag FilePath
 - ghcOptOutputDynFile :: Flag FilePath
 - ghcOptSourcePathClear :: Flag Bool
 - ghcOptSourcePath :: NubListR FilePath
 - 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 FilePath
 - ghcOptLinkOptions :: [String]
 - ghcOptLinkFrameworks :: NubListR String
 - ghcOptLinkFrameworkDirs :: NubListR String
 - ghcOptNoLink :: Flag Bool
 - ghcOptLinkNoHsMain :: Flag Bool
 - ghcOptLinkModDefFiles :: NubListR FilePath
 - ghcOptCcOptions :: [String]
 - ghcOptCxxOptions :: [String]
 - ghcOptCppOptions :: [String]
 - ghcOptCppIncludePath :: NubListR FilePath
 - ghcOptCppIncludes :: NubListR FilePath
 - ghcOptFfiIncludes :: NubListR FilePath
 - ghcOptLanguage :: Flag Language
 - ghcOptExtensions :: NubListR Extension
 - ghcOptExtensionMap :: Map Extension (Maybe Flag)
 - ghcOptOptimisation :: Flag GhcOptimisation
 - ghcOptDebugInfo :: Flag DebugInfoLevel
 - ghcOptProfilingMode :: Flag Bool
 - ghcOptProfilingAuto :: Flag GhcProfAuto
 - ghcOptSplitSections :: Flag Bool
 - ghcOptSplitObjs :: Flag Bool
 - ghcOptNumJobs :: Flag (Maybe Int)
 - ghcOptHPCDir :: Flag FilePath
 - ghcOptGHCiScripts :: [FilePath]
 - ghcOptHiSuffix :: Flag String
 - ghcOptObjSuffix :: Flag String
 - ghcOptDynHiSuffix :: Flag String
 - ghcOptDynObjSuffix :: Flag String
 - ghcOptHiDir :: Flag FilePath
 - ghcOptObjDir :: Flag FilePath
 - ghcOptOutputDir :: Flag FilePath
 - ghcOptStubDir :: Flag FilePath
 - ghcOptDynLinkMode :: Flag GhcDynLinkMode
 - ghcOptStaticLib :: Flag Bool
 - ghcOptShared :: Flag Bool
 - ghcOptFPic :: Flag Bool
 - ghcOptDylibName :: Flag String
 - ghcOptRPaths :: NubListR FilePath
 - ghcOptVerbosity :: Flag Verbosity
 - ghcOptExtraPath :: NubListR FilePath
 - ghcOptCabal :: Flag Bool
 
 - data GhcMode
 - data GhcOptimisation
 - data GhcDynLinkMode
 - data GhcProfAuto
 - ghcInvocation :: ConfiguredProgram -> Compiler -> Platform -> GhcOptions -> ProgramInvocation
 - renderGhcOptions :: Compiler -> Platform -> GhcOptions -> [String]
 - runGHC :: Verbosity -> ConfiguredProgram -> Compiler -> Platform -> GhcOptions -> IO ()
 - packageDbArgsDb :: PackageDBStack -> [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
| GhcOptions | |
Fields 
  | |
Instances
Constructors
| GhcModeCompile | ghc -c  | 
| GhcModeLink | ghc  | 
| GhcModeMake | ghc --make  | 
| GhcModeInteractive | 
  | 
| GhcModeAbiHash | 
  | 
data GhcOptimisation Source #
Constructors
| GhcNoOptimisation | -O0  | 
| GhcNormalOptimisation | -O  | 
| GhcMaximumOptimisation | -O2  | 
| GhcSpecialOptimisation String | e.g.   | 
Instances
| Eq GhcOptimisation Source # | |
Defined in Distribution.Simple.Program.GHC Methods (==) :: GhcOptimisation -> GhcOptimisation -> Bool # (/=) :: GhcOptimisation -> GhcOptimisation -> Bool #  | |
| Show GhcOptimisation Source # | |
Defined in Distribution.Simple.Program.GHC Methods showsPrec :: Int -> GhcOptimisation -> ShowS # show :: GhcOptimisation -> String # showList :: [GhcOptimisation] -> ShowS #  | |
data GhcDynLinkMode Source #
Constructors
| GhcStaticOnly | -static  | 
| GhcDynamicOnly | -dynamic  | 
| GhcStaticAndDynamic | -static -dynamic-too  | 
Instances
| Eq GhcDynLinkMode Source # | |
Defined in Distribution.Simple.Program.GHC Methods (==) :: GhcDynLinkMode -> GhcDynLinkMode -> Bool # (/=) :: GhcDynLinkMode -> GhcDynLinkMode -> Bool #  | |
| Show GhcDynLinkMode Source # | |
Defined in Distribution.Simple.Program.GHC Methods showsPrec :: Int -> GhcDynLinkMode -> ShowS # show :: GhcDynLinkMode -> String # showList :: [GhcDynLinkMode] -> ShowS #  | |
data GhcProfAuto Source #
Constructors
| GhcProfAutoAll | -fprof-auto  | 
| GhcProfAutoToplevel | -fprof-auto-top  | 
| GhcProfAutoExported | -fprof-auto-exported  | 
Instances
| Eq GhcProfAuto Source # | |
Defined in Distribution.Simple.Program.GHC  | |
| Show GhcProfAuto Source # | |
Defined in Distribution.Simple.Program.GHC Methods showsPrec :: Int -> GhcProfAuto -> ShowS # show :: GhcProfAuto -> String # showList :: [GhcProfAuto] -> ShowS #  | |
ghcInvocation :: ConfiguredProgram -> Compiler -> Platform -> GhcOptions -> ProgramInvocation Source #
renderGhcOptions :: Compiler -> Platform -> GhcOptions -> [String] Source #
runGHC :: Verbosity -> ConfiguredProgram -> Compiler -> Platform -> GhcOptions -> IO () Source #
packageDbArgsDb :: PackageDBStack -> [String] Source #
GHC >= 7.6 uses the '-package-db' flag. See https://ghc.haskell.org/trac/ghc/ticket/5977.
normaliseGhcArgs :: Maybe Version -> PackageDescription -> [String] -> [String] Source #