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