Add NoImplicitPrelude to buildTypeScript
[cabal.git] / cabal-install / src / Distribution / Client / CmdErrorMessages.hs
blob8345d9ed59aea02dc47f820af7d2326652d4e05f
1 {-# LANGUAGE LambdaCase #-}
2 {-# LANGUAGE NamedFieldPuns #-}
3 {-# LANGUAGE RecordWildCards #-}
5 -- | Utilities to help format error messages for the various CLI commands.
6 module Distribution.Client.CmdErrorMessages
7 ( module Distribution.Client.CmdErrorMessages
8 , module Distribution.Client.TargetSelector
9 ) where
11 import Distribution.Client.Compat.Prelude
12 import Prelude ()
14 import Distribution.Client.ProjectPlanning
15 ( AvailableTarget (..)
16 , AvailableTargetStatus (..)
17 , CannotPruneDependencies (..)
18 , TargetRequested (..)
20 import Distribution.Client.TargetProblem
21 ( TargetProblem (..)
22 , TargetProblem'
24 import Distribution.Client.TargetSelector
25 ( ComponentKind (..)
26 , ComponentKindFilter
27 , SubComponentTarget (..)
28 , TargetSelector (..)
29 , componentKind
30 , showTargetSelector
33 import Distribution.Package
34 ( PackageId
35 , PackageName
36 , packageId
37 , packageName
39 import Distribution.Simple.Utils
40 ( dieWithException
42 import Distribution.Solver.Types.OptionalStanza
43 ( OptionalStanza (..)
45 import Distribution.Types.ComponentName
46 ( ComponentName (..)
47 , showComponentName
49 import Distribution.Types.LibraryName
50 ( LibraryName (..)
53 import qualified Data.List.NonEmpty as NE
54 import Distribution.Client.Errors
56 -----------------------
57 -- Singular or plural
60 -- | A tag used in rendering messages to distinguish singular or plural.
61 data Plural = Singular | Plural
63 -- | Used to render a singular or plural version of something
65 -- > plural (listPlural theThings) "it is" "they are"
66 plural :: Plural -> a -> a -> a
67 plural Singular si _pl = si
68 plural Plural _si pl = pl
70 -- | Singular for singleton lists and plural otherwise.
71 listPlural :: [a] -> Plural
72 listPlural [_] = Singular
73 listPlural _ = Plural
75 --------------------
76 -- Rendering lists
79 -- | Render a list of things in the style @foo, bar and baz@
80 renderListCommaAnd :: [String] -> String
81 renderListCommaAnd [] = ""
82 renderListCommaAnd [x] = x
83 renderListCommaAnd [x, x'] = x ++ " and " ++ x'
84 renderListCommaAnd (x : xs) = x ++ ", " ++ renderListCommaAnd xs
86 renderListTabular :: [String] -> String
87 renderListTabular = ("\n" ++) . unlines . map ("| * " ++)
89 renderListPretty :: [String] -> String
90 renderListPretty xs =
91 if length xs > 5
92 then renderListTabular xs
93 else renderListCommaAnd xs
95 -- | Render a list of things in the style @blah blah; this that; and the other@
96 renderListSemiAnd :: [String] -> String
97 renderListSemiAnd [] = ""
98 renderListSemiAnd [x] = x
99 renderListSemiAnd [x, x'] = x ++ "; and " ++ x'
100 renderListSemiAnd (x : xs) = x ++ "; " ++ renderListSemiAnd xs
102 -- | When rendering lists of things it often reads better to group related
103 -- things, e.g. grouping components by package name
105 -- > renderListSemiAnd
106 -- > [ "the package " ++ prettyShow pkgname ++ " components "
107 -- > ++ renderListCommaAnd showComponentName components
108 -- > | (pkgname, components) <- sortGroupOn packageName allcomponents ]
109 sortGroupOn :: Ord b => (a -> b) -> [a] -> [(b, [a])]
110 sortGroupOn key =
111 map (\(x :| xs) -> (key x, x : xs))
112 . NE.groupBy ((==) `on` key)
113 . sortBy (compare `on` key)
115 ----------------------------------------------------
116 -- Rendering for a few project and package types
119 renderTargetSelector :: TargetSelector -> String
120 renderTargetSelector (TargetPackage _ pkgids Nothing) =
121 "the "
122 ++ plural (listPlural pkgids) "package" "packages"
123 ++ " "
124 ++ renderListCommaAnd (map prettyShow pkgids)
125 renderTargetSelector (TargetPackage _ pkgids (Just kfilter)) =
126 "the "
127 ++ renderComponentKind Plural kfilter
128 ++ " in the "
129 ++ plural (listPlural pkgids) "package" "packages"
130 ++ " "
131 ++ renderListCommaAnd (map prettyShow pkgids)
132 renderTargetSelector (TargetPackageNamed pkgname Nothing) =
133 "the package " ++ prettyShow pkgname
134 renderTargetSelector (TargetPackageNamed pkgname (Just kfilter)) =
135 "the "
136 ++ renderComponentKind Plural kfilter
137 ++ " in the package "
138 ++ prettyShow pkgname
139 renderTargetSelector (TargetAllPackages Nothing) =
140 "all the packages in the project"
141 renderTargetSelector (TargetAllPackages (Just kfilter)) =
142 "all the "
143 ++ renderComponentKind Plural kfilter
144 ++ " in the project"
145 renderTargetSelector (TargetComponent pkgid cname subtarget) =
146 renderSubComponentTarget subtarget
147 ++ "the "
148 ++ renderComponentName (packageName pkgid) cname
149 renderTargetSelector (TargetComponentUnknown pkgname (Left ucname) subtarget) =
150 renderSubComponentTarget subtarget
151 ++ "the component "
152 ++ prettyShow ucname
153 ++ " in the package "
154 ++ prettyShow pkgname
155 renderTargetSelector (TargetComponentUnknown pkgname (Right cname) subtarget) =
156 renderSubComponentTarget subtarget
157 ++ "the "
158 ++ renderComponentName pkgname cname
160 renderSubComponentTarget :: SubComponentTarget -> String
161 renderSubComponentTarget WholeComponent = ""
162 renderSubComponentTarget (FileTarget filename) =
163 "the file " ++ filename ++ " in "
164 renderSubComponentTarget (ModuleTarget modname) =
165 "the module " ++ prettyShow modname ++ " in "
167 renderOptionalStanza :: Plural -> OptionalStanza -> String
168 renderOptionalStanza Singular TestStanzas = "test suite"
169 renderOptionalStanza Plural TestStanzas = "test suites"
170 renderOptionalStanza Singular BenchStanzas = "benchmark"
171 renderOptionalStanza Plural BenchStanzas = "benchmarks"
173 -- | The optional stanza type (test suite or benchmark), if it is one.
174 optionalStanza :: ComponentName -> Maybe OptionalStanza
175 optionalStanza (CTestName _) = Just TestStanzas
176 optionalStanza (CBenchName _) = Just BenchStanzas
177 optionalStanza _ = Nothing
179 -- | Does the 'TargetSelector' potentially refer to one package or many?
180 targetSelectorPluralPkgs :: TargetSelector -> Plural
181 targetSelectorPluralPkgs (TargetAllPackages _) = Plural
182 targetSelectorPluralPkgs (TargetPackage _ pids _) = listPlural pids
183 targetSelectorPluralPkgs (TargetPackageNamed _ _) = Singular
184 targetSelectorPluralPkgs TargetComponent{} = Singular
185 targetSelectorPluralPkgs TargetComponentUnknown{} = Singular
187 -- | Does the 'TargetSelector' refer to packages or to components?
188 targetSelectorRefersToPkgs :: TargetSelector -> Bool
189 targetSelectorRefersToPkgs (TargetAllPackages mkfilter) = isNothing mkfilter
190 targetSelectorRefersToPkgs (TargetPackage _ _ mkfilter) = isNothing mkfilter
191 targetSelectorRefersToPkgs (TargetPackageNamed _ mkfilter) = isNothing mkfilter
192 targetSelectorRefersToPkgs TargetComponent{} = False
193 targetSelectorRefersToPkgs TargetComponentUnknown{} = False
195 targetSelectorFilter :: TargetSelector -> Maybe ComponentKindFilter
196 targetSelectorFilter (TargetPackage _ _ mkfilter) = mkfilter
197 targetSelectorFilter (TargetPackageNamed _ mkfilter) = mkfilter
198 targetSelectorFilter (TargetAllPackages mkfilter) = mkfilter
199 targetSelectorFilter TargetComponent{} = Nothing
200 targetSelectorFilter TargetComponentUnknown{} = Nothing
202 renderComponentName :: PackageName -> ComponentName -> String
203 renderComponentName pkgname (CLibName LMainLibName) = "library " ++ prettyShow pkgname
204 renderComponentName _ (CLibName (LSubLibName name)) = "library " ++ prettyShow name
205 renderComponentName _ (CFLibName name) = "foreign library " ++ prettyShow name
206 renderComponentName _ (CExeName name) = "executable " ++ prettyShow name
207 renderComponentName _ (CTestName name) = "test suite " ++ prettyShow name
208 renderComponentName _ (CBenchName name) = "benchmark " ++ prettyShow name
210 renderComponentKind :: Plural -> ComponentKind -> String
211 renderComponentKind Singular ckind = case ckind of
212 LibKind -> "library" -- internal/sub libs?
213 FLibKind -> "foreign library"
214 ExeKind -> "executable"
215 TestKind -> "test suite"
216 BenchKind -> "benchmark"
217 renderComponentKind Plural ckind = case ckind of
218 LibKind -> "libraries" -- internal/sub libs?
219 FLibKind -> "foreign libraries"
220 ExeKind -> "executables"
221 TestKind -> "test suites"
222 BenchKind -> "benchmarks"
224 -------------------------------------------------------
225 -- Rendering error messages for TargetProblem
228 -- | Default implementation of 'reportTargetProblems' simply renders one problem per line.
229 reportTargetProblems :: Verbosity -> String -> [TargetProblem'] -> IO a
230 reportTargetProblems verbosity verb =
231 dieWithException verbosity . CmdErrorMessages . map (renderTargetProblem verb absurd)
233 -- | Default implementation of 'renderTargetProblem'.
234 renderTargetProblem
235 :: String
236 -- ^ verb
237 -> (a -> String)
238 -- ^ how to render custom problems
239 -> TargetProblem a
240 -> String
241 renderTargetProblem _verb f (CustomTargetProblem x) = f x
242 renderTargetProblem verb _ (TargetProblemNoneEnabled targetSelector targets) =
243 renderTargetProblemNoneEnabled verb targetSelector targets
244 renderTargetProblem verb _ (TargetProblemNoTargets targetSelector) =
245 renderTargetProblemNoTargets verb targetSelector
246 renderTargetProblem verb _ (TargetNotInProject pkgname) =
247 "Cannot "
248 ++ verb
249 ++ " the package "
250 ++ prettyShow pkgname
251 ++ ", it is not "
252 ++ "in this project (either directly or indirectly). If you want to add it "
253 ++ "to the project then edit the cabal.project file."
254 renderTargetProblem verb _ (TargetAvailableInIndex pkgname) =
255 "Cannot "
256 ++ verb
257 ++ " the package "
258 ++ prettyShow pkgname
259 ++ ", it is not "
260 ++ "in this project (either directly or indirectly), but it is in the current "
261 ++ "package index. If you want to add it to the project then edit the "
262 ++ "cabal.project file."
263 renderTargetProblem verb _ (TargetComponentNotProjectLocal pkgid cname _) =
264 "Cannot "
265 ++ verb
266 ++ " the "
267 ++ showComponentName cname
268 ++ " because the "
269 ++ "package "
270 ++ prettyShow pkgid
271 ++ " is not local to the project, and cabal "
272 ++ "does not currently support building test suites or benchmarks of "
273 ++ "non-local dependencies. To run test suites or benchmarks from "
274 ++ "dependencies you can unpack the package locally and adjust the "
275 ++ "cabal.project file to include that package directory."
276 renderTargetProblem verb _ (TargetComponentNotBuildable pkgid cname _) =
277 "Cannot "
278 ++ verb
279 ++ " the "
280 ++ showComponentName cname
281 ++ " because it is "
282 ++ "marked as 'buildable: False' within the '"
283 ++ prettyShow (packageName pkgid)
284 ++ ".cabal' file (at least for the current configuration). If you believe it "
285 ++ "should be buildable then check the .cabal file to see if the buildable "
286 ++ "property is conditional on flags. Alternatively you may simply have to "
287 ++ "edit the .cabal file to declare it as buildable and fix any resulting "
288 ++ "build problems."
289 renderTargetProblem verb _ (TargetOptionalStanzaDisabledByUser _ cname _) =
290 "Cannot "
291 ++ verb
292 ++ " the "
293 ++ showComponentName cname
294 ++ " because "
295 ++ "building "
296 ++ compkinds
297 ++ " has been explicitly disabled in the "
298 ++ "configuration. You can adjust this configuration in the "
299 ++ "cabal.project{.local} file either for all packages in the project or on "
300 ++ "a per-package basis. Note that if you do not explicitly disable "
301 ++ compkinds
302 ++ " then the solver will merely try to make a plan with "
303 ++ "them available, so you may wish to explicitly enable them which will "
304 ++ "require the solver to find a plan with them available or to fail with an "
305 ++ "explanation."
306 where
307 compkinds = renderComponentKind Plural (componentKind cname)
308 renderTargetProblem verb _ (TargetOptionalStanzaDisabledBySolver pkgid cname _) =
309 "Cannot "
310 ++ verb
311 ++ " the "
312 ++ showComponentName cname
313 ++ " because the "
314 ++ "solver did not find a plan that included the "
315 ++ compkinds
316 ++ " for "
317 ++ prettyShow pkgid
318 ++ ". It is probably worth trying again with "
319 ++ compkinds
320 ++ " explicitly enabled in the configuration in the "
321 ++ "cabal.project{.local} file. This will ask the solver to find a plan with "
322 ++ "the "
323 ++ compkinds
324 ++ " available. It will either fail with an "
325 ++ "explanation or find a different plan that uses different versions of some "
326 ++ "other packages. Use the '--dry-run' flag to see package versions and "
327 ++ "check that you are happy with the choices."
328 where
329 compkinds = renderComponentKind Plural (componentKind cname)
330 renderTargetProblem verb _ (TargetProblemUnknownComponent pkgname ecname) =
331 "Cannot "
332 ++ verb
333 ++ " the "
334 ++ ( case ecname of
335 Left ucname -> "component " ++ prettyShow ucname
336 Right cname -> renderComponentName pkgname cname
338 ++ " from the package "
339 ++ prettyShow pkgname
340 ++ ", because the package does not contain a "
341 ++ ( case ecname of
342 Left _ -> "component"
343 Right cname -> renderComponentKind Singular (componentKind cname)
345 ++ " with that name."
346 renderTargetProblem verb _ (TargetProblemNoSuchPackage pkgid) =
347 "Internal error when trying to "
348 ++ verb
349 ++ " the package "
350 ++ prettyShow pkgid
351 ++ ". The package is not in the set of available targets "
352 ++ "for the project plan, which would suggest an inconsistency "
353 ++ "between readTargetSelectors and resolveTargets."
354 renderTargetProblem verb _ (TargetProblemNoSuchComponent pkgid cname) =
355 "Internal error when trying to "
356 ++ verb
357 ++ " the "
358 ++ showComponentName cname
359 ++ " from the package "
360 ++ prettyShow pkgid
361 ++ ". The package,component pair is not in the set of available targets "
362 ++ "for the project plan, which would suggest an inconsistency "
363 ++ "between readTargetSelectors and resolveTargets."
365 ------------------------------------------------------------
366 -- Rendering error messages for TargetProblemNoneEnabled
369 -- | Several commands have a @TargetProblemNoneEnabled@ problem constructor.
370 -- This renders an error message for those cases.
371 renderTargetProblemNoneEnabled
372 :: String
373 -> TargetSelector
374 -> [AvailableTarget ()]
375 -> String
376 renderTargetProblemNoneEnabled verb targetSelector targets =
377 "Cannot "
378 ++ verb
379 ++ " "
380 ++ renderTargetSelector targetSelector
381 ++ " because none of the components are available to build: "
382 ++ renderListSemiAnd
383 [ case (status, mstanza) of
384 (TargetDisabledByUser, Just stanza) ->
385 renderListCommaAnd
386 [ "the " ++ showComponentName availableTargetComponentName
387 | AvailableTarget{availableTargetComponentName} <- targets'
389 ++ plural (listPlural targets') " is " " are "
390 ++ " not available because building "
391 ++ renderOptionalStanza Plural stanza
392 ++ " has been disabled in the configuration"
393 (TargetDisabledBySolver, Just stanza) ->
394 renderListCommaAnd
395 [ "the " ++ showComponentName availableTargetComponentName
396 | AvailableTarget{availableTargetComponentName} <- targets'
398 ++ plural (listPlural targets') " is " " are "
399 ++ "not available because the solver picked a plan that does not "
400 ++ "include the "
401 ++ renderOptionalStanza Plural stanza
402 ++ ", perhaps because no such plan exists. To see the error message "
403 ++ "explaining the problems with such plans, force the solver to "
404 ++ "include the "
405 ++ renderOptionalStanza Plural stanza
406 ++ " for all "
407 ++ "packages, by adding the line 'tests: True' to the "
408 ++ "'cabal.project.local' file."
409 (TargetNotBuildable, _) ->
410 renderListCommaAnd
411 [ "the " ++ showComponentName availableTargetComponentName
412 | AvailableTarget{availableTargetComponentName} <- targets'
414 ++ plural (listPlural targets') " is " " are all "
415 ++ "marked as 'buildable: False'"
416 (TargetNotLocal, _) ->
417 renderListCommaAnd
418 [ "the " ++ showComponentName availableTargetComponentName
419 | AvailableTarget{availableTargetComponentName} <- targets'
421 ++ " cannot be built because cabal does not currently support "
422 ++ "building test suites or benchmarks of non-local dependencies"
423 (TargetBuildable () TargetNotRequestedByDefault, Just stanza) ->
424 renderListCommaAnd
425 [ "the " ++ showComponentName availableTargetComponentName
426 | AvailableTarget{availableTargetComponentName} <- targets'
428 ++ " will not be built because "
429 ++ renderOptionalStanza Plural stanza
430 ++ " are not built by default in the current configuration (but you "
431 ++ "can still build them specifically)" -- TODO: say how
432 _ ->
433 error $
434 "renderBuildTargetProblem: unexpected status "
435 ++ show (status, mstanza)
436 | ((status, mstanza), targets') <- sortGroupOn groupingKey targets
438 where
439 groupingKey t =
440 ( availableTargetStatus t
441 , case availableTargetStatus t of
442 TargetNotBuildable -> Nothing
443 TargetNotLocal -> Nothing
444 _ -> optionalStanza (availableTargetComponentName t)
447 ------------------------------------------------------------
448 -- Rendering error messages for TargetProblemNoneEnabled
451 -- | Several commands have a @TargetProblemNoTargets@ problem constructor.
452 -- This renders an error message for those cases.
453 renderTargetProblemNoTargets :: String -> TargetSelector -> String
454 renderTargetProblemNoTargets verb targetSelector =
455 "Cannot "
456 ++ verb
457 ++ " "
458 ++ renderTargetSelector targetSelector
459 ++ " because "
460 ++ reason targetSelector
461 ++ ". "
462 ++ "Check the .cabal "
463 ++ plural
464 (targetSelectorPluralPkgs targetSelector)
465 "file for the package and make sure that it properly declares "
466 "files for the packages and make sure that they properly declare "
467 ++ "the components that you expect."
468 where
469 reason (TargetPackage _ _ Nothing) =
470 "it does not contain any components at all"
471 reason (TargetPackage _ _ (Just kfilter)) =
472 "it does not contain any " ++ renderComponentKind Plural kfilter
473 reason (TargetPackageNamed _ Nothing) =
474 "it does not contain any components at all"
475 reason (TargetPackageNamed _ (Just kfilter)) =
476 "it does not contain any " ++ renderComponentKind Plural kfilter
477 reason (TargetAllPackages Nothing) =
478 "none of them contain any components at all"
479 reason (TargetAllPackages (Just kfilter)) =
480 "none of the packages contain any "
481 ++ renderComponentKind Plural kfilter
482 reason ts@TargetComponent{} =
483 error $ "renderTargetProblemNoTargets: " ++ show ts
484 reason ts@TargetComponentUnknown{} =
485 error $ "renderTargetProblemNoTargets: " ++ show ts
487 -----------------------------------------------------------
488 -- Rendering error messages for CannotPruneDependencies
491 renderCannotPruneDependencies :: CannotPruneDependencies -> String
492 renderCannotPruneDependencies (CannotPruneDependencies brokenPackages) =
493 "Cannot select only the dependencies (as requested by the "
494 ++ "'--only-dependencies' flag), "
495 ++ ( case pkgids of
496 [pkgid] -> "the package " ++ prettyShow pkgid ++ " is "
497 _ ->
498 "the packages "
499 ++ renderListCommaAnd (map prettyShow pkgids)
500 ++ " are "
502 ++ "required by a dependency of one of the other targets."
503 where
504 -- throw away the details and just list the deps that are needed
505 pkgids :: [PackageId]
506 pkgids = nub . map packageId . concatMap snd $ brokenPackages
509 ++ "Syntax:\n"
510 ++ " - build [package]\n"
511 ++ " - build [package:]component\n"
512 ++ " - build [package:][component:]module\n"
513 ++ " - build [package:][component:]file\n"
514 ++ " where\n"
515 ++ " package is a package name, package dir or .cabal file\n\n"
516 ++ "Examples:\n"
517 ++ " - build foo -- package name\n"
518 ++ " - build tests -- component name\n"
519 ++ " (name of library, executable, test-suite or benchmark)\n"
520 ++ " - build Data.Foo -- module name\n"
521 ++ " - build Data/Foo.hsc -- file name\n\n"
522 ++ "An ambiguous target can be qualified by package, component\n"
523 ++ "and/or component kind (lib|exe|test|bench|flib)\n"
524 ++ " - build foo:tests -- component qualified by package\n"
525 ++ " - build tests:Data.Foo -- module qualified by component\n"
526 ++ " - build lib:foo -- component qualified by kind"