| Copyright | Isaac Jones 2003-2007 | 
|---|---|
| License | BSD3 | 
| Maintainer | cabal-devel@haskell.org | 
| Portability | portable | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Distribution.Simple.GHC
Description
This is a fairly large module. It contains most of the GHC-specific code for
 configuring, building and installing packages. It also exports a function
 for finding out what packages are already installed. Configuring involves
 finding the ghc and ghc-pkg programs, finding what language extensions
 this version of ghc supports and returning a Compiler value.
getInstalledPackages involves calling the ghc-pkg program to find out
 what packages are installed.
Building is somewhat complex as there is quite a bit of information to take
 into account. We have to build libs and programs, possibly for profiling and
 shared libs. We have to support building libraries that will be usable by
 GHCi and also ghc's -split-objs feature. We have to compile any C files
 using ghc. Linking, especially for split-objs is remarkably complex,
 partly because there tend to be 1,000's of .o files and this can often be
 more than we can pass to the ld or ar programs in one go.
Installing for libs and exes involves finding the right files and copying them to the right places. One of the more tricky things about this module is remembering the layout of files in the build directory (which is not explicitly documented) and thus what search dirs are used for various kinds of files.
Synopsis
- getGhcInfo :: Verbosity -> ConfiguredProgram -> IO [(String, String)]
 - configure :: Verbosity -> Maybe FilePath -> Maybe FilePath -> ProgramDb -> IO (Compiler, Maybe Platform, ProgramDb)
 - getInstalledPackages :: Verbosity -> Compiler -> Maybe (SymbolicPath CWD (Dir from)) -> PackageDBStackX (SymbolicPath from (Dir PkgDB)) -> ProgramDb -> IO InstalledPackageIndex
 - getInstalledPackagesMonitorFiles :: forall from. Verbosity -> Maybe (SymbolicPath CWD (Dir from)) -> Platform -> ProgramDb -> [PackageDBS from] -> IO [FilePath]
 - getPackageDBContents :: Verbosity -> Maybe (SymbolicPath CWD (Dir from)) -> PackageDBX (SymbolicPath from (Dir PkgDB)) -> ProgramDb -> IO InstalledPackageIndex
 - buildLib :: BuildFlags -> Flag ParStrat -> PackageDescription -> LocalBuildInfo -> Library -> ComponentLocalBuildInfo -> IO ()
 - buildFLib :: Verbosity -> Flag ParStrat -> PackageDescription -> LocalBuildInfo -> ForeignLib -> ComponentLocalBuildInfo -> IO ()
 - buildExe :: Verbosity -> Flag ParStrat -> PackageDescription -> LocalBuildInfo -> Executable -> ComponentLocalBuildInfo -> IO ()
 - replLib :: ReplFlags -> Flag ParStrat -> PackageDescription -> LocalBuildInfo -> Library -> ComponentLocalBuildInfo -> IO ()
 - replFLib :: ReplFlags -> Flag ParStrat -> PackageDescription -> LocalBuildInfo -> ForeignLib -> ComponentLocalBuildInfo -> IO ()
 - replExe :: ReplFlags -> Flag ParStrat -> PackageDescription -> LocalBuildInfo -> Executable -> ComponentLocalBuildInfo -> IO ()
 - startInterpreter :: Verbosity -> ProgramDb -> Compiler -> Platform -> PackageDBStack -> IO ()
 - installLib :: Verbosity -> LocalBuildInfo -> FilePath -> FilePath -> FilePath -> PackageDescription -> Library -> ComponentLocalBuildInfo -> IO ()
 - installFLib :: Verbosity -> LocalBuildInfo -> FilePath -> FilePath -> PackageDescription -> ForeignLib -> IO ()
 - installExe :: Verbosity -> LocalBuildInfo -> FilePath -> FilePath -> (FilePath, FilePath) -> PackageDescription -> Executable -> IO ()
 - libAbiHash :: Verbosity -> PackageDescription -> LocalBuildInfo -> Library -> ComponentLocalBuildInfo -> IO String
 - hcPkgInfo :: ProgramDb -> HcPkgInfo
 - registerPackage :: Verbosity -> ProgramDb -> Maybe (SymbolicPath CWD (Dir from)) -> PackageDBStackS from -> InstalledPackageInfo -> RegisterOptions -> IO ()
 - componentGhcOptions :: Verbosity -> LocalBuildInfo -> BuildInfo -> ComponentLocalBuildInfo -> SymbolicPath Pkg (Dir build) -> GhcOptions
 - componentCcGhcOptions :: Verbosity -> LocalBuildInfo -> BuildInfo -> ComponentLocalBuildInfo -> SymbolicPath Pkg (Dir Artifacts) -> SymbolicPath Pkg File -> GhcOptions
 - getGhcAppDir :: IO FilePath
 - getLibDir :: Verbosity -> LocalBuildInfo -> IO FilePath
 - compilerBuildWay :: Compiler -> BuildWay
 - getGlobalPackageDB :: Verbosity -> ConfiguredProgram -> IO FilePath
 - pkgRoot :: Verbosity -> LocalBuildInfo -> PackageDB -> IO (SymbolicPath CWD (Dir Pkg))
 - data GhcEnvironmentFileEntry fp
 - simpleGhcEnvironmentFile :: PackageDBStackX fp -> [UnitId] -> [GhcEnvironmentFileEntry fp]
 - renderGhcEnvironmentFile :: [GhcEnvironmentFileEntry FilePath] -> String
 - writeGhcEnvironmentFile :: FilePath -> Platform -> Version -> [GhcEnvironmentFileEntry FilePath] -> IO FilePath
 - ghcPlatformAndVersionString :: Platform -> Version -> String
 - readGhcEnvironmentFile :: FilePath -> IO [GhcEnvironmentFileEntry FilePath]
 - parseGhcEnvironmentFile :: Parser [GhcEnvironmentFileEntry FilePath]
 - newtype ParseErrorExc = ParseErrorExc ParseError
 - getImplInfo :: Compiler -> GhcImplInfo
 - data GhcImplInfo = GhcImplInfo {
- supportsHaskell2010 :: Bool
 - supportsGHC2021 :: Bool
 - supportsGHC2024 :: Bool
 - reportsNoExt :: Bool
 - alwaysNondecIndent :: Bool
 - flagGhciScript :: Bool
 - flagProfAuto :: Bool
 - flagProfLate :: Bool
 - flagPackageConf :: Bool
 - flagDebugInfo :: Bool
 - flagHie :: Bool
 - supportsDebugLevels :: Bool
 - supportsPkgEnvFiles :: Bool
 - flagWarnMissingHomeModules :: Bool
 - unitIdForExes :: Bool
 
 
Documentation
getGhcInfo :: Verbosity -> ConfiguredProgram -> IO [(String, String)] Source #
configure :: Verbosity -> Maybe FilePath -> Maybe FilePath -> ProgramDb -> IO (Compiler, Maybe Platform, ProgramDb) Source #
getInstalledPackages :: Verbosity -> Compiler -> Maybe (SymbolicPath CWD (Dir from)) -> PackageDBStackX (SymbolicPath from (Dir PkgDB)) -> ProgramDb -> IO InstalledPackageIndex Source #
Given a package DB stack, return all installed packages.
getInstalledPackagesMonitorFiles :: forall from. Verbosity -> Maybe (SymbolicPath CWD (Dir from)) -> Platform -> ProgramDb -> [PackageDBS from] -> IO [FilePath] Source #
getPackageDBContents :: Verbosity -> Maybe (SymbolicPath CWD (Dir from)) -> PackageDBX (SymbolicPath from (Dir PkgDB)) -> ProgramDb -> IO InstalledPackageIndex Source #
Given a single package DB, return all installed packages.
buildLib :: BuildFlags -> Flag ParStrat -> PackageDescription -> LocalBuildInfo -> Library -> ComponentLocalBuildInfo -> IO () Source #
buildFLib :: Verbosity -> Flag ParStrat -> PackageDescription -> LocalBuildInfo -> ForeignLib -> ComponentLocalBuildInfo -> IO () Source #
Build a foreign library
buildExe :: Verbosity -> Flag ParStrat -> PackageDescription -> LocalBuildInfo -> Executable -> ComponentLocalBuildInfo -> IO () Source #
Build an executable with GHC.
replLib :: ReplFlags -> Flag ParStrat -> PackageDescription -> LocalBuildInfo -> Library -> ComponentLocalBuildInfo -> IO () Source #
replFLib :: ReplFlags -> Flag ParStrat -> PackageDescription -> LocalBuildInfo -> ForeignLib -> ComponentLocalBuildInfo -> IO () Source #
replExe :: ReplFlags -> Flag ParStrat -> PackageDescription -> LocalBuildInfo -> Executable -> ComponentLocalBuildInfo -> IO () Source #
startInterpreter :: Verbosity -> ProgramDb -> Compiler -> Platform -> PackageDBStack -> IO () Source #
Start a REPL without loading any source files.
Arguments
| :: Verbosity | |
| -> LocalBuildInfo | |
| -> FilePath | install location  | 
| -> FilePath | install location for dynamic libraries  | 
| -> FilePath | Build location  | 
| -> PackageDescription | |
| -> Library | |
| -> ComponentLocalBuildInfo | |
| -> IO () | 
Install for ghc, .hi, .a and, if --with-ghci given, .o
Arguments
| :: Verbosity | |
| -> LocalBuildInfo | |
| -> FilePath | install location  | 
| -> FilePath | Build location  | 
| -> PackageDescription | |
| -> ForeignLib | |
| -> IO () | 
Install foreign library for GHC.
Arguments
| :: Verbosity | |
| -> LocalBuildInfo | |
| -> FilePath | Where to copy the files to  | 
| -> FilePath | Build location  | 
| -> (FilePath, FilePath) | Executable (prefix,suffix)  | 
| -> PackageDescription | |
| -> Executable | |
| -> IO () | 
Install executables for GHC.
libAbiHash :: Verbosity -> PackageDescription -> LocalBuildInfo -> Library -> ComponentLocalBuildInfo -> IO String Source #
Extracts a String representing a hash of the ABI of a built library. It can fail if the library has not yet been built.
registerPackage :: Verbosity -> ProgramDb -> Maybe (SymbolicPath CWD (Dir from)) -> PackageDBStackS from -> InstalledPackageInfo -> RegisterOptions -> IO () Source #
componentGhcOptions :: Verbosity -> LocalBuildInfo -> BuildInfo -> ComponentLocalBuildInfo -> SymbolicPath Pkg (Dir build) -> GhcOptions Source #
componentCcGhcOptions :: Verbosity -> LocalBuildInfo -> BuildInfo -> ComponentLocalBuildInfo -> SymbolicPath Pkg (Dir Artifacts) -> SymbolicPath Pkg File -> GhcOptions Source #
getGhcAppDir :: IO FilePath Source #
Return the FilePath to the GHC application data directory.
Since: 3.4.0.0
compilerBuildWay :: Compiler -> BuildWay Source #
getGlobalPackageDB :: Verbosity -> ConfiguredProgram -> IO FilePath Source #
Return the FilePath to the global GHC package database.
Constructing and deconstructing GHC environment files
data GhcEnvironmentFileEntry fp Source #
The kinds of entries we can stick in a .ghc.environment file.
Constructors
| GhcEnvFileComment String | -- a comment  | 
| GhcEnvFilePackageId UnitId | package-id foo-1.0-4fe301a...  | 
| GhcEnvFilePackageDb (PackageDBX fp) | 
  | 
| GhcEnvFileClearPackageDbStack | clear-package-db  | 
Instances
simpleGhcEnvironmentFile :: PackageDBStackX fp -> [UnitId] -> [GhcEnvironmentFileEntry fp] Source #
Make entries for a GHC environment file based on a PackageDBStack and
 a bunch of package (unit) ids.
If you need to do anything more complicated then either use this as a basis and add more entries, or just make all the entries directly.
renderGhcEnvironmentFile :: [GhcEnvironmentFileEntry FilePath] -> String Source #
Render a bunch of GHC environment file entries
writeGhcEnvironmentFile Source #
Arguments
| :: FilePath | directory in which to put it  | 
| -> Platform | the GHC target platform  | 
| -> Version | the GHC version  | 
| -> [GhcEnvironmentFileEntry FilePath] | the content  | 
| -> IO FilePath | 
Write a .ghc.environment-$arch-$os-$ver file in the given directory.
The Platform and GHC Version are needed as part of the file name.
Returns the name of the file written.
ghcPlatformAndVersionString :: Platform -> Version -> String Source #
GHC's rendering of its platform and compiler version string as used in
 certain file locations (such as user package db location).
 For example x86_64-linux-7.10.4
newtype ParseErrorExc Source #
Constructors
| ParseErrorExc ParseError | 
Instances
| Exception ParseErrorExc Source # | |
Defined in Distribution.Simple.GHC.EnvironmentParser Methods toException :: ParseErrorExc -> SomeException # fromException :: SomeException -> Maybe ParseErrorExc # displayException :: ParseErrorExc -> String #  | |
| Show ParseErrorExc Source # | |
Defined in Distribution.Simple.GHC.EnvironmentParser Methods showsPrec :: Int -> ParseErrorExc -> ShowS # show :: ParseErrorExc -> String # showList :: [ParseErrorExc] -> ShowS #  | |
Version-specific implementation quirks
getImplInfo :: Compiler -> GhcImplInfo Source #
data GhcImplInfo Source #
Information about features and quirks of a GHC-based implementation.
Compiler flavors based on GHC behave similarly enough that some of the support code for them is shared. Every implementation has its own peculiarities, that may or may not be a direct result of the underlying GHC version. This record keeps track of these differences.
All shared code (i.e. everything not in the Distribution.Simple.FLAVOR module) should use implementation info rather than version numbers to test for supported features.
Constructors
| GhcImplInfo | |
Fields 
  | |