{-# LANGUAGE LambdaCase #-}
module Distribution.Simple.Errors
( CabalException (..)
, FailedDependency (..)
, exceptionCode
, exceptionMessage
) where
import Distribution.Compat.Prelude
import Distribution.Compiler
import Distribution.InstalledPackageInfo
import Distribution.ModuleName
import Distribution.Package
import Distribution.PackageDescription
import Distribution.Pretty
( Pretty (pretty)
, prettyShow
)
import Distribution.Simple.InstallDirs
import Distribution.Simple.PreProcess.Types (Suffix)
import Distribution.Simple.SetupHooks.Errors
import Distribution.System (OS)
import Distribution.Types.VersionRange.Internal ()
import Distribution.Version
import Text.PrettyPrint
data FailedDependency
= DependencyNotExists PackageName
| DependencyMissingInternal PackageName LibraryName
| DependencyNoVersion Dependency
deriving (Int -> FailedDependency -> ShowS
[FailedDependency] -> ShowS
FailedDependency -> String
(Int -> FailedDependency -> ShowS)
-> (FailedDependency -> String)
-> ([FailedDependency] -> ShowS)
-> Show FailedDependency
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FailedDependency -> ShowS
showsPrec :: Int -> FailedDependency -> ShowS
$cshow :: FailedDependency -> String
show :: FailedDependency -> String
$cshowList :: [FailedDependency] -> ShowS
showList :: [FailedDependency] -> ShowS
Show)
data CabalException
= NoBenchMarkProgram FilePath
| EnableBenchMark
| BenchMarkNameDisabled String
| NoBenchMark String
|
NoLibraryFound
| CompilerNotInstalled CompilerFlavor
| CantFindIncludeFile String
| UnsupportedTestSuite String
| UnsupportedBenchMark String
| NoIncludeFileFound String
| NoModuleFound ModuleName [Suffix]
| RegMultipleInstancePkg
| SuppressingChecksOnFile
| NoSupportDirStylePackageDb
| OnlySupportSpecificPackageDb
| FailedToParseOutputDescribe String PackageId
| DumpFailed String String
| FailedToParseOutputDump String
| ListFailed String
| FailedToParseOutputList String
| ProgramNotFound String
| NoSupportForHoogle
| NoSupportForQuickJumpFlag
| NoGHCVersionFromHaddock
| NoGHCVersionFromCompiler
| HaddockAndGHCVersionDoesntMatch Version Version
| MustHaveSharedLibraries
| HaddockPackageFlags [(InstalledPackageInfo, [UnitId])]
| UnknownCompilerFlavor CompilerFlavor
| FailedToDetermineTarget
| NoMultipleTargets
| REPLNotSupported
| NoSupportBuildingTestSuite TestType
| NoSupportBuildingBenchMark BenchmarkType
| BuildingNotSupportedWithCompiler
| ProvideHaskellSuiteTool String
| CannotDetermineCompilerVersion
| PkgDumpFailed
| FailedToParseOutput
| CantFindSourceModule ModuleName
| VersionMismatchJS FilePath Version FilePath Version
| VersionMismatchGHCJS FilePath Version FilePath Version
| GlobalPackageDBLimitation
| GlobalPackageDBSpecifiedFirst
| MatchDirFileGlob String
| MatchDirFileGlobErrors [String]
| ErrorParsingFileDoesntExist FilePath
| FailedParsing String
| NotFoundMsg
| UnrecognisedBuildTarget [String]
| ReportBuildTargetProblems [(String, [String], String)]
| UnknownBuildTarget [(String, [(String, String)])]
| AmbiguousBuildTarget [(String, [(String, String)])]
| CheckBuildTargets String
| VersionMismatchGHC FilePath Version FilePath Version
| CheckPackageDbStackPost76
| CheckPackageDbStackPre76
| GlobalPackageDbSpecifiedFirst
| CantInstallForeignLib
| NoSupportForPreProcessingTest TestType
| NoSupportForPreProcessingBenchmark BenchmarkType
| CantFindSourceForPreProcessFile String
| TestType
| BenchmarkType
| UnlitException String
| RunProgramInvocationException FilePath String
| GetProgramInvocationException FilePath String
| GetProgramInvocationLBSException FilePath String
| CheckSemaphoreSupport
| NoLibraryForPackage
| SanityCheckHookedBuildInfo UnqualComponentName
| ConfigureScriptNotFound FilePath
| NoValidComponent
| ConfigureEitherSingleOrAll
| ConfigCIDValidForPreComponent
| SanityCheckForEnableComponents
| SanityCheckForDynamicStaticLinking
| UnsupportedLanguages PackageIdentifier CompilerId [String]
| UnsupportedLanguageExtension PackageIdentifier CompilerId [String]
| CantFindForeignLibraries [String]
| ExpectedAbsoluteDirectory FilePath
| FlagsNotSpecified [FlagName]
| EncounteredMissingDependency [Dependency]
| CompilerDoesn'tSupportThinning
| CompilerDoesn'tSupportReexports
| CompilerDoesn'tSupportBackpack
| LibraryWithinSamePackage [PackageId]
| ReportFailedDependencies [FailedDependency] String
| NoPackageDatabaseSpecified
| HowToFindInstalledPackages CompilerFlavor
| PkgConfigNotFound String String
| BadVersion String String PkgconfigVersion
| UnknownCompilerException
| NoWorkingGcc
| NoOSSupport OS String
| NoCompilerSupport String
| InstallDirsNotPrefixRelative (InstallDirs FilePath)
| ExplainErrors (Maybe (Either [Char] [Char])) [String]
| CheckPackageProblems [String]
| LibDirDepsPrefixNotRelative FilePath FilePath
| CombinedConstraints Doc
| CantParseGHCOutput
| IncompatibleWithCabal String String
| Couldn'tFindTestProgram FilePath
| TestCoverageSupport
| Couldn'tFindTestProgLibV09 FilePath
| TestCoverageSupportLibV09
| RawSystemStdout String
| FindFile FilePath
| FindModuleFileEx ModuleName [Suffix] [FilePath]
| MultipleFilesWithExtension String
| NoDesc
| MultiDesc [String]
| RelocRegistrationInfo
| CreatePackageDB
| WithHcPkg String
| RegisMultiplePkgNotSupported
| RegisteringNotImplemented
| NoTestSuitesEnabled
| TestNameDisabled String
| NoSuchTest String
| ConfigureProgram String FilePath
| RequireProgram String
| NoProgramFound String VersionRange
| BadVersionDb String Version VersionRange FilePath
| UnknownVersionDb String VersionRange FilePath
| MissingCoveredInstalledLibrary UnitId
| SetupHooksException SetupHooksException
deriving (Int -> CabalException -> ShowS
[CabalException] -> ShowS
CabalException -> String
(Int -> CabalException -> ShowS)
-> (CabalException -> String)
-> ([CabalException] -> ShowS)
-> Show CabalException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CabalException -> ShowS
showsPrec :: Int -> CabalException -> ShowS
$cshow :: CabalException -> String
show :: CabalException -> String
$cshowList :: [CabalException] -> ShowS
showList :: [CabalException] -> ShowS
Show, Typeable)
exceptionCode :: CabalException -> Int
exceptionCode :: CabalException -> Int
exceptionCode CabalException
e = case CabalException
e of
NoBenchMarkProgram{} -> Int
1678
EnableBenchMark{} -> Int
1453
BenchMarkNameDisabled{} -> Int
2781
NoBenchMark{} -> Int
1654
CabalException
NoLibraryFound -> Int
2546
CompilerNotInstalled{} -> Int
7465
CantFindIncludeFile{} -> Int
3876
UnsupportedTestSuite{} -> Int
3245
UnsupportedBenchMark{} -> Int
9123
NoIncludeFileFound{} -> Int
2987
NoModuleFound{} -> Int
6421
RegMultipleInstancePkg{} -> Int
3421
SuppressingChecksOnFile{} -> Int
5436
CabalException
NoSupportDirStylePackageDb -> Int
2980
CabalException
OnlySupportSpecificPackageDb -> Int
6547
FailedToParseOutputDescribe{} -> Int
7218
DumpFailed{} -> Int
6736
FailedToParseOutputDump{} -> Int
9076
ListFailed{} -> Int
5109
FailedToParseOutputList{} -> Int
7650
ProgramNotFound{} -> Int
4123
NoSupportForHoogle{} -> Int
8706
NoSupportForQuickJumpFlag{} -> Int
7086
CabalException
NoGHCVersionFromHaddock -> Int
5045
CabalException
NoGHCVersionFromCompiler -> Int
4098
HaddockAndGHCVersionDoesntMatch{} -> Int
1998
MustHaveSharedLibraries{} -> Int
6032
HaddockPackageFlags{} -> Int
4569
UnknownCompilerFlavor{} -> Int
3102
FailedToDetermineTarget{} -> Int
5049
NoMultipleTargets{} -> Int
6091
REPLNotSupported{} -> Int
1098
NoSupportBuildingTestSuite{} -> Int
4106
NoSupportBuildingBenchMark{} -> Int
5320
BuildingNotSupportedWithCompiler{} -> Int
7077
ProvideHaskellSuiteTool{} -> Int
7509
CannotDetermineCompilerVersion{} -> Int
4519
PkgDumpFailed{} -> Int
2291
FailedToParseOutput{} -> Int
5500
CantFindSourceModule{} -> Int
8870
VersionMismatchJS{} -> Int
9001
VersionMismatchGHCJS{} -> Int
4001
GlobalPackageDBLimitation{} -> Int
5002
GlobalPackageDBSpecifiedFirst{} -> Int
3901
MatchDirFileGlob{} -> Int
9760
MatchDirFileGlobErrors{} -> Int
6661
ErrorParsingFileDoesntExist{} -> Int
1234
FailedParsing{} -> Int
6565
NotFoundMsg{} -> Int
8011
UnrecognisedBuildTarget{} -> Int
3410
ReportBuildTargetProblems{} -> Int
5504
UnknownBuildTarget{} -> Int
4444
AmbiguousBuildTarget{} -> Int
7865
CheckBuildTargets{} -> Int
4733
VersionMismatchGHC{} -> Int
4000
CheckPackageDbStackPost76{} -> Int
3000
CheckPackageDbStackPre76{} -> Int
5640
GlobalPackageDbSpecifiedFirst{} -> Int
2345
CantInstallForeignLib{} -> Int
8221
NoSupportForPreProcessingTest{} -> Int
3008
NoSupportForPreProcessingBenchmark{} -> Int
6990
CantFindSourceForPreProcessFile{} -> Int
7554
NoSupportPreProcessingTestExtras{} -> Int
7886
NoSupportPreProcessingBenchmarkExtras{} -> Int
9999
UnlitException{} -> Int
5454
RunProgramInvocationException{} -> Int
8012
GetProgramInvocationException{} -> Int
7300
GetProgramInvocationLBSException{} -> Int
6578
CheckSemaphoreSupport{} -> Int
2002
NoLibraryForPackage{} -> Int
8004
SanityCheckHookedBuildInfo{} -> Int
6007
ConfigureScriptNotFound{} -> Int
4567
NoValidComponent{} -> Int
5680
ConfigureEitherSingleOrAll{} -> Int
2001
ConfigCIDValidForPreComponent{} -> Int
7006
SanityCheckForEnableComponents{} -> Int
5004
SanityCheckForDynamicStaticLinking{} -> Int
4007
UnsupportedLanguages{} -> Int
8074
UnsupportedLanguageExtension{} -> Int
5656
CantFindForeignLibraries{} -> Int
4574
ExpectedAbsoluteDirectory{} -> Int
6662
FlagsNotSpecified{} -> Int
9080
EncounteredMissingDependency{} -> Int
8010
CompilerDoesn'tSupportThinning{} -> Int
4003
CompilerDoesn'tSupportReexports{} -> Int
3456
CompilerDoesn'tSupportBackpack{} -> Int
5446
LibraryWithinSamePackage{} -> Int
7007
ReportFailedDependencies{} -> Int
4321
NoPackageDatabaseSpecified{} -> Int
2300
HowToFindInstalledPackages{} -> Int
3003
PkgConfigNotFound{} -> Int
7123
BadVersion{} -> Int
7600
UnknownCompilerException{} -> Int
3022
NoWorkingGcc{} -> Int
1088
NoOSSupport{} -> Int
3339
NoCompilerSupport{} -> Int
2290
InstallDirsNotPrefixRelative{} -> Int
6000
ExplainErrors{} -> Int
4345
CheckPackageProblems{} -> Int
5559
LibDirDepsPrefixNotRelative{} -> Int
6667
CombinedConstraints{} -> Int
5000
CantParseGHCOutput{} -> Int
1980
IncompatibleWithCabal{} -> Int
8123
Couldn'tFindTestProgram{} -> Int
5678
TestCoverageSupport{} -> Int
7890
Couldn'tFindTestProgLibV09{} -> Int
9012
TestCoverageSupportLibV09{} -> Int
1076
RawSystemStdout{} -> Int
3098
FindFile{} -> Int
2115
FindModuleFileEx{} -> Int
6663
MultipleFilesWithExtension{} -> Int
3333
NoDesc{} -> Int
7654
MultiDesc{} -> Int
5554
RelocRegistrationInfo{} -> Int
4343
CreatePackageDB{} -> Int
6787
WithHcPkg{} -> Int
9876
RegisMultiplePkgNotSupported{} -> Int
7632
RegisteringNotImplemented{} -> Int
5411
NoTestSuitesEnabled{} -> Int
9061
TestNameDisabled{} -> Int
8210
NoSuchTest{} -> Int
8000
ConfigureProgram{} -> Int
5490
RequireProgram{} -> Int
6666
NoProgramFound{} -> Int
7620
BadVersionDb{} -> Int
8038
UnknownVersionDb{} -> Int
1008
MissingCoveredInstalledLibrary{} -> Int
9341
SetupHooksException SetupHooksException
err ->
SetupHooksException -> Int
setupHooksExceptionCode SetupHooksException
err
versionRequirement :: VersionRange -> String
versionRequirement :: VersionRange -> String
versionRequirement VersionRange
range
| VersionRange -> Bool
isAnyVersion VersionRange
range = String
""
| Bool
otherwise = String
" version " String -> ShowS
forall a. [a] -> [a] -> [a]
++ VersionRange -> String
forall a. Pretty a => a -> String
prettyShow VersionRange
range
exceptionMessage :: CabalException -> String
exceptionMessage :: CabalException -> String
exceptionMessage CabalException
e = case CabalException
e of
NoBenchMarkProgram String
cmd -> String
"Could not find benchmark program \"" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
cmd String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\". Did you build the package first?"
CabalException
EnableBenchMark -> String
"No benchmarks enabled. Did you remember to \'Setup configure\' with " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\'--enable-benchmarks\'?"
BenchMarkNameDisabled String
bmName -> String
"Package configured with benchmark " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
bmName String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" disabled."
NoBenchMark String
bmName -> String
"no such benchmark: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
bmName
CabalException
NoLibraryFound -> String
"No executables and no library found. Nothing to do."
CompilerNotInstalled CompilerFlavor
compilerFlavor -> String
"installing with " String -> ShowS
forall a. [a] -> [a] -> [a]
++ CompilerFlavor -> String
forall a. Pretty a => a -> String
prettyShow CompilerFlavor
compilerFlavor String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"is not implemented"
CantFindIncludeFile String
file -> String
"can't find include file " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
file
UnsupportedTestSuite String
test_type -> String
"Unsupported test suite type: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
test_type
UnsupportedBenchMark String
benchMarkType -> String
"Unsupported benchmark type: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
benchMarkType
NoIncludeFileFound String
f -> String
"can't find include file " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
f
NoModuleFound ModuleName
m [Suffix]
suffixes ->
String
"Could not find module: "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ ModuleName -> String
forall a. Pretty a => a -> String
prettyShow ModuleName
m
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" with any suffix: "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ [String] -> String
forall a. Show a => a -> String
show ((Suffix -> String) -> [Suffix] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Suffix -> String
forall a. Pretty a => a -> String
prettyShow [Suffix]
suffixes)
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
".\n"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"If the module "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"is autogenerated it should be added to 'autogen-modules'."
CabalException
RegMultipleInstancePkg -> String
"HcPkg.register: the compiler does not support registering multiple instances of packages."
CabalException
SuppressingChecksOnFile -> String
"HcPkg.register: the compiler does not support suppressing checks on files."
CabalException
NoSupportDirStylePackageDb -> String
"HcPkg.writeRegistrationFileDirectly: compiler does not support dir style package dbs"
CabalException
OnlySupportSpecificPackageDb -> String
"HcPkg.writeRegistrationFileDirectly: only supports SpecificPackageDB for now"
FailedToParseOutputDescribe String
programId PackageId
pkgId -> String
"failed to parse output of '" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
programId String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" describe " String -> ShowS
forall a. [a] -> [a] -> [a]
++ PackageId -> String
forall a. Pretty a => a -> String
prettyShow PackageId
pkgId String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"'"
DumpFailed String
programId String
exception -> String
programId String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" dump failed: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
exception
FailedToParseOutputDump String
programId -> String
"failed to parse output of '" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
programId String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" dump'"
ListFailed String
programId -> String
programId String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" list failed"
FailedToParseOutputList String
programId -> String
"failed to parse output of '" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
programId String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" list'"
ProgramNotFound String
progName -> String
"The program '" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
progName String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"' is required but it could not be found"
CabalException
NoSupportForHoogle -> String
"Haddock 2.0 and 2.1 do not support the --hoogle flag."
CabalException
NoSupportForQuickJumpFlag -> String
"Haddock prior to 2.19 does not support the --quickjump flag."
CabalException
NoGHCVersionFromHaddock -> String
"Could not get GHC version from Haddock"
CabalException
NoGHCVersionFromCompiler -> String
"Could not get GHC version from compiler"
HaddockAndGHCVersionDoesntMatch Version
ghcVersion Version
haddockGhcVersion ->
String
"Haddock's internal GHC version must match the configured "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"GHC version.\n"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"The GHC version is "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ Version -> String
forall a. Pretty a => a -> String
prettyShow Version
ghcVersion
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" but "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"haddock is using GHC version "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ Version -> String
forall a. Pretty a => a -> String
prettyShow Version
haddockGhcVersion
CabalException
MustHaveSharedLibraries -> String
"Must have vanilla or shared libraries enabled in order to run haddock"
HaddockPackageFlags [(InstalledPackageInfo, [UnitId])]
inf ->
String
"internal error when calculating transitive "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"package dependencies.\nDebug info: "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ [(InstalledPackageInfo, [UnitId])] -> String
forall a. Show a => a -> String
show [(InstalledPackageInfo, [UnitId])]
inf
UnknownCompilerFlavor CompilerFlavor
compilerFlavor -> String
"dumpBuildInfo: Unknown compiler flavor: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ CompilerFlavor -> String
forall a. Show a => a -> String
show CompilerFlavor
compilerFlavor
CabalException
FailedToDetermineTarget -> String
"Failed to determine target."
CabalException
NoMultipleTargets -> String
"The 'repl' command does not support multiple targets at once."
CabalException
REPLNotSupported -> String
"A REPL is not supported with this compiler."
NoSupportBuildingTestSuite TestType
test_type -> String
"No support for building test suite type " String -> ShowS
forall a. [a] -> [a] -> [a]
++ TestType -> String
forall a. Show a => a -> String
show TestType
test_type
NoSupportBuildingBenchMark BenchmarkType
benchMarkType -> String
"No support for building benchmark type " String -> ShowS
forall a. [a] -> [a] -> [a]
++ BenchmarkType -> String
forall a. Show a => a -> String
show BenchmarkType
benchMarkType
CabalException
BuildingNotSupportedWithCompiler -> String
"Building is not supported with this compiler."
ProvideHaskellSuiteTool String
msg -> ShowS
forall a. Show a => a -> String
show String
msg
CabalException
CannotDetermineCompilerVersion -> String
"haskell-suite: couldn't determine compiler version"
CabalException
PkgDumpFailed -> String
"pkg dump failed"
CabalException
FailedToParseOutput -> String
"failed to parse output of 'pkg dump'"
CantFindSourceModule ModuleName
moduleName -> String
"can't find source for module " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ModuleName -> String
forall a. Pretty a => a -> String
prettyShow ModuleName
moduleName
VersionMismatchJS String
ghcjsProgPath Version
ghcjsVersion String
ghcjsPkgProgPath Version
ghcjsPkgGhcjsVersion ->
String
"Version mismatch between ghcjs and ghcjs-pkg: "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show String
ghcjsProgPath
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" is version "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ Version -> String
forall a. Pretty a => a -> String
prettyShow Version
ghcjsVersion
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show String
ghcjsPkgProgPath
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" is version "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ Version -> String
forall a. Pretty a => a -> String
prettyShow Version
ghcjsPkgGhcjsVersion
VersionMismatchGHCJS String
ghcjsProgPath Version
ghcjsGhcVersion String
ghcjsPkgProgPath Version
ghcjsPkgVersion ->
String
"Version mismatch between ghcjs and ghcjs-pkg: "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show String
ghcjsProgPath
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" was built with GHC version "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ Version -> String
forall a. Pretty a => a -> String
prettyShow Version
ghcjsGhcVersion
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show String
ghcjsPkgProgPath
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" was built with GHC version "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ Version -> String
forall a. Pretty a => a -> String
prettyShow Version
ghcjsPkgVersion
CabalException
GlobalPackageDBLimitation ->
String
"With current ghc versions the global package db is always used "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"and must be listed first. This ghc limitation may be lifted in "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"the future, see https://gitlab.haskell.org/ghc/ghc/-/issues/5977"
CabalException
GlobalPackageDBSpecifiedFirst ->
String
"If the global package db is specified, it must be "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"specified first and cannot be specified multiple times"
MatchDirFileGlob String
pathError -> String
pathError
MatchDirFileGlobErrors [String]
errors -> [String] -> String
unlines [String]
errors
ErrorParsingFileDoesntExist String
filePath -> String
"Error Parsing: file \"" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
filePath String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\" doesn't exist. Cannot continue."
FailedParsing String
name -> String
"Failed parsing \"" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
name String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\"."
CabalException
NotFoundMsg ->
String
"The package has a './configure' script. "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"If you are on Windows, This requires a "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"Unix compatibility toolchain such as MinGW+MSYS or Cygwin. "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"If you are not on Windows, ensure that an 'sh' command "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"is discoverable in your path."
UnrecognisedBuildTarget [String]
target ->
[String] -> String
unlines
[ String
"Unrecognised build target '" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
name String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"'."
| String
name <- [String]
target
]
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"Examples:\n"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" - build foo -- component name "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"(library, executable, test-suite or benchmark)\n"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" - build Data.Foo -- module name\n"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" - build Data/Foo.hsc -- file name\n"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" - build lib:foo exe:foo -- component qualified by kind\n"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" - build foo:Data.Foo -- module qualified by component\n"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" - build foo:Data/Foo.hsc -- file qualified by component"
ReportBuildTargetProblems [(String, [String], String)]
targets ->
[String] -> String
unlines
[ String
"Unrecognised build target '"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
target
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"'.\n"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"Expected a "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
" or " [String]
expected
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
", rather than '"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
got
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"'."
| (String
target, [String]
expected, String
got) <- [(String, [String], String)]
targets
]
UnknownBuildTarget [(String, [(String, String)])]
targets ->
[String] -> String
unlines
[ String
"Unknown build target '"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
target
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"'.\nThere is no "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate
String
" or "
[ ShowS
mungeThing String
thing String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" '" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
got String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"'"
| (String
thing, String
got) <- [(String, String)]
nosuch
]
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"."
| (String
target, [(String, String)]
nosuch) <- [(String, [(String, String)])]
targets
]
where
mungeThing :: ShowS
mungeThing String
"file" = String
"file target"
mungeThing String
thing = String
thing
AmbiguousBuildTarget [(String, [(String, String)])]
targets ->
[String] -> String
unlines
[ String
"Ambiguous build target '"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
target
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"'. It could be:\n "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ [String] -> String
unlines
[ String
" "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
ut
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" ("
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
bt
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"
| (String
ut, String
bt) <- [(String, String)]
amb
]
| (String
target, [(String, String)]
amb) <- [(String, [(String, String)])]
targets
]
CheckBuildTargets String
errorStr -> String
errorStr
VersionMismatchGHC String
ghcProgPath Version
ghcVersion String
ghcPkgProgPath Version
ghcPkgVersion ->
String
"Version mismatch between ghc and ghc-pkg: "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
ghcProgPath
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" is version "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ Version -> String
forall a. Pretty a => a -> String
prettyShow Version
ghcVersion
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
ghcPkgProgPath
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" is version "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ Version -> String
forall a. Pretty a => a -> String
prettyShow Version
ghcPkgVersion
CabalException
CheckPackageDbStackPost76 ->
String
"If the global package db is specified, it must be "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"specified first and cannot be specified multiple times"
CabalException
CheckPackageDbStackPre76 ->
String
"With current ghc versions the global package db is always used "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"and must be listed first. This ghc limitation is lifted in GHC 7.6,"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"see https://gitlab.haskell.org/ghc/ghc/-/issues/5977"
CabalException
GlobalPackageDbSpecifiedFirst ->
String
"If the global package db is specified, it must be "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"specified first and cannot be specified multiple times"
CabalException
CantInstallForeignLib -> String
"Can't install foreign-library symlink on non-Linux OS"
NoSupportForPreProcessingTest TestType
tt ->
String
"No support for preprocessing test "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"suite type "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ TestType -> String
forall a. Pretty a => a -> String
prettyShow TestType
tt
NoSupportForPreProcessingBenchmark BenchmarkType
tt ->
String
"No support for preprocessing benchmark type "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ BenchmarkType -> String
forall a. Pretty a => a -> String
prettyShow BenchmarkType
tt
CantFindSourceForPreProcessFile String
errorStr -> String
errorStr
NoSupportPreProcessingTestExtras TestType
tt ->
String
"No support for preprocessing test suite type "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ TestType -> String
forall a. Pretty a => a -> String
prettyShow TestType
tt
NoSupportPreProcessingBenchmarkExtras BenchmarkType
tt ->
String
"No support for preprocessing benchmark "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"type "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ BenchmarkType -> String
forall a. Pretty a => a -> String
prettyShow BenchmarkType
tt
UnlitException String
str -> String
str
RunProgramInvocationException String
path String
errors -> String
"'" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
path String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"' exited with an error:\n" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
errors
GetProgramInvocationException String
path String
errors -> String
"'" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
path String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"' exited with an error:\n" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
errors
GetProgramInvocationLBSException String
path String
errors -> String
"'" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
path String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"' exited with an error:\n" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
errors
CabalException
CheckSemaphoreSupport ->
String
"Your compiler does not support the -jsem flag. "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"To use this feature you must use GHC 9.8 or later."
CabalException
NoLibraryForPackage ->
String
"The buildinfo contains info for a library, "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"but the package does not have a library."
SanityCheckHookedBuildInfo UnqualComponentName
exe1 ->
String
"The buildinfo contains info for an executable called '"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ UnqualComponentName -> String
forall a. Pretty a => a -> String
prettyShow UnqualComponentName
exe1
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"' but the package does not have an "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"executable with that name."
ConfigureScriptNotFound String
fp -> String
"configure script not found at " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
fp String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"."
CabalException
NoValidComponent -> String
"No valid component targets found"
CabalException
ConfigureEitherSingleOrAll -> String
"Can only configure either a single component or all of them"
CabalException
ConfigCIDValidForPreComponent -> String
"--cid is only supported for per-component configure"
CabalException
SanityCheckForEnableComponents ->
String
"--enable-tests/--enable-benchmarks are incompatible with"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" explicitly specifying a component to configure."
CabalException
SanityCheckForDynamicStaticLinking ->
String
"--enable-executable-dynamic and --enable-executable-static"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" are incompatible with each other."
UnsupportedLanguages PackageId
pkgId CompilerId
compilerId [String]
langs ->
String
"The package "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ PackageId -> String
forall a. Pretty a => a -> String
prettyShow PackageId
pkgId
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" requires the following languages which are not "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"supported by "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ CompilerId -> String
forall a. Pretty a => a -> String
prettyShow CompilerId
compilerId
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
": "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " [String]
langs
UnsupportedLanguageExtension PackageId
pkgId CompilerId
compilerId [String]
exts ->
String
"The package "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ PackageId -> String
forall a. Pretty a => a -> String
prettyShow PackageId
pkgId
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" requires the following language extensions which are not "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"supported by "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ CompilerId -> String
forall a. Pretty a => a -> String
prettyShow CompilerId
compilerId
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
": "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " [String]
exts
CantFindForeignLibraries [String]
unsupportedFLibs ->
String
"Cannot build some foreign libraries: "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " [String]
unsupportedFLibs
ExpectedAbsoluteDirectory String
fPath -> String
"expected an absolute directory name for --prefix: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
fPath
FlagsNotSpecified [FlagName]
diffFlags ->
String
"'--exact-configuration' was given, "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"but the following flags were not specified: "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " ((FlagName -> String) -> [FlagName] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map FlagName -> String
forall a. Show a => a -> String
show [FlagName]
diffFlags)
EncounteredMissingDependency [Dependency]
missing ->
String
"Encountered missing or private dependencies:\n"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ ( Doc -> String
render
(Doc -> String) -> ([Dependency] -> Doc) -> [Dependency] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Doc -> Doc
nest Int
4
(Doc -> Doc) -> ([Dependency] -> Doc) -> [Dependency] -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Doc] -> Doc
sep
([Doc] -> Doc) -> ([Dependency] -> [Doc]) -> [Dependency] -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc -> [Doc] -> [Doc]
punctuate Doc
comma
([Doc] -> [Doc])
-> ([Dependency] -> [Doc]) -> [Dependency] -> [Doc]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Dependency -> Doc) -> [Dependency] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Dependency -> Doc
forall a. Pretty a => a -> Doc
pretty (Dependency -> Doc)
-> (Dependency -> Dependency) -> Dependency -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dependency -> Dependency
simplifyDependency)
([Dependency] -> String) -> [Dependency] -> String
forall a b. (a -> b) -> a -> b
$ [Dependency]
missing
)
CabalException
CompilerDoesn'tSupportThinning ->
String
"Your compiler does not support thinning and renaming on "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"package flags. To use this feature you must use "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"GHC 7.9 or later."
CabalException
CompilerDoesn'tSupportReexports ->
String
"Your compiler does not support module re-exports. To use "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"this feature you must use GHC 7.9 or later."
CabalException
CompilerDoesn'tSupportBackpack ->
String
"Your compiler does not support Backpack. To use "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"this feature you must use GHC 8.1 or later."
LibraryWithinSamePackage [PackageId]
internalPkgDeps ->
String
"The field 'build-depends: "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " ((PackageId -> String) -> [PackageId] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (PackageName -> String
forall a. Pretty a => a -> String
prettyShow (PackageName -> String)
-> (PackageId -> PackageName) -> PackageId -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageId -> PackageName
forall pkg. Package pkg => pkg -> PackageName
packageName) [PackageId]
internalPkgDeps)
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"' refers to a library which is defined within the same "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"package. To use this feature the package must specify at "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"least 'cabal-version: >= 1.8'."
ReportFailedDependencies [FailedDependency]
failed String
hackageUrl -> String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n\n" ((FailedDependency -> String) -> [FailedDependency] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map FailedDependency -> String
reportFailedDependency [FailedDependency]
failed)
where
reportFailedDependency :: FailedDependency -> String
reportFailedDependency (DependencyNotExists PackageName
pkgname) =
String
"there is no version of "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ PackageName -> String
forall a. Pretty a => a -> String
prettyShow PackageName
pkgname
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" installed.\n"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"Perhaps you need to download and install it from\n"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
hackageUrl
String -> ShowS
forall a. [a] -> [a] -> [a]
++ PackageName -> String
forall a. Pretty a => a -> String
prettyShow PackageName
pkgname
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"?"
reportFailedDependency (DependencyMissingInternal PackageName
pkgname LibraryName
lib) =
String
"internal dependency "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ Doc -> String
forall a. Pretty a => a -> String
prettyShow (LibraryName -> Doc
prettyLibraryNameComponent LibraryName
lib)
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" not installed.\n"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"Perhaps you need to configure and install it first?\n"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"(This library was defined by "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ PackageName -> String
forall a. Pretty a => a -> String
prettyShow PackageName
pkgname
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"
reportFailedDependency (DependencyNoVersion Dependency
dep) =
String
"cannot satisfy dependency " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Dependency -> String
forall a. Pretty a => a -> String
prettyShow (Dependency -> Dependency
simplifyDependency Dependency
dep) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\n"
CabalException
NoPackageDatabaseSpecified ->
String
"No package databases have been specified. If you use "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"--package-db=clear, you must follow it with --package-db= "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"with 'global', 'user' or a specific file."
HowToFindInstalledPackages CompilerFlavor
flv ->
String
"don't know how to find the installed packages for "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ CompilerFlavor -> String
forall a. Pretty a => a -> String
prettyShow CompilerFlavor
flv
PkgConfigNotFound String
pkg String
versionReq ->
String
"The pkg-config package '"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
pkg
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"'"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
versionReq
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" is required but it could not be found."
BadVersion String
pkg String
versionReq PkgconfigVersion
v ->
String
"The pkg-config package '"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
pkg
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"'"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
versionReq
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" is required but the version installed on the"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" system is version "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ PkgconfigVersion -> String
forall a. Pretty a => a -> String
prettyShow PkgconfigVersion
v
CabalException
UnknownCompilerException -> String
"Unknown compiler"
CabalException
NoWorkingGcc ->
[String] -> String
unlines
[ String
"No working gcc"
, String
"This package depends on a foreign library but we cannot "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"find a working C compiler. If you have it in a "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"non-standard location you can use the --with-gcc "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"flag to specify it."
]
NoOSSupport OS
os String
what ->
String
"Operating system: "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ OS -> String
forall a. Pretty a => a -> String
prettyShow OS
os
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
", does not support "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
what
NoCompilerSupport String
comp ->
String
"Compiler: "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
comp
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
", does not support relocatable builds"
InstallDirsNotPrefixRelative InstallDirs String
installDirs -> String
"Installation directories are not prefix_relative:\n" String -> ShowS
forall a. [a] -> [a] -> [a]
++ InstallDirs String -> String
forall a. Show a => a -> String
show InstallDirs String
installDirs
ExplainErrors Maybe (Either String String)
hdr [String]
libs ->
[String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$
[ if Bool
plural
then String
"Missing dependencies on foreign libraries:"
else String
"Missing dependency on a foreign library:"
| Bool
missing
]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ case Maybe (Either String String)
hdr of
Just (Left String
h) -> [String
"* Missing (or bad) header file: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
h]
Maybe (Either String String)
_ -> []
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ case [String]
libs of
[] -> []
[String
lib] -> [String
"* Missing (or bad) C library: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
lib]
[String]
_ ->
[ String
"* Missing (or bad) C libraries: "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " [String]
libs
]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [if Bool
plural then String
messagePlural else String
messageSingular | Bool
missing]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ case Maybe (Either String String)
hdr of
Just (Left String
_) -> [String
headerCppMessage]
Just (Right String
h) ->
[ (if Bool
missing then String
"* " else String
"")
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"Bad header file: "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
h
, String
headerCcMessage
]
Maybe (Either String String)
_ -> []
where
plural :: Bool
plural = [String] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
libs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
2
missing :: Bool
missing =
Bool -> Bool
not ([String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
libs)
Bool -> Bool -> Bool
|| case Maybe (Either String String)
hdr of Just (Left String
_) -> Bool
True; Maybe (Either String String)
_ -> Bool
False
messageSingular :: String
messageSingular =
String
"This problem can usually be solved by installing the system "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"package that provides this library (you may need the "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\"-dev\" version). If the library is already installed "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"but in a non-standard location then you can use the flags "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"--extra-include-dirs= and --extra-lib-dirs= to specify "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"where it is."
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"If the library file does exist, it may contain errors that "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"are caught by the C compiler at the preprocessing stage. "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"In this case you can re-run 'Setup configure' with the "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"verbosity flag -v3 to see the error messages."
messagePlural :: String
messagePlural =
String
"This problem can usually be solved by installing the system "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"packages that provide these libraries (you may need the "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\"-dev\" versions). If the libraries are already installed "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"but in a non-standard location then you can use the flags "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"--extra-include-dirs= and --extra-lib-dirs= to specify "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"where they are."
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"If the library files do exist, it may contain errors that "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"are caught by the C compiler at the preprocessing stage. "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"In this case you can re-run 'Setup configure' with the "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"verbosity flag -v3 to see the error messages."
headerCppMessage :: String
headerCppMessage =
String
"If the header file does exist, it may contain errors that "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"are caught by the C compiler at the preprocessing stage. "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"In this case you can re-run 'Setup configure' with the "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"verbosity flag -v3 to see the error messages."
headerCcMessage :: String
headerCcMessage =
String
"The header file contains a compile error. "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"You can re-run 'Setup configure' with the verbosity flag "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"-v3 to see the error messages from the C compiler."
CheckPackageProblems [String]
errors -> String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n\n" [String]
errors
LibDirDepsPrefixNotRelative String
l String
p ->
String
"Library directory of a dependency: "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show String
l
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\nis not relative to the installation prefix:\n"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show String
p
CombinedConstraints Doc
dispDepend ->
Doc -> String
render (Doc -> String) -> Doc -> String
forall a b. (a -> b) -> a -> b
$
String -> Doc
text String
"The following package dependencies were requested"
Doc -> Doc -> Doc
$+$ Int -> Doc -> Doc
nest Int
4 Doc
dispDepend
Doc -> Doc -> Doc
$+$ String -> Doc
text String
"however the given installed package instance does not exist."
CabalException
CantParseGHCOutput -> String
"Can't parse --info output of GHC"
IncompatibleWithCabal String
compilerName String
packagePathEnvVar ->
String
"Use of "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
compilerName
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"'s environment variable "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
packagePathEnvVar
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" is incompatible with Cabal. Use the "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"flag --package-db to specify a package database (it can be "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"used multiple times)."
Couldn'tFindTestProgram String
cmd ->
String
"Could not find test program \""
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
cmd
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\". Did you build the package first?"
CabalException
TestCoverageSupport -> String
"Test coverage is only supported for packages with a library component."
Couldn'tFindTestProgLibV09 String
cmd ->
String
"Could not find test program \""
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
cmd
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\". Did you build the package first?"
CabalException
TestCoverageSupportLibV09 -> String
"Test coverage is only supported for packages with a library component."
RawSystemStdout String
errors -> String
errors
FindFile String
fileName -> String
fileName String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" doesn't exist"
FindModuleFileEx ModuleName
mod_name [Suffix]
extensions [String]
searchPath ->
String
"Could not find module: "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ ModuleName -> String
forall a. Pretty a => a -> String
prettyShow ModuleName
mod_name
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" with any suffix: "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ [String] -> String
forall a. Show a => a -> String
show ((Suffix -> String) -> [Suffix] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Suffix -> String
forall a. Pretty a => a -> String
prettyShow [Suffix]
extensions)
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" in the search path: "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ [String] -> String
forall a. Show a => a -> String
show [String]
searchPath
MultipleFilesWithExtension String
buildInfoExt -> String
"Multiple files with extension " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
buildInfoExt
CabalException
NoDesc ->
String
"No cabal file found.\n"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"Please create a package description file <pkgname>.cabal"
MultiDesc [String]
l ->
String
"Multiple cabal files found.\n"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"Please use only one of: "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " [String]
l
CabalException
RelocRegistrationInfo ->
String
"Distribution.Simple.Register.relocRegistrationInfo: \
\not implemented for this compiler"
CabalException
CreatePackageDB ->
String
"Distribution.Simple.Register.createPackageDB: "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"not implemented for this compiler"
WithHcPkg String
name ->
String
"Distribution.Simple.Register."
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
name
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
":\
\not implemented for this compiler"
CabalException
RegisMultiplePkgNotSupported -> String
"Registering multiple package instances is not yet supported for this compiler"
CabalException
RegisteringNotImplemented -> String
"Registering is not implemented for this compiler"
CabalException
NoTestSuitesEnabled ->
String
"No test suites enabled. Did you remember to 'Setup configure' with "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\'--enable-tests\'?"
TestNameDisabled String
tName ->
String
"Package configured with test suite "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
tName
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" disabled."
NoSuchTest String
tName -> String
"no such test: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
tName
ConfigureProgram String
name String
path ->
String
"Cannot find the program '"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
name
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"'. User-specified path '"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
path
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"' does not refer to an executable and "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"the program is not on the system path."
RequireProgram String
progName -> String
"The program '" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
progName String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"' is required but it could not be found."
NoProgramFound String
progName VersionRange
versionRange ->
String
"The program '"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
progName
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"'"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ VersionRange -> String
versionRequirement VersionRange
versionRange
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" is required but it could not be found."
BadVersionDb String
progName Version
version VersionRange
range String
locationPath ->
String
"The program '"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
progName
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"'"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ VersionRange -> String
versionRequirement VersionRange
range
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" is required but the version found at "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
locationPath
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" is version "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ Version -> String
forall a. Pretty a => a -> String
prettyShow Version
version
UnknownVersionDb String
progName VersionRange
versionRange String
locationPath ->
String
"The program '"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
progName
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"'"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ VersionRange -> String
versionRequirement VersionRange
versionRange
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" is required but the version of "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
locationPath
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" could not be determined."
MissingCoveredInstalledLibrary UnitId
unitId ->
String
"Failed to find the installed unit '"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ UnitId -> String
forall a. Pretty a => a -> String
prettyShow UnitId
unitId
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"' in package database stack."
SetupHooksException SetupHooksException
err ->
SetupHooksException -> String
setupHooksExceptionMessage SetupHooksException
err