Regen cabal help after #9583
[cabal.git] / cabal-install / src / Distribution / Client / Errors.hs
blobd25c59af41e7de244c47648b111a19bc24924790
1 {-# LANGUAGE ConstraintKinds #-}
2 {-# LANGUAGE DeriveGeneric #-}
3 {-# LANGUAGE FlexibleInstances #-}
4 {-# LANGUAGE InstanceSigs #-}
5 {-# LANGUAGE NamedFieldPuns #-}
6 {-# OPTIONS_GHC -fno-warn-incomplete-uni-patterns #-}
8 -----------------------------------------------------------------------------
10 -- Module : Distribution.Client.Errors
11 -- Copyright : Suganya Arun
12 -- License : BSD3
13 -- Maintainer : cabal-devel@haskell.org
14 -- Portability : portable
16 -- A collection of Exception Types in the Cabal-Install library package
18 module Distribution.Client.Errors
19 ( CabalInstallException (..)
20 , exceptionCodeCabalInstall
21 , exceptionMessageCabalInstall
22 ) where
24 import Data.ByteString (ByteString)
25 import qualified Data.ByteString.Base16 as Base16
26 import qualified Data.ByteString.Char8 as BS8
27 import Data.List (groupBy)
28 import Distribution.Client.IndexUtils.Timestamp
29 import Distribution.Client.Types.Repo
30 import Distribution.Client.Types.RepoName (RepoName (..))
31 import Distribution.Compat.Prelude
32 import Distribution.Deprecated.ParseUtils (PWarning, showPWarning)
33 import Distribution.Package
34 import Distribution.Pretty
35 import Distribution.Simple (VersionRange)
36 import Distribution.Simple.Utils
37 import Network.URI
38 import Text.Regex.Posix.ByteString (WrapError)
40 data CabalInstallException
41 = UnpackGet
42 | NotTarballDir FilePath
43 | DirectoryAlreadyExists FilePath
44 | FileExists FilePath
45 | FileAlreadyExists FilePath
46 | DirectoryExists FilePath
47 | SplitRunArgs String
48 | CouldNotFindExecutable
49 | FoundMultipleMatchingExes
50 | NoRemoteRepositories
51 | NotATarDotGzFile FilePath
52 | ExpectedMatchingFileName
53 | NoTargetProvided
54 | OneTargetRequired
55 | ThisIsABug
56 | NoOrMultipleTargetsGiven
57 | NoTargetFound
58 | MultipleTargetsFound
59 | UnexpectedNamedPkgSpecifiers
60 | UnexpectedSourcePkgSpecifiers
61 | UnableToPerformInplaceUpdate
62 | EmptyValuePagerEnvVariable
63 | FileDoesntExist FilePath
64 | ParseError
65 | CabalFileNotFound FilePath
66 | FindOpenProgramLocationErr String
67 | PkgConfParseFailed String
68 | ErrorPackingSdist String
69 | SdistException PackageIdentifier
70 | SpecifyAnExecutable
71 | TestCommandDoesn'tSupport
72 | ReportTargetProblems String
73 | ListBinTargetException String
74 | ResolveWithoutDependency String
75 | CannotReadCabalFile FilePath
76 | ErrorUpdatingIndex FilePath IOException
77 | InternalError FilePath
78 | ReadIndexCache FilePath
79 | ConfigStateFileException String
80 | UploadAction
81 | UploadActionDocumentation
82 | UploadActionOnlyArchives [FilePath]
83 | FileNotFound FilePath
84 | CheckAction [String]
85 | ReportAction [String]
86 | InitAction
87 | UserConfigAction FilePath
88 | SpecifySubcommand
89 | UnknownUserConfigSubcommand [String]
90 | ManpageAction [String]
91 | UnrecognizedResponse
92 | CheckTarget
93 | FetchPackage
94 | PlanPackages String
95 | NoSupportForRunCommand
96 | RunPhaseReached
97 | UnknownExecutable String UnitId
98 | MultipleMatchingExecutables String [String]
99 | CmdRunReportTargetProblems String
100 | CleanAction [String]
101 | ReportCannotPruneDependencies String
102 | ReplCommandDoesn'tSupport
103 | ReplTakesNoArguments [String]
104 | ReplTakesSingleArgument [String]
105 | RenderReplTargetProblem [String]
106 | GetPkgList String WrapError
107 | GatherPkgInfo PackageName VersionRange
108 | UnableToParseRepo String
109 | NullUnknownrepos [String] [String]
110 | UpdateSetupScript
111 | InstalledCabalVersion PackageName VersionRange
112 | FailNoConfigFile String
113 | ParseFailedErr FilePath String String
114 | ParseExtraLinesFailedErr String String
115 | ParseExtraLinesOkError [PWarning]
116 | FetchPackageErr
117 | ReportParseResult String FilePath String String
118 | ReportSourceRepoProblems String
119 | BenchActionException
120 | RenderBenchTargetProblem [String]
121 | ReportUserTargetProblems [String]
122 | ReportUserTargerNonexistantFile [String]
123 | ReportUserTargetUnexpectedFile [String]
124 | ReportUserTargetUnexpectedUriScheme [String]
125 | ReportUserTargetUnrecognisedUri [String]
126 | ReadTarballPackageTarget FilePath FilePath
127 | ReportPackageTargetProblems [PackageName]
128 | PackageNameAmbiguousErr [(PackageName, [PackageName])]
129 | ExtractTarballPackageErr String
130 | OutdatedAction
131 | FreezeFileExistsErr FilePath
132 | FinalizePDFailed
133 | ProjectTargetSelector String String
134 | PhaseRunSolverErr String
135 | HaddockCommandDoesn'tSupport
136 | CannotParseURIFragment String String
137 | MakeDownload URI ByteString ByteString
138 | FailedToDownloadURI URI String
139 | RemoteRepoCheckHttps String String
140 | TransportCheckHttps URI String
141 | NoPostYet
142 | WGetServerError FilePath String
143 | Couldn'tEstablishHttpConnection
144 | StatusParseFail URI String
145 | TryUpgradeToHttps [String]
146 | UnknownHttpTransportSpecified String [String]
147 | CmdHaddockReportTargetProblems [String]
148 | FailedExtractingScriptBlock String
149 | FreezeAction [String]
150 | TryFindPackageDescErr String
151 | DieIfNotHaddockFailureException String
152 | ConfigureInstallInternalError
153 | CmdErrorMessages [String]
154 | ReportTargetSelectorProblems [String]
155 | UnrecognisedTarget [(String, [String], String)]
156 | NoSuchTargetSelectorErr [(String, [(Maybe (String, String), String, String, [String])])]
157 | TargetSelectorAmbiguousErr [(String, [(String, String)])]
158 | TargetSelectorNoCurrentPackageErr String
159 | TargetSelectorNoTargetsInCwdTrue
160 | TargetSelectorNoTargetsInCwdFalse
161 | TargetSelectorNoTargetsInProjectErr
162 | TargetSelectorNoScriptErr String
163 | MatchingInternalErrorErr String String String [(String, [String])]
164 | ReportPlanningFailure String
165 | Can'tDownloadPackagesOffline [String]
166 | SomePackagesFailedToInstall [(String, String)]
167 | PackageDotCabalFileNotFound FilePath
168 | PkgConfParsedFailed String
169 | BrokenException String
170 | WithoutProject String [String]
171 | PackagesAlreadyExistInEnvfile FilePath [String]
172 | ConfigTests
173 | ConfigBenchmarks
174 | UnknownPackage String [String]
175 | InstallUnitExes String
176 | SelectComponentTargetError String
177 | SdistActionException [String]
178 | Can'tWriteMultipleTarballs
179 | ImpossibleHappened String
180 | CannotConvertTarballPackage String
181 | Win32SelfUpgradeNotNeeded
182 | FreezeException String
183 | PkgSpecifierException [String]
184 | CorruptedIndexCache String
185 | UnusableIndexState RemoteRepo Timestamp Timestamp
186 | MissingPackageList RemoteRepo
187 | CmdPathAcceptsNoTargets
188 | CmdPathCommandDoesn'tSupportDryRun
189 deriving (Show, Typeable)
191 exceptionCodeCabalInstall :: CabalInstallException -> Int
192 exceptionCodeCabalInstall e = case e of
193 UnpackGet{} -> 7013
194 NotTarballDir{} -> 7012
195 DirectoryAlreadyExists{} -> 7014
196 FileExists{} -> 7015
197 FileAlreadyExists{} -> 7016
198 DirectoryExists{} -> 7017
199 SplitRunArgs{} -> 7018
200 CouldNotFindExecutable{} -> 7019
201 FoundMultipleMatchingExes{} -> 7020
202 NoRemoteRepositories{} -> 7021
203 NotATarDotGzFile{} -> 7022
204 ExpectedMatchingFileName{} -> 7023
205 NoTargetProvided{} -> 7024
206 OneTargetRequired{} -> 7025
207 ThisIsABug -> 7026
208 NoOrMultipleTargetsGiven{} -> 7027
209 NoTargetFound{} -> 7028
210 MultipleTargetsFound{} -> 7029
211 UnexpectedNamedPkgSpecifiers{} -> 7030
212 UnexpectedSourcePkgSpecifiers{} -> 7031
213 UnableToPerformInplaceUpdate{} -> 7032
214 EmptyValuePagerEnvVariable{} -> 7033
215 FileDoesntExist{} -> 7034
216 ParseError{} -> 7035
217 CabalFileNotFound{} -> 7036
218 FindOpenProgramLocationErr{} -> 7037
219 PkgConfParseFailed{} -> 7038
220 ErrorPackingSdist{} -> 7039
221 SdistException{} -> 7040
222 SpecifyAnExecutable{} -> 7041
223 TestCommandDoesn'tSupport{} -> 7042
224 ReportTargetProblems{} -> 7043
225 ListBinTargetException{} -> 7044
226 ResolveWithoutDependency{} -> 7045
227 CannotReadCabalFile{} -> 7046
228 ErrorUpdatingIndex{} -> 7047
229 InternalError{} -> 7048
230 ReadIndexCache{} -> 7049
231 ConfigStateFileException{} -> 7050
232 UploadAction{} -> 7051
233 UploadActionDocumentation{} -> 7052
234 UploadActionOnlyArchives{} -> 7053
235 FileNotFound{} -> 7054
236 CheckAction{} -> 7055
237 ReportAction{} -> 7056
238 InitAction{} -> 7057
239 UserConfigAction{} -> 7058
240 SpecifySubcommand{} -> 7059
241 UnknownUserConfigSubcommand{} -> 7060
242 ManpageAction{} -> 7061
243 UnrecognizedResponse{} -> 7062
244 CheckTarget{} -> 7063
245 FetchPackage{} -> 7064
246 PlanPackages{} -> 7065
247 NoSupportForRunCommand{} -> 7066
248 RunPhaseReached{} -> 7067
249 UnknownExecutable{} -> 7068
250 MultipleMatchingExecutables{} -> 7069
251 CmdRunReportTargetProblems{} -> 7070
252 CleanAction{} -> 7071
253 ReportCannotPruneDependencies{} -> 7072
254 ReplCommandDoesn'tSupport{} -> 7073
255 ReplTakesNoArguments{} -> 7074
256 ReplTakesSingleArgument{} -> 7075
257 RenderReplTargetProblem{} -> 7076
258 GetPkgList{} -> 7078
259 GatherPkgInfo{} -> 7079
260 UnableToParseRepo{} -> 7080
261 NullUnknownrepos{} -> 7081
262 UpdateSetupScript{} -> 7082
263 InstalledCabalVersion{} -> 7083
264 FailNoConfigFile{} -> 7084
265 ParseFailedErr{} -> 7085
266 ParseExtraLinesFailedErr{} -> 7087
267 ParseExtraLinesOkError{} -> 7088
268 FetchPackageErr{} -> 7089
269 ReportParseResult{} -> 7090
270 ReportSourceRepoProblems{} -> 7091
271 BenchActionException{} -> 7092
272 RenderBenchTargetProblem{} -> 7093
273 ReportUserTargetProblems{} -> 7094
274 ReportUserTargerNonexistantFile{} -> 7095
275 ReportUserTargetUnexpectedFile{} -> 7096
276 ReportUserTargetUnexpectedUriScheme{} -> 7097
277 ReportUserTargetUnrecognisedUri{} -> 7098
278 ReadTarballPackageTarget{} -> 7099
279 ReportPackageTargetProblems{} -> 7100
280 PackageNameAmbiguousErr{} -> 7101
281 ExtractTarballPackageErr{} -> 7102
282 OutdatedAction{} -> 7103
283 FreezeFileExistsErr{} -> 7104
284 FinalizePDFailed{} -> 7105
285 ProjectTargetSelector{} -> 7106
286 PhaseRunSolverErr{} -> 7107
287 HaddockCommandDoesn'tSupport{} -> 7108
288 CannotParseURIFragment{} -> 7109
289 MakeDownload{} -> 7110
290 FailedToDownloadURI{} -> 7111
291 RemoteRepoCheckHttps{} -> 7112
292 TransportCheckHttps{} -> 7113
293 NoPostYet{} -> 7114
294 WGetServerError{} -> 7115
295 Couldn'tEstablishHttpConnection{} -> 7116
296 StatusParseFail{} -> 7117
297 TryUpgradeToHttps{} -> 7118
298 UnknownHttpTransportSpecified{} -> 7119
299 CmdHaddockReportTargetProblems{} -> 7120
300 FailedExtractingScriptBlock{} -> 7121
301 FreezeAction{} -> 7122
302 TryFindPackageDescErr{} -> 7124
303 DieIfNotHaddockFailureException{} -> 7125
304 ConfigureInstallInternalError{} -> 7126
305 CmdErrorMessages{} -> 7127
306 ReportTargetSelectorProblems{} -> 7128
307 UnrecognisedTarget{} -> 7129
308 NoSuchTargetSelectorErr{} -> 7131
309 TargetSelectorAmbiguousErr{} -> 7132
310 TargetSelectorNoCurrentPackageErr{} -> 7133
311 TargetSelectorNoTargetsInCwdTrue{} -> 7134
312 TargetSelectorNoTargetsInCwdFalse{} -> 7135
313 TargetSelectorNoTargetsInProjectErr{} -> 7136
314 TargetSelectorNoScriptErr{} -> 7137
315 MatchingInternalErrorErr{} -> 7130
316 ReportPlanningFailure{} -> 7138
317 Can'tDownloadPackagesOffline{} -> 7139
318 SomePackagesFailedToInstall{} -> 7140
319 PackageDotCabalFileNotFound{} -> 7141
320 PkgConfParsedFailed{} -> 7142
321 BrokenException{} -> 7143
322 WithoutProject{} -> 7144
323 PackagesAlreadyExistInEnvfile{} -> 7145
324 ConfigTests{} -> 7146
325 ConfigBenchmarks{} -> 7147
326 UnknownPackage{} -> 7148
327 InstallUnitExes{} -> 7149
328 SelectComponentTargetError{} -> 7150
329 SdistActionException{} -> 7151
330 Can'tWriteMultipleTarballs{} -> 7152
331 ImpossibleHappened{} -> 7153
332 CannotConvertTarballPackage{} -> 7154
333 Win32SelfUpgradeNotNeeded{} -> 7155
334 FreezeException{} -> 7156
335 PkgSpecifierException{} -> 7157
336 CorruptedIndexCache{} -> 7158
337 UnusableIndexState{} -> 7159
338 MissingPackageList{} -> 7160
339 CmdPathAcceptsNoTargets{} -> 7161
340 CmdPathCommandDoesn'tSupportDryRun -> 7163
342 exceptionMessageCabalInstall :: CabalInstallException -> String
343 exceptionMessageCabalInstall e = case e of
344 UnpackGet ->
345 "The 'get' command does no yet support targets "
346 ++ "that are remote source repositories."
347 NotTarballDir t ->
348 "The 'get' command is for tarball packages. "
349 ++ "The target '"
350 ++ t
351 ++ "' is not a tarball."
352 DirectoryAlreadyExists pkgdir' -> "The directory \"" ++ pkgdir' ++ "\" already exists and is not empty, not unpacking."
353 FileExists pkgdir -> "A file \"" ++ pkgdir ++ "\" is in the way, not unpacking."
354 FileAlreadyExists pkgFile -> "The file \"" ++ pkgFile ++ "\" already exists, not overwriting."
355 DirectoryExists pkgFile -> "A directory \"" ++ pkgFile ++ "\" is in the way, not unpacking."
356 SplitRunArgs err -> err
357 CouldNotFindExecutable -> "run: Could not find executable in LocalBuildInfo"
358 FoundMultipleMatchingExes -> "run: Found multiple matching exes in LocalBuildInfo"
359 NoRemoteRepositories -> "Cannot upload. No remote repositories are configured."
360 NotATarDotGzFile paths -> "Not a tar.gz file: " ++ paths
361 ExpectedMatchingFileName -> "Expected a file name matching the pattern <pkgid>-docs.tar.gz"
362 NoTargetProvided -> "One target is required, none provided"
363 OneTargetRequired -> "One target is required, given multiple"
364 ThisIsABug ->
365 "No or multiple targets given, but the run "
366 ++ "phase has been reached. This is a bug."
367 NoOrMultipleTargetsGiven -> "No or multiple targets given..."
368 NoTargetFound -> "No target found"
369 MultipleTargetsFound -> "Multiple targets found"
370 UnexpectedNamedPkgSpecifiers ->
371 "internal error: 'resolveUserTargets' returned "
372 ++ "unexpected named package specifiers!"
373 UnexpectedSourcePkgSpecifiers ->
374 "internal error: 'resolveUserTargets' returned "
375 ++ "unexpected source package specifiers!"
376 UnableToPerformInplaceUpdate -> "local project file has conditional and/or import logic, unable to perform and automatic in-place update"
377 EmptyValuePagerEnvVariable -> "man: empty value of the PAGER environment variable"
378 FileDoesntExist fpath -> "Error Parsing: file \"" ++ fpath ++ "\" doesn't exist. Cannot continue."
379 ParseError -> "parse error"
380 CabalFileNotFound cabalFile -> "Package .cabal file not found in the tarball: " ++ cabalFile
381 FindOpenProgramLocationErr err -> err
382 PkgConfParseFailed perror ->
383 "Couldn't parse the output of 'setup register --gen-pkg-config':"
384 ++ show perror
385 ErrorPackingSdist err -> "Error packing sdist: " ++ err
386 SdistException pkgIdentifier -> "sdist of " ++ prettyShow pkgIdentifier
387 SpecifyAnExecutable -> "Please specify an executable to run"
388 TestCommandDoesn'tSupport ->
389 "The test command does not support '--only-dependencies'. "
390 ++ "You may wish to use 'build --only-dependencies' and then "
391 ++ "use 'test'."
392 ReportTargetProblems problemsMsg -> problemsMsg
393 ListBinTargetException errorStr -> errorStr
394 ResolveWithoutDependency errorStr -> errorStr
395 CannotReadCabalFile file -> "Cannot read .cabal file inside " ++ file
396 ErrorUpdatingIndex name ioe -> "Error while updating index for " ++ name ++ " repository " ++ show ioe
397 InternalError msg ->
398 "internal error when reading package index: "
399 ++ msg
400 ++ "The package index or index cache is probably "
401 ++ "corrupt. Running cabal update might fix it."
402 ReadIndexCache paths -> show (paths)
403 ConfigStateFileException err -> err
404 UploadAction -> "the 'upload' command expects at least one .tar.gz archive."
405 UploadActionDocumentation ->
406 "the 'upload' command can only upload documentation "
407 ++ "for one package at a time."
408 UploadActionOnlyArchives otherFiles ->
409 "the 'upload' command expects only .tar.gz archives: "
410 ++ intercalate ", " otherFiles
411 FileNotFound tarfile -> "file not found: " ++ tarfile
412 CheckAction extraArgs -> "'check' doesn't take any extra arguments: " ++ unwords extraArgs
413 ReportAction extraArgs -> "'report' doesn't take any extra arguments: " ++ unwords extraArgs
414 InitAction ->
415 "'init' only takes a single, optional, extra "
416 ++ "argument for the project root directory"
417 UserConfigAction paths -> paths ++ " already exists."
418 SpecifySubcommand -> "Please specify a subcommand (see 'help user-config')"
419 UnknownUserConfigSubcommand extraArgs -> "Unknown 'user-config' subcommand: " ++ unwords extraArgs
420 ManpageAction extraArgs -> "'man' doesn't take any extra arguments: " ++ unwords extraArgs
421 UnrecognizedResponse -> "unrecognized response"
422 CheckTarget ->
423 "The 'fetch' command does not yet support remote tarballs. "
424 ++ "In the meantime you can use the 'get' commands."
425 FetchPackage ->
426 "The 'fetch' command does not yet support remote "
427 ++ "source repositories."
428 PlanPackages errorStr -> errorStr
429 NoSupportForRunCommand ->
430 "The run command does not support '--only-dependencies'. "
431 ++ "You may wish to use 'build --only-dependencies' and then "
432 ++ "use 'run'."
433 RunPhaseReached ->
434 "No or multiple targets given, but the run "
435 ++ "phase has been reached. This is a bug."
436 UnknownExecutable exeName selectedUnitId ->
437 "Unknown executable "
438 ++ exeName
439 ++ " in package "
440 ++ prettyShow selectedUnitId
441 MultipleMatchingExecutables exeName elabUnitId ->
442 "Multiple matching executables found matching "
443 ++ exeName
444 ++ ":\n"
445 ++ unlines elabUnitId
446 CmdRunReportTargetProblems renderProb -> renderProb
447 CleanAction notScripts ->
448 "'clean' extra arguments should be script files: "
449 ++ unwords notScripts
450 ReportCannotPruneDependencies renderCannotPruneDependencies -> renderCannotPruneDependencies
451 ReplCommandDoesn'tSupport ->
452 "The repl command does not support '--only-dependencies'. "
453 ++ "You may wish to use 'build --only-dependencies' and then "
454 ++ "use 'repl'."
455 ReplTakesNoArguments targetStrings -> "'repl' takes no arguments or a script argument outside a project: " ++ unwords targetStrings
456 ReplTakesSingleArgument targetStrings -> "'repl' takes a single argument which should be a script: " ++ unwords targetStrings
457 RenderReplTargetProblem renderProblem -> unlines renderProblem
458 GetPkgList pat err -> "Failed to compile regex " ++ pat ++ ": " ++ snd err
459 GatherPkgInfo name verConstraint ->
460 "There is no available version of "
461 ++ prettyShow name
462 ++ " that satisfies "
463 ++ prettyShow verConstraint
464 UnableToParseRepo s -> "'v2-update' unable to parse repo: \"" ++ s ++ "\""
465 NullUnknownrepos unRepoName remoteRepoNames ->
466 "'v2-update' repo(s): \""
467 ++ intercalate "\", \"" unRepoName
468 ++ "\" can not be found in known remote repo(s): "
469 ++ intercalate ", " remoteRepoNames
470 UpdateSetupScript -> "Using 'build-type: Custom' but there is no Setup.hs or Setup.lhs script."
471 InstalledCabalVersion name verRange ->
472 "The package '"
473 ++ prettyShow name
474 ++ "' requires Cabal library version "
475 ++ prettyShow verRange
476 ++ " but no suitable version is installed."
477 FailNoConfigFile msgNotFound ->
478 unlines
479 [ msgNotFound
480 , "(Config files can be created via the cabal-command 'user-config init'.)"
482 ParseFailedErr configFile msg line ->
483 "Error parsing config file "
484 ++ configFile
485 ++ line
486 ++ ":\n"
487 ++ msg
488 ParseExtraLinesFailedErr msg line ->
489 "Error parsing additional config lines\n"
490 ++ line
491 ++ ":\n"
492 ++ msg
493 ParseExtraLinesOkError ws -> unlines (map (showPWarning "Error parsing additional config lines") ws)
494 FetchPackageErr -> "fetchPackage: source repos not supported"
495 ReportParseResult filetype filename line msg ->
496 "Error parsing "
497 ++ filetype
498 ++ " "
499 ++ filename
500 ++ line
501 ++ ":\n"
502 ++ msg
503 ReportSourceRepoProblems errorStr -> errorStr
504 BenchActionException ->
505 "The bench command does not support '--only-dependencies'. "
506 ++ "You may wish to use 'build --only-dependencies' and then "
507 ++ "use 'bench'."
508 RenderBenchTargetProblem errorStr -> unlines errorStr
509 ReportUserTargetProblems target ->
510 unlines
511 [ "Unrecognised target '" ++ name ++ "'."
512 | name <- target
514 ++ "Targets can be:\n"
515 ++ " - package names, e.g. 'pkgname', 'pkgname-1.0.1', 'pkgname < 2.0'\n"
516 ++ " - cabal files 'pkgname.cabal' or package directories 'pkgname/'\n"
517 ++ " - package tarballs 'pkgname.tar.gz' or 'http://example.com/pkgname.tar.gz'"
518 ReportUserTargerNonexistantFile target ->
519 unlines
520 [ "The file does not exist '" ++ name ++ "'."
521 | name <- target
523 ReportUserTargetUnexpectedFile target ->
524 unlines
525 [ "Unrecognised file target '" ++ name ++ "'."
526 | name <- target
528 ++ "File targets can be either package tarballs 'pkgname.tar.gz' "
529 ++ "or cabal files 'pkgname.cabal'."
530 ReportUserTargetUnexpectedUriScheme target ->
531 unlines
532 [ "URL target not supported '" ++ name ++ "'."
533 | name <- target
535 ++ "Only 'http://' and 'https://' URLs are supported."
536 ReportUserTargetUnrecognisedUri target ->
537 unlines
538 [ "Unrecognise URL target '" ++ name ++ "'."
539 | name <- target
541 ReadTarballPackageTarget filename tarballFile ->
542 "Could not parse the cabal file "
543 ++ filename
544 ++ " in "
545 ++ tarballFile
546 ReportPackageTargetProblems pkgs ->
547 unlines
548 [ "There is no package named '" ++ prettyShow name ++ "'. "
549 | name <- pkgs
551 ++ "You may need to run 'cabal update' to get the latest "
552 ++ "list of available packages."
553 PackageNameAmbiguousErr ambiguities ->
554 unlines
555 [ "There is no package named '"
556 ++ prettyShow name
557 ++ "'. "
558 ++ ( if length matches > 1
559 then "However, the following package names exist: "
560 else "However, the following package name exists: "
562 ++ intercalate ", " ["'" ++ prettyShow m ++ "'" | m <- matches]
563 ++ "."
564 | (name, matches) <- ambiguities
566 ExtractTarballPackageErr err -> err
567 OutdatedAction -> "--project-dir and --project-file must only be used with --v2-freeze-file."
568 FreezeFileExistsErr freezeFile ->
569 "Couldn't find a freeze file expected at: "
570 ++ freezeFile
571 ++ "\n\n"
572 ++ "We are looking for this file because you supplied '--project-file' or '--v2-freeze-file'. "
573 ++ "When one of these flags is given, we try to read the dependencies from a freeze file. "
574 ++ "If it is undesired behaviour, you should not use these flags, otherwise please generate "
575 ++ "a freeze file via 'cabal freeze'."
576 FinalizePDFailed -> "finalizePD failed"
577 ProjectTargetSelector input err -> "Invalid package ID: " ++ input ++ "\n" ++ err
578 PhaseRunSolverErr msg -> msg
579 HaddockCommandDoesn'tSupport -> "The haddock command does not support '--only-dependencies'."
580 CannotParseURIFragment uriFrag err -> "Cannot parse URI fragment " ++ uriFrag ++ " " ++ err
581 MakeDownload uri expected actual ->
582 unwords
583 [ "Failed to download"
584 , show uri
585 , ": SHA256 don't match; expected:"
586 , BS8.unpack (Base16.encode expected)
587 , "actual:"
588 , BS8.unpack (Base16.encode actual)
590 FailedToDownloadURI uri errCode ->
591 "failed to download "
592 ++ show uri
593 ++ " : HTTP code "
594 ++ errCode
595 RemoteRepoCheckHttps unRepoName requiresHttpsErrorMessage ->
596 "The remote repository '"
597 ++ unRepoName
598 ++ "' specifies a URL that "
599 ++ requiresHttpsErrorMessage
600 TransportCheckHttps uri requiresHttpsErrorMessage ->
601 "The URL "
602 ++ show uri
603 ++ " "
604 ++ requiresHttpsErrorMessage
605 NoPostYet -> "Posting (for report upload) is not implemented yet"
606 WGetServerError programPath resp ->
608 ++ programPath
609 ++ "' exited with an error:\n"
610 ++ resp
611 Couldn'tEstablishHttpConnection ->
612 "Couldn't establish HTTP connection. "
613 ++ "Possible cause: HTTP proxy server is down."
614 StatusParseFail uri r ->
615 "Failed to download "
616 ++ show uri
617 ++ " : "
618 ++ "No Status Code could be parsed from response: "
619 ++ r
620 TryUpgradeToHttps str ->
621 "The builtin HTTP implementation does not support HTTPS, but using "
622 ++ "HTTPS for authenticated uploads is recommended. "
623 ++ "The transport implementations with HTTPS support are "
624 ++ intercalate ", " str
625 ++ "but they require the corresponding external program to be "
626 ++ "available. You can either make one available or use plain HTTP by "
627 ++ "using the global flag --http-transport=plain-http (or putting the "
628 ++ "equivalent in the config file). With plain HTTP, your password "
629 ++ "is sent using HTTP digest authentication so it cannot be easily "
630 ++ "intercepted, but it is not as secure as using HTTPS."
631 UnknownHttpTransportSpecified name str ->
632 "Unknown HTTP transport specified: "
633 ++ name
634 ++ ". The supported transports are "
635 ++ intercalate
636 ", "
638 CmdHaddockReportTargetProblems str -> unlines str
639 FailedExtractingScriptBlock eStr -> "Failed extracting script block: " ++ eStr
640 FreezeAction extraArgs ->
641 "'freeze' doesn't take any extra arguments: "
642 ++ unwords extraArgs
643 TryFindPackageDescErr err -> err
644 DieIfNotHaddockFailureException errorStr -> errorStr
645 ConfigureInstallInternalError ->
646 "internal error: configure install plan should have exactly "
647 ++ "one local ready package."
648 CmdErrorMessages err -> unlines err
649 ReportTargetSelectorProblems targets ->
650 unlines
651 [ "Unrecognised target syntax for '" ++ name ++ "'."
652 | name <- targets
654 UnrecognisedTarget targets ->
655 unlines
656 [ "Unrecognised target '"
657 ++ target
658 ++ "'.\n"
659 ++ "Expected a "
660 ++ intercalate " or " expected
661 ++ ", rather than '"
662 ++ got
663 ++ "'."
664 | (target, expected, got) <- targets
666 NoSuchTargetSelectorErr targets ->
667 unlines
668 [ "Unknown target '"
669 ++ target
670 ++ "'.\n"
671 ++ unlines
672 [ ( case inside of
673 Just (kind, "") ->
674 "The " ++ kind ++ " has no "
675 Just (kind, thing) ->
676 "The " ++ kind ++ " " ++ thing ++ " has no "
677 Nothing -> "There is no "
679 ++ intercalate
680 " or "
681 [ mungeThing thing ++ " '" ++ got ++ "'"
682 | (thing, got, _alts) <- nosuch'
684 ++ "."
685 ++ if null alternatives
686 then ""
687 else
688 "\nPerhaps you meant "
689 ++ intercalate
690 ";\nor "
691 [ "the " ++ thing ++ " '" ++ intercalate "' or '" alts ++ "'?"
692 | (thing, alts) <- alternatives
694 | (inside, nosuch') <- groupByContainer nosuch
695 , let alternatives =
696 [ (thing, alts)
697 | (thing, _got, alts@(_ : _)) <- nosuch'
700 | (target, nosuch) <- targets
701 , let groupByContainer =
703 ( \g@((inside, _, _, _) : _) ->
704 ( inside
705 , [ (thing, got, alts)
706 | (_, thing, got, alts) <- g
710 . groupBy ((==) `on` (\(x, _, _, _) -> x))
711 . sortBy (compare `on` (\(x, _, _, _) -> x))
713 where
714 mungeThing "file" = "file target"
715 mungeThing thing = thing
716 TargetSelectorAmbiguousErr targets ->
717 unlines
718 [ "Ambiguous target '"
719 ++ target
720 ++ "'. It could be:\n "
721 ++ unlines
722 [ " "
723 ++ ut
724 ++ " ("
725 ++ bt
726 ++ ")"
727 | (ut, bt) <- amb
729 | (target, amb) <- targets
731 TargetSelectorNoCurrentPackageErr target ->
732 "The target '"
733 ++ target
734 ++ "' refers to the "
735 ++ "components in the package in the current directory, but there "
736 ++ "is no package in the current directory (or at least not listed "
737 ++ "as part of the project)."
738 TargetSelectorNoTargetsInCwdTrue ->
739 "No targets given and there is no package in the current "
740 ++ "directory. Use the target 'all' for all packages in the "
741 ++ "project or specify packages or components by name or location. "
742 ++ "See 'cabal build --help' for more details on target options."
743 TargetSelectorNoTargetsInCwdFalse ->
744 "No targets given and there is no package in the current "
745 ++ "directory. Specify packages or components by name or location. "
746 ++ "See 'cabal build --help' for more details on target options."
747 TargetSelectorNoTargetsInProjectErr ->
748 "There is no <pkgname>.cabal package file or cabal.project file. "
749 ++ "To build packages locally you need at minimum a <pkgname>.cabal "
750 ++ "file. You can use 'cabal init' to create one.\n"
751 ++ "\n"
752 ++ "For non-trivial projects you will also want a cabal.project "
753 ++ "file in the root directory of your project. This file lists the "
754 ++ "packages in your project and all other build configuration. "
755 ++ "See the Cabal user guide for full details."
756 TargetSelectorNoScriptErr target ->
757 "The script '"
758 ++ target
759 ++ "' does not exist, "
760 ++ "and only script targets may contain whitespace characters or end "
761 ++ "with ':'"
762 MatchingInternalErrorErr t s sKind renderingsAndMatches ->
763 "Internal error in target matching: could not make an "
764 ++ "unambiguous fully qualified target selector for '"
765 ++ t
766 ++ "'.\n"
767 ++ "We made the target '"
768 ++ s
769 ++ "' ("
770 ++ sKind
771 ++ ") that was expected to "
772 ++ "be unambiguous but matches the following targets:\n"
773 ++ unlines
774 [ "'"
775 ++ rendering
776 ++ "', matching:"
777 ++ concatMap
778 ("\n - " ++)
779 matches
780 | (rendering, matches) <- renderingsAndMatches
782 ++ "\nNote: Cabal expects to be able to make a single fully "
783 ++ "qualified name for a target or provide a more specific error. "
784 ++ "Our failure to do so is a bug in cabal. "
785 ++ "Tracking issue: https://github.com/haskell/cabal/issues/8684"
786 ++ "\n\nHint: this may be caused by trying to build a package that "
787 ++ "exists in the project directory but is missing from "
788 ++ "the 'packages' stanza in your cabal project file."
789 ReportPlanningFailure message -> message
790 Can'tDownloadPackagesOffline notFetched ->
791 "Can't download packages in offline mode. "
792 ++ "Must download the following packages to proceed:\n"
793 ++ intercalate ", " notFetched
794 ++ "\nTry using 'cabal fetch'."
795 SomePackagesFailedToInstall failed ->
796 unlines $
797 "Some packages failed to install:"
798 : [ pkgid ++ reason
799 | (pkgid, reason) <- failed
801 PackageDotCabalFileNotFound descFilePath -> "Package .cabal file not found: " ++ show descFilePath
802 PkgConfParsedFailed perror ->
803 "Couldn't parse the output of 'setup register --gen-pkg-config':"
804 ++ show perror
805 BrokenException errorStr -> errorStr
806 WithoutProject str1 str2 ->
807 concat $
808 [ "Unknown package \""
809 , str1
810 , "\". "
812 ++ str2
813 PackagesAlreadyExistInEnvfile envFile name ->
814 "Packages requested to install already exist in environment file at "
815 ++ envFile
816 ++ ". Overwriting them may break other packages. Use --force-reinstalls to proceed anyway. Packages: "
817 ++ intercalate ", " name
818 ConfigTests ->
819 "--enable-tests was specified, but tests can't "
820 ++ "be enabled in a remote package"
821 ConfigBenchmarks ->
822 "--enable-benchmarks was specified, but benchmarks can't "
823 ++ "be enabled in a remote package"
824 UnknownPackage hn name ->
825 concat $
826 [ "Unknown package \""
827 , hn
828 , "\". "
829 , "Did you mean any of the following?\n"
830 , unlines name
832 InstallUnitExes errorMessage -> errorMessage
833 SelectComponentTargetError render -> render
834 SdistActionException errs -> unlines errs
835 Can'tWriteMultipleTarballs -> "Can't write multiple tarballs to standard output!"
836 ImpossibleHappened pkg -> "The impossible happened: a local package isn't local" <> pkg
837 CannotConvertTarballPackage format -> "cannot convert tarball package to " ++ format
838 Win32SelfUpgradeNotNeeded -> "win32selfupgrade not needed except on win32"
839 FreezeException errs -> errs
840 PkgSpecifierException errorStr -> unlines errorStr
841 CorruptedIndexCache str -> str
842 UnusableIndexState repoRemote maxFound requested ->
843 "Latest known index-state for '"
844 ++ unRepoName (remoteRepoName repoRemote)
845 ++ "' ("
846 ++ prettyShow maxFound
847 ++ ") is older than the requested index-state ("
848 ++ prettyShow requested
849 ++ ").\nRun 'cabal update' or set the index-state to a value at or before "
850 ++ prettyShow maxFound
851 ++ "."
852 MissingPackageList repoRemote ->
853 "The package list for '"
854 ++ unRepoName (remoteRepoName repoRemote)
855 ++ "' does not exist. Run 'cabal update' to download it."
856 CmdPathAcceptsNoTargets ->
857 "The 'path' command accepts no target arguments."
858 CmdPathCommandDoesn'tSupportDryRun ->
859 "The 'path' command doesn't support the flag '--dry-run'."
861 instance Exception (VerboseException CabalInstallException) where
862 displayException :: VerboseException CabalInstallException -> [Char]
863 displayException (VerboseException stack timestamp verb cabalInstallException) =
864 withOutputMarker
865 verb
866 ( concat
867 [ "Error: [Cabal-"
868 , show (exceptionCodeCabalInstall cabalInstallException)
869 , "]\n"
872 ++ exceptionWithMetadata stack timestamp verb (exceptionMessageCabalInstall cabalInstallException)