Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- getGhcInfo :: Verbosity -> ConfiguredProgram -> IO [(String, String)]
- configure :: Verbosity -> Maybe FilePath -> Maybe FilePath -> ProgramDb -> IO (Compiler, Maybe Platform, ProgramDb)
- getInstalledPackages :: Verbosity -> Maybe (SymbolicPath CWD ('Dir from)) -> PackageDBStackX (SymbolicPath from ('Dir PkgDB)) -> ProgramDb -> IO InstalledPackageIndex
- getInstalledPackagesMonitorFiles :: Verbosity -> Platform -> Maybe (SymbolicPath CWD ('Dir Pkg)) -> ProgramDb -> [PackageDB] -> IO [FilePath]
- getPackageDBContents :: Verbosity -> Maybe (SymbolicPath CWD ('Dir from)) -> PackageDBX (SymbolicPath from ('Dir PkgDB)) -> ProgramDb -> IO InstalledPackageIndex
- buildLib :: Verbosity -> 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 :: [String] -> Verbosity -> Flag ParStrat -> PackageDescription -> LocalBuildInfo -> Library -> ComponentLocalBuildInfo -> IO ()
- replFLib :: [String] -> Verbosity -> Flag ParStrat -> PackageDescription -> LocalBuildInfo -> ForeignLib -> ComponentLocalBuildInfo -> IO ()
- replExe :: [String] -> Verbosity -> 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
- getLibDir :: Verbosity -> LocalBuildInfo -> IO FilePath
- isDynamic :: Compiler -> Bool
- getGlobalPackageDB :: Verbosity -> ConfiguredProgram -> IO FilePath
- pkgRoot :: Verbosity -> LocalBuildInfo -> PackageDB -> IO FilePath
- runCmd :: ProgramDb -> FilePath -> (FilePath, FilePath, [String])
- 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 -> Maybe (SymbolicPath CWD ('Dir from)) -> PackageDBStackX (SymbolicPath from ('Dir PkgDB)) -> ProgramDb -> IO InstalledPackageIndex Source #
Given a package DB stack, return all installed packages.
getInstalledPackagesMonitorFiles :: Verbosity -> Platform -> Maybe (SymbolicPath CWD ('Dir Pkg)) -> ProgramDb -> [PackageDB] -> IO [FilePath] Source #
Get the packages from specific PackageDBs, not cumulative.
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 :: Verbosity -> 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 :: [String] -> Verbosity -> Flag ParStrat -> PackageDescription -> LocalBuildInfo -> Library -> ComponentLocalBuildInfo -> IO () Source #
replFLib :: [String] -> Verbosity -> Flag ParStrat -> PackageDescription -> LocalBuildInfo -> ForeignLib -> ComponentLocalBuildInfo -> IO () Source #
replExe :: [String] -> Verbosity -> Flag ParStrat -> PackageDescription -> LocalBuildInfo -> Executable -> ComponentLocalBuildInfo -> IO () Source #
startInterpreter :: Verbosity -> ProgramDb -> Compiler -> Platform -> PackageDBStack -> IO () Source #
Start a REPL without loading any source files.
:: 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
:: Verbosity | |
-> LocalBuildInfo | |
-> FilePath | install location |
-> FilePath | Build location |
-> PackageDescription | |
-> ForeignLib | |
-> IO () |
Install foreign library for GHC.
:: Verbosity | |
-> LocalBuildInfo | |
-> FilePath | Where to copy the files to |
-> FilePath | Build location |
-> (FilePath, FilePath) | Executable (prefix,suffix) |
-> PackageDescription | |
-> Executable | |
-> IO () |
Install executables for GHCJS.
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 #
getGlobalPackageDB :: Verbosity -> ConfiguredProgram -> IO FilePath Source #
Return the FilePath
to the global GHC package database.
runCmd :: ProgramDb -> FilePath -> (FilePath, FilePath, [String]) Source #
Get the JavaScript file name and command and arguments to run a program compiled by GHCJS the exe should be the base program name without exe extension
Constructing and deconstructing GHC environment files
data GhcEnvironmentFileEntry fp Source #
The kinds of entries we can stick in a .ghc.environment
file.
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
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 #
Instances
Exception ParseErrorExc Source # | |
Defined in Distribution.Simple.GHC.EnvironmentParser | |
Show ParseErrorExc Source # | |
Defined in Distribution.Simple.GHC.EnvironmentParser 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.
GhcImplInfo | |
|