| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
GHC.Check
Synopsis
- makeGhcVersionChecker :: IO FilePath -> SpliceQ GhcVersionChecker
- type GhcVersionChecker = String -> IO InstallationCheck
- data InstallationCheck
- = InstallationChecked { }
- | InstallationMismatch {
- libdir :: !String
- compileTime, runTime :: !Version
- | InstallationNotFound { }
- data PackageCheckResult
- data PackageCheck
- = VersionMismatch {
- compileTime, runTime :: !Version
- | AbiMismatch {
- compileTimeAbi, runTimeAbi :: !String
- compileTime :: !Version
- | VersionMatch { }
- = VersionMismatch {
- guessCompatibility :: PackageCheckResult -> CompatibilityGuess
- data CompatibilityGuess
- = ProbablyCompatible { }
- | NotCompatible { }
- data NotCompatibleReason
- = PackageVersionMismatch {
- compileTime :: !Version
- runTime :: !Version
- packageName :: !String
- | BasePackageAbiMismatch {
- compileTimeAbi :: !String
- runTimeAbi :: !String
- compileTime :: !Version
- = PackageVersionMismatch {
- checkGhcVersion :: [(String, PackageVersion)] -> GhcVersionChecker
GHC version check
makeGhcVersionChecker :: IO FilePath -> SpliceQ GhcVersionChecker Source #
makeGhcVersionChecker libdir returns a function to check the run-time
version of GHC against the compile-time version. It performs two checks:
- It checks the version of the GHC installation given the run-time libdir In some platforms, like Nix, the libdir is not fixed at compile-time
- It compares the version of the
ghcpackage, if found at run-time. If not, it compares the abi of thebasepackage.
ghcChecker :: IO(Ghc (String -> PackageCheck))
ghcChecker = $$(makeGhcVersionChecker (pure $ Just GHC.Paths.libdir))
checkGhcVersion :: IO ()
checkGhcVersion = do
InstallationChecked packageCheck <- ghcChecker runTimeLibdir
res <- runGhc (Just runTimeLibdir) $ do
setupGhcApi
result <- packageCheck
case guessCompatibility result of ...type GhcVersionChecker = String -> IO InstallationCheck Source #
Given a run-time libdir, checks the ghc installation and returns
a Ghc action to check the package database
data InstallationCheck Source #
Constructors
| InstallationChecked | The GHC installation looks fine. Further checks are needed for the package libraries. |
Fields
| |
| InstallationMismatch | The libdir points to a different GHC version |
Fields
| |
| InstallationNotFound | The libdir does not exist |
data PackageCheckResult Source #
Constructors
| PackageCheckSuccess !(NonEmpty (String, PackageCheck)) | All the compile time packages tested match |
| PackageCheckFailure !(NonEmpty (String, PackageCheck)) | Found package mismatches |
| PackageCheckInconclusive ![String] | None of the compile time packages could be found |
| PackageCheckError !SomeException | An exception arised during the package check |
data PackageCheck Source #
Constructors
| VersionMismatch | Different versions |
Fields
| |
| AbiMismatch | Same version but different abi |
Fields
| |
| VersionMatch | Same version and abi |
Fields | |
Instances
| Eq PackageCheck Source # | |
Defined in GHC.Check | |
| Show PackageCheck Source # | |
Defined in GHC.Check Methods showsPrec :: Int -> PackageCheck -> ShowS # show :: PackageCheck -> String # showList :: [PackageCheck] -> ShowS # | |
Interpreting the results
guessCompatibility :: PackageCheckResult -> CompatibilityGuess Source #
Interpret a PackageCheckResult into a yes/no GHC compatibility answer
data CompatibilityGuess Source #
The result of interpreting a PackageCheckResult
Constructors
| ProbablyCompatible | |
| NotCompatible | |
Fields | |
Instances
| Eq CompatibilityGuess Source # | |
Defined in GHC.Check Methods (==) :: CompatibilityGuess -> CompatibilityGuess -> Bool # (/=) :: CompatibilityGuess -> CompatibilityGuess -> Bool # | |
| Show CompatibilityGuess Source # | |
Defined in GHC.Check Methods showsPrec :: Int -> CompatibilityGuess -> ShowS # show :: CompatibilityGuess -> String # showList :: [CompatibilityGuess] -> ShowS # | |
data NotCompatibleReason Source #
Constructors
| PackageVersionMismatch | |
Fields
| |
| BasePackageAbiMismatch | |
Fields
| |
Instances
| Eq NotCompatibleReason Source # | |
Defined in GHC.Check Methods (==) :: NotCompatibleReason -> NotCompatibleReason -> Bool # (/=) :: NotCompatibleReason -> NotCompatibleReason -> Bool # | |
| Show NotCompatibleReason Source # | |
Defined in GHC.Check Methods showsPrec :: Int -> NotCompatibleReason -> ShowS # show :: NotCompatibleReason -> String # showList :: [NotCompatibleReason] -> ShowS # | |
Exports for TH
checkGhcVersion :: [(String, PackageVersion)] -> GhcVersionChecker Source #
Checks if the run-time version of the ghc package matches the given version.
If the package database contains an unstable ghc library version, we omit the package version check. This leads to a more convenient usage for working on GHC. When developing for or on GHC, you can compile GHC HEAD with a bootstrap compiler and use the freshly compiled ghc library to load programs that use the latest GHC API. We consider the ghc version to be unstable according to the GHC User Guide