Add “Add default-language” suggestion
[cabal.git] / Cabal / src / Distribution / PackageDescription / Check / Warning.hs
blob6f21d5d0da6a4b44acaf4480fb332f60d8a96539
1 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
2 {-# LANGUAGE LambdaCase #-}
3 {-# LANGUAGE ScopedTypeVariables #-}
5 -- |
6 -- Module : Distribution.PackageDescription.Check.Warning
7 -- Copyright : Francesco Ariis 2022
8 -- License : BSD3
9 --
10 -- Maintainer : cabal-devel@haskell.org
11 -- Portability : portable
13 -- Warning types, messages, severity and associated functions.
14 module Distribution.PackageDescription.Check.Warning
15 ( -- * Types and constructors
16 PackageCheck (..)
17 , CheckExplanation (..)
18 , CheckExplanationID
19 , CheckExplanationIDString
20 , CEType (..)
21 , WarnLang (..)
23 -- * Operations
24 , ppPackageCheck
25 , ppCheckExplanationId
26 , isHackageDistError
27 , extractCheckExplantion
28 , filterPackageChecksById
29 , filterPackageChecksByIdString
30 ) where
32 import Distribution.Compat.Prelude
33 import Prelude ()
35 import Distribution.CabalSpecVersion (CabalSpecVersion, showCabalSpecVersion)
36 import Distribution.License (License, knownLicenses)
37 import Distribution.ModuleName (ModuleName)
38 import Distribution.Parsec.Warning (PWarning, showPWarning)
39 import Distribution.Pretty (prettyShow)
40 import Distribution.Types.BenchmarkType (BenchmarkType, knownBenchmarkTypes)
41 import Distribution.Types.Dependency (Dependency (..))
42 import Distribution.Types.ExeDependency (ExeDependency)
43 import Distribution.Types.Flag (FlagName, unFlagName)
44 import Distribution.Types.LibraryName (LibraryName (..), showLibraryName)
45 import Distribution.Types.PackageName (PackageName)
46 import Distribution.Types.TestType (TestType, knownTestTypes)
47 import Distribution.Types.UnqualComponentName
48 import Distribution.Types.Version (Version)
49 import Distribution.Utils.Path
50 ( LicenseFile
51 , PackageDir
52 , SymbolicPath
53 , getSymbolicPath
55 import Language.Haskell.Extension (Extension)
57 import qualified Data.Either as Either
58 import qualified Data.List as List
59 import qualified Data.Set as Set
61 -- ------------------------------------------------------------
62 -- Check types and explanations
63 -- ------------------------------------------------------------
65 -- | Results of some kind of failed package check.
67 -- There are a range of severities, from merely dubious to totally insane.
68 -- All of them come with a human readable explanation. In future we may augment
69 -- them with more machine readable explanations, for example to help an IDE
70 -- suggest automatic corrections.
71 data PackageCheck
72 = -- | This package description is no good. There's no way it's going to
73 -- build sensibly. This should give an error at configure time.
74 PackageBuildImpossible {explanation :: CheckExplanation}
75 | -- | A problem that is likely to affect building the package, or an
76 -- issue that we'd like every package author to be aware of, even if
77 -- the package is never distributed.
78 PackageBuildWarning {explanation :: CheckExplanation}
79 | -- | An issue that might not be a problem for the package author but
80 -- might be annoying or detrimental when the package is distributed to
81 -- users. We should encourage distributed packages to be free from these
82 -- issues, but occasionally there are justifiable reasons so we cannot
83 -- ban them entirely.
84 PackageDistSuspicious {explanation :: CheckExplanation}
85 | -- | Like PackageDistSuspicious but will only display warnings
86 -- rather than causing abnormal exit when you run 'cabal check'.
87 PackageDistSuspiciousWarn {explanation :: CheckExplanation}
88 | -- | An issue that is OK in the author's environment but is almost
89 -- certain to be a portability problem for other environments. We can
90 -- quite legitimately refuse to publicly distribute packages with these
91 -- problems.
92 PackageDistInexcusable {explanation :: CheckExplanation}
93 deriving (Eq, Ord)
95 -- | Pretty printing 'PackageCheck'.
96 ppPackageCheck :: PackageCheck -> String
97 ppPackageCheck e =
98 let ex = explanation e
99 in "["
100 ++ (ppCheckExplanationId . checkExplanationId) ex
101 ++ "] "
102 ++ ppExplanation ex
104 -- | Broken 'Show' instance (not bijective with Read), alas external packages
105 -- depend on it.
106 instance Show PackageCheck where
107 show notice = ppPackageCheck notice
109 -- | Would Hackage refuse a package because of this error?
110 isHackageDistError :: PackageCheck -> Bool
111 isHackageDistError = \case
112 (PackageBuildImpossible{}) -> True
113 (PackageBuildWarning{}) -> True
114 (PackageDistInexcusable{}) -> True
115 (PackageDistSuspicious{}) -> False
116 (PackageDistSuspiciousWarn{}) -> False
118 -- | Filter Package Check by CheckExplanationID.
119 filterPackageChecksById
120 :: [PackageCheck]
121 -- ^ Original checks.
122 -> [CheckExplanationID]
123 -- ^ IDs to omit.
124 -> [PackageCheck]
125 filterPackageChecksById cs is = filter ff cs
126 where
127 ff :: PackageCheck -> Bool
128 ff c =
129 flip notElem is
130 . checkExplanationId
131 . extractCheckExplantion
134 -- | Filter Package Check by Check explanation /string/.
135 filterPackageChecksByIdString
136 :: [PackageCheck]
137 -- ^ Original checks.
138 -> [CheckExplanationIDString]
139 -- ^ IDs to omit, in @String@ format.
140 -> ([PackageCheck], [CheckExplanationIDString])
141 -- Filtered checks plus unrecognised id strings.
142 filterPackageChecksByIdString cs ss =
143 let (es, is) = Either.partitionEithers $ map readExplanationID ss
144 in (filterPackageChecksById cs is, es)
146 -- | Explanations of 'PackageCheck`'s errors/warnings.
147 data CheckExplanation
148 = ParseWarning FilePath PWarning
149 | NoNameField
150 | NoVersionField
151 | NoTarget
152 | UnnamedInternal
153 | DuplicateSections [UnqualComponentName]
154 | IllegalLibraryName PackageName
155 | NoModulesExposed LibraryName
156 | SignaturesCabal2
157 | AutogenNotExposed
158 | AutogenIncludesNotIncluded
159 | NoMainIs UnqualComponentName
160 | NoHsLhsMain
161 | MainCCabal1_18
162 | AutogenNoOther CEType
163 | AutogenIncludesNotIncludedExe
164 | TestsuiteTypeNotKnown TestType
165 | TestsuiteNotSupported TestType
166 | BenchmarkTypeNotKnown BenchmarkType
167 | BenchmarkNotSupported BenchmarkType
168 | NoHsLhsMainBench
169 | InvalidNameWin PackageName
170 | ZPrefix
171 | NoBuildType
172 | NoCustomSetup
173 | UnknownCompilers [String]
174 | UnknownLanguages [String]
175 | UnknownExtensions [String]
176 | LanguagesAsExtension [String]
177 | DeprecatedExtensions [(Extension, Maybe Extension)]
178 | MissingFieldCategory
179 | MissingFieldMaintainer
180 | MissingFieldSynopsis
181 | MissingFieldDescription
182 | MissingFieldSynOrDesc
183 | SynopsisTooLong
184 | ShortDesc
185 | InvalidTestWith [Dependency]
186 | ImpossibleInternalDep [Dependency]
187 | ImpossibleInternalExe [ExeDependency]
188 | MissingInternalExe [ExeDependency]
189 | NONELicense
190 | NoLicense
191 | AllRightsReservedLicense
192 | LicenseMessParse License
193 | UnrecognisedLicense String
194 | UncommonBSD4
195 | UnknownLicenseVersion License [Version]
196 | NoLicenseFile
197 | UnrecognisedSourceRepo String
198 | MissingType
199 | MissingLocation
200 | MissingModule
201 | MissingTag
202 | SubdirRelPath
203 | SubdirGoodRelPath String
204 | OptFasm String
205 | OptHpc String
206 | OptProf String
207 | OptO String
208 | OptHide String
209 | OptMake String
210 | OptONot String
211 | OptOOne String
212 | OptOTwo String
213 | OptSplitSections String
214 | OptSplitObjs String
215 | OptWls String
216 | OptExts String
217 | OptRts String
218 | OptWithRts String
219 | COptONumber String WarnLang
220 | COptCPP String
221 | OptAlternatives String String [(String, String)]
222 | RelativeOutside String FilePath
223 | AbsolutePath String FilePath
224 | BadRelativePath String FilePath String
225 | DistPoint (Maybe String) FilePath
226 | GlobSyntaxError String String
227 | RecursiveGlobInRoot String FilePath
228 | InvalidOnWin [FilePath]
229 | FilePathTooLong FilePath
230 | FilePathNameTooLong FilePath
231 | FilePathSplitTooLong FilePath
232 | FilePathEmpty
233 | CVTestSuite
234 | CVDefaultLanguage
235 | CVDefaultLanguageComponent
236 | CVDefaultLanguageComponentSoft
237 | CVExtraDocFiles
238 | CVMultiLib
239 | CVReexported
240 | CVMixins
241 | CVExtraFrameworkDirs
242 | CVDefaultExtensions
243 | CVExtensionsDeprecated
244 | CVSources
245 | CVExtraDynamic [[String]]
246 | CVVirtualModules
247 | CVSourceRepository
248 | CVExtensions CabalSpecVersion [Extension]
249 | CVCustomSetup
250 | CVExpliticDepsCustomSetup
251 | CVAutogenPaths
252 | CVAutogenPackageInfo
253 | CVAutogenPackageInfoGuard
254 | GlobNoMatch String String
255 | GlobExactMatch String String FilePath
256 | GlobNoDir String String FilePath
257 | UnknownOS [String]
258 | UnknownArch [String]
259 | UnknownCompiler [String]
260 | BaseNoUpperBounds
261 | MissingUpperBounds CEType [String]
262 | SuspiciousFlagName [String]
263 | DeclaredUsedFlags (Set.Set FlagName) (Set.Set FlagName)
264 | NonASCIICustomField [String]
265 | RebindableClashPaths
266 | RebindableClashPackageInfo
267 | WErrorUnneeded String
268 | JUnneeded String
269 | FDeferTypeErrorsUnneeded String
270 | DynamicUnneeded String
271 | ProfilingUnneeded String
272 | UpperBoundSetup String
273 | DuplicateModule String [ModuleName]
274 | PotentialDupModule String [ModuleName]
275 | BOMStart FilePath
276 | NotPackageName FilePath String
277 | NoDesc
278 | MultiDesc [String]
279 | UnknownFile String (SymbolicPath PackageDir LicenseFile)
280 | MissingSetupFile
281 | MissingConfigureScript
282 | UnknownDirectory String FilePath
283 | MissingSourceControl
284 | MissingExpectedDocFiles Bool [FilePath]
285 | WrongFieldForExpectedDocFiles Bool String [FilePath]
286 deriving (Eq, Ord, Show)
288 -- TODO Some checks have a constructor in list form
289 -- (e.g. `SomeWarn [n]`), CheckM m () correctly catches warnings in
290 -- different stanzas in different checks (so it is not one soup).
292 -- Ideally [SomeWar [a], SomeWar [b]] would be translated into
293 -- SomeWar [a,b] in the few cases where it is appropriate for UX
294 -- and left separated otherwise.
295 -- To achieve this the Writer part of CheckM could be modified
296 -- to be a ad hoc monoid.
298 -- Convenience.
299 extractCheckExplantion :: PackageCheck -> CheckExplanation
300 extractCheckExplantion (PackageBuildImpossible e) = e
301 extractCheckExplantion (PackageBuildWarning e) = e
302 extractCheckExplantion (PackageDistSuspicious e) = e
303 extractCheckExplantion (PackageDistSuspiciousWarn e) = e
304 extractCheckExplantion (PackageDistInexcusable e) = e
306 -- | Identifier for the speficic 'CheckExplanation'. This ensures `--ignore`
307 -- can output a warning on unrecognised values.
308 -- ☞ N.B.: should be kept in sync with 'CheckExplanation'.
309 data CheckExplanationID
310 = CIParseWarning
311 | CINoNameField
312 | CINoVersionField
313 | CINoTarget
314 | CIUnnamedInternal
315 | CIDuplicateSections
316 | CIIllegalLibraryName
317 | CINoModulesExposed
318 | CISignaturesCabal2
319 | CIAutogenNotExposed
320 | CIAutogenIncludesNotIncluded
321 | CINoMainIs
322 | CINoHsLhsMain
323 | CIMainCCabal1_18
324 | CIAutogenNoOther
325 | CIAutogenIncludesNotIncludedExe
326 | CITestsuiteTypeNotKnown
327 | CITestsuiteNotSupported
328 | CIBenchmarkTypeNotKnown
329 | CIBenchmarkNotSupported
330 | CINoHsLhsMainBench
331 | CIInvalidNameWin
332 | CIZPrefix
333 | CINoBuildType
334 | CINoCustomSetup
335 | CIUnknownCompilers
336 | CIUnknownLanguages
337 | CIUnknownExtensions
338 | CILanguagesAsExtension
339 | CIDeprecatedExtensions
340 | CIMissingFieldCategory
341 | CIMissingFieldMaintainer
342 | CIMissingFieldSynopsis
343 | CIMissingFieldDescription
344 | CIMissingFieldSynOrDesc
345 | CISynopsisTooLong
346 | CIShortDesc
347 | CIInvalidTestWith
348 | CIImpossibleInternalDep
349 | CIImpossibleInternalExe
350 | CIMissingInternalExe
351 | CINONELicense
352 | CINoLicense
353 | CIAllRightsReservedLicense
354 | CILicenseMessParse
355 | CIUnrecognisedLicense
356 | CIUncommonBSD4
357 | CIUnknownLicenseVersion
358 | CINoLicenseFile
359 | CIUnrecognisedSourceRepo
360 | CIMissingType
361 | CIMissingLocation
362 | CIMissingModule
363 | CIMissingTag
364 | CISubdirRelPath
365 | CISubdirGoodRelPath
366 | CIOptFasm
367 | CIOptHpc
368 | CIOptProf
369 | CIOptO
370 | CIOptHide
371 | CIOptMake
372 | CIOptONot
373 | CIOptOOne
374 | CIOptOTwo
375 | CIOptSplitSections
376 | CIOptSplitObjs
377 | CIOptWls
378 | CIOptExts
379 | CIOptRts
380 | CIOptWithRts
381 | CICOptONumber
382 | CICOptCPP
383 | CIOptAlternatives
384 | CIRelativeOutside
385 | CIAbsolutePath
386 | CIBadRelativePath
387 | CIDistPoint
388 | CIGlobSyntaxError
389 | CIRecursiveGlobInRoot
390 | CIInvalidOnWin
391 | CIFilePathTooLong
392 | CIFilePathNameTooLong
393 | CIFilePathSplitTooLong
394 | CIFilePathEmpty
395 | CICVTestSuite
396 | CICVDefaultLanguage
397 | CICVDefaultLanguageComponent
398 | CICVDefaultLanguageComponentSoft
399 | CICVExtraDocFiles
400 | CICVMultiLib
401 | CICVReexported
402 | CICVMixins
403 | CICVExtraFrameworkDirs
404 | CICVDefaultExtensions
405 | CICVExtensionsDeprecated
406 | CICVSources
407 | CICVExtraDynamic
408 | CICVVirtualModules
409 | CICVSourceRepository
410 | CICVExtensions
411 | CICVCustomSetup
412 | CICVExpliticDepsCustomSetup
413 | CICVAutogenPaths
414 | CICVAutogenPackageInfo
415 | CICVAutogenPackageInfoGuard
416 | CIGlobNoMatch
417 | CIGlobExactMatch
418 | CIGlobNoDir
419 | CIUnknownOS
420 | CIUnknownArch
421 | CIUnknownCompiler
422 | CIBaseNoUpperBounds
423 | CIMissingUpperBounds
424 | CISuspiciousFlagName
425 | CIDeclaredUsedFlags
426 | CINonASCIICustomField
427 | CIRebindableClashPaths
428 | CIRebindableClashPackageInfo
429 | CIWErrorUnneeded
430 | CIJUnneeded
431 | CIFDeferTypeErrorsUnneeded
432 | CIDynamicUnneeded
433 | CIProfilingUnneeded
434 | CIUpperBoundSetup
435 | CIDuplicateModule
436 | CIPotentialDupModule
437 | CIBOMStart
438 | CINotPackageName
439 | CINoDesc
440 | CIMultiDesc
441 | CIUnknownFile
442 | CIMissingSetupFile
443 | CIMissingConfigureScript
444 | CIUnknownDirectory
445 | CIMissingSourceControl
446 | CIMissingExpectedDocFiles
447 | CIWrongFieldForExpectedDocFiles
448 deriving (Eq, Ord, Show, Enum, Bounded)
450 checkExplanationId :: CheckExplanation -> CheckExplanationID
451 checkExplanationId (ParseWarning{}) = CIParseWarning
452 checkExplanationId (NoNameField{}) = CINoNameField
453 checkExplanationId (NoVersionField{}) = CINoVersionField
454 checkExplanationId (NoTarget{}) = CINoTarget
455 checkExplanationId (UnnamedInternal{}) = CIUnnamedInternal
456 checkExplanationId (DuplicateSections{}) = CIDuplicateSections
457 checkExplanationId (IllegalLibraryName{}) = CIIllegalLibraryName
458 checkExplanationId (NoModulesExposed{}) = CINoModulesExposed
459 checkExplanationId (SignaturesCabal2{}) = CISignaturesCabal2
460 checkExplanationId (AutogenNotExposed{}) = CIAutogenNotExposed
461 checkExplanationId (AutogenIncludesNotIncluded{}) = CIAutogenIncludesNotIncluded
462 checkExplanationId (NoMainIs{}) = CINoMainIs
463 checkExplanationId (NoHsLhsMain{}) = CINoHsLhsMain
464 checkExplanationId (MainCCabal1_18{}) = CIMainCCabal1_18
465 checkExplanationId (AutogenNoOther{}) = CIAutogenNoOther
466 checkExplanationId (AutogenIncludesNotIncludedExe{}) = CIAutogenIncludesNotIncludedExe
467 checkExplanationId (TestsuiteTypeNotKnown{}) = CITestsuiteTypeNotKnown
468 checkExplanationId (TestsuiteNotSupported{}) = CITestsuiteNotSupported
469 checkExplanationId (BenchmarkTypeNotKnown{}) = CIBenchmarkTypeNotKnown
470 checkExplanationId (BenchmarkNotSupported{}) = CIBenchmarkNotSupported
471 checkExplanationId (NoHsLhsMainBench{}) = CINoHsLhsMainBench
472 checkExplanationId (InvalidNameWin{}) = CIInvalidNameWin
473 checkExplanationId (ZPrefix{}) = CIZPrefix
474 checkExplanationId (NoBuildType{}) = CINoBuildType
475 checkExplanationId (NoCustomSetup{}) = CINoCustomSetup
476 checkExplanationId (UnknownCompilers{}) = CIUnknownCompilers
477 checkExplanationId (UnknownLanguages{}) = CIUnknownLanguages
478 checkExplanationId (UnknownExtensions{}) = CIUnknownExtensions
479 checkExplanationId (LanguagesAsExtension{}) = CILanguagesAsExtension
480 checkExplanationId (DeprecatedExtensions{}) = CIDeprecatedExtensions
481 checkExplanationId (MissingFieldCategory{}) = CIMissingFieldCategory
482 checkExplanationId (MissingFieldMaintainer{}) = CIMissingFieldMaintainer
483 checkExplanationId (MissingFieldSynopsis{}) = CIMissingFieldSynopsis
484 checkExplanationId (MissingFieldDescription{}) = CIMissingFieldDescription
485 checkExplanationId (MissingFieldSynOrDesc{}) = CIMissingFieldSynOrDesc
486 checkExplanationId (SynopsisTooLong{}) = CISynopsisTooLong
487 checkExplanationId (ShortDesc{}) = CIShortDesc
488 checkExplanationId (InvalidTestWith{}) = CIInvalidTestWith
489 checkExplanationId (ImpossibleInternalDep{}) = CIImpossibleInternalDep
490 checkExplanationId (ImpossibleInternalExe{}) = CIImpossibleInternalExe
491 checkExplanationId (MissingInternalExe{}) = CIMissingInternalExe
492 checkExplanationId (NONELicense{}) = CINONELicense
493 checkExplanationId (NoLicense{}) = CINoLicense
494 checkExplanationId (AllRightsReservedLicense{}) = CIAllRightsReservedLicense
495 checkExplanationId (LicenseMessParse{}) = CILicenseMessParse
496 checkExplanationId (UnrecognisedLicense{}) = CIUnrecognisedLicense
497 checkExplanationId (UncommonBSD4{}) = CIUncommonBSD4
498 checkExplanationId (UnknownLicenseVersion{}) = CIUnknownLicenseVersion
499 checkExplanationId (NoLicenseFile{}) = CINoLicenseFile
500 checkExplanationId (UnrecognisedSourceRepo{}) = CIUnrecognisedSourceRepo
501 checkExplanationId (MissingType{}) = CIMissingType
502 checkExplanationId (MissingLocation{}) = CIMissingLocation
503 checkExplanationId (MissingModule{}) = CIMissingModule
504 checkExplanationId (MissingTag{}) = CIMissingTag
505 checkExplanationId (SubdirRelPath{}) = CISubdirRelPath
506 checkExplanationId (SubdirGoodRelPath{}) = CISubdirGoodRelPath
507 checkExplanationId (OptFasm{}) = CIOptFasm
508 checkExplanationId (OptHpc{}) = CIOptHpc
509 checkExplanationId (OptProf{}) = CIOptProf
510 checkExplanationId (OptO{}) = CIOptO
511 checkExplanationId (OptHide{}) = CIOptHide
512 checkExplanationId (OptMake{}) = CIOptMake
513 checkExplanationId (OptONot{}) = CIOptONot
514 checkExplanationId (OptOOne{}) = CIOptOOne
515 checkExplanationId (OptOTwo{}) = CIOptOTwo
516 checkExplanationId (OptSplitSections{}) = CIOptSplitSections
517 checkExplanationId (OptSplitObjs{}) = CIOptSplitObjs
518 checkExplanationId (OptWls{}) = CIOptWls
519 checkExplanationId (OptExts{}) = CIOptExts
520 checkExplanationId (OptRts{}) = CIOptRts
521 checkExplanationId (OptWithRts{}) = CIOptWithRts
522 checkExplanationId (COptONumber{}) = CICOptONumber
523 checkExplanationId (COptCPP{}) = CICOptCPP
524 checkExplanationId (OptAlternatives{}) = CIOptAlternatives
525 checkExplanationId (RelativeOutside{}) = CIRelativeOutside
526 checkExplanationId (AbsolutePath{}) = CIAbsolutePath
527 checkExplanationId (BadRelativePath{}) = CIBadRelativePath
528 checkExplanationId (DistPoint{}) = CIDistPoint
529 checkExplanationId (GlobSyntaxError{}) = CIGlobSyntaxError
530 checkExplanationId (RecursiveGlobInRoot{}) = CIRecursiveGlobInRoot
531 checkExplanationId (InvalidOnWin{}) = CIInvalidOnWin
532 checkExplanationId (FilePathTooLong{}) = CIFilePathTooLong
533 checkExplanationId (FilePathNameTooLong{}) = CIFilePathNameTooLong
534 checkExplanationId (FilePathSplitTooLong{}) = CIFilePathSplitTooLong
535 checkExplanationId (FilePathEmpty{}) = CIFilePathEmpty
536 checkExplanationId (CVTestSuite{}) = CICVTestSuite
537 checkExplanationId (CVDefaultLanguage{}) = CICVDefaultLanguage
538 checkExplanationId (CVDefaultLanguageComponent{}) = CICVDefaultLanguageComponent
539 checkExplanationId (CVDefaultLanguageComponentSoft{}) = CICVDefaultLanguageComponentSoft
540 checkExplanationId (CVExtraDocFiles{}) = CICVExtraDocFiles
541 checkExplanationId (CVMultiLib{}) = CICVMultiLib
542 checkExplanationId (CVReexported{}) = CICVReexported
543 checkExplanationId (CVMixins{}) = CICVMixins
544 checkExplanationId (CVExtraFrameworkDirs{}) = CICVExtraFrameworkDirs
545 checkExplanationId (CVDefaultExtensions{}) = CICVDefaultExtensions
546 checkExplanationId (CVExtensionsDeprecated{}) = CICVExtensionsDeprecated
547 checkExplanationId (CVSources{}) = CICVSources
548 checkExplanationId (CVExtraDynamic{}) = CICVExtraDynamic
549 checkExplanationId (CVVirtualModules{}) = CICVVirtualModules
550 checkExplanationId (CVSourceRepository{}) = CICVSourceRepository
551 checkExplanationId (CVExtensions{}) = CICVExtensions
552 checkExplanationId (CVCustomSetup{}) = CICVCustomSetup
553 checkExplanationId (CVExpliticDepsCustomSetup{}) = CICVExpliticDepsCustomSetup
554 checkExplanationId (CVAutogenPaths{}) = CICVAutogenPaths
555 checkExplanationId (CVAutogenPackageInfo{}) = CICVAutogenPackageInfo
556 checkExplanationId (CVAutogenPackageInfoGuard{}) = CICVAutogenPackageInfoGuard
557 checkExplanationId (GlobNoMatch{}) = CIGlobNoMatch
558 checkExplanationId (GlobExactMatch{}) = CIGlobExactMatch
559 checkExplanationId (GlobNoDir{}) = CIGlobNoDir
560 checkExplanationId (UnknownOS{}) = CIUnknownOS
561 checkExplanationId (UnknownArch{}) = CIUnknownArch
562 checkExplanationId (UnknownCompiler{}) = CIUnknownCompiler
563 checkExplanationId (BaseNoUpperBounds{}) = CIBaseNoUpperBounds
564 checkExplanationId (MissingUpperBounds{}) = CIMissingUpperBounds
565 checkExplanationId (SuspiciousFlagName{}) = CISuspiciousFlagName
566 checkExplanationId (DeclaredUsedFlags{}) = CIDeclaredUsedFlags
567 checkExplanationId (NonASCIICustomField{}) = CINonASCIICustomField
568 checkExplanationId (RebindableClashPaths{}) = CIRebindableClashPaths
569 checkExplanationId (RebindableClashPackageInfo{}) = CIRebindableClashPackageInfo
570 checkExplanationId (WErrorUnneeded{}) = CIWErrorUnneeded
571 checkExplanationId (JUnneeded{}) = CIJUnneeded
572 checkExplanationId (FDeferTypeErrorsUnneeded{}) = CIFDeferTypeErrorsUnneeded
573 checkExplanationId (DynamicUnneeded{}) = CIDynamicUnneeded
574 checkExplanationId (ProfilingUnneeded{}) = CIProfilingUnneeded
575 checkExplanationId (UpperBoundSetup{}) = CIUpperBoundSetup
576 checkExplanationId (DuplicateModule{}) = CIDuplicateModule
577 checkExplanationId (PotentialDupModule{}) = CIPotentialDupModule
578 checkExplanationId (BOMStart{}) = CIBOMStart
579 checkExplanationId (NotPackageName{}) = CINotPackageName
580 checkExplanationId (NoDesc{}) = CINoDesc
581 checkExplanationId (MultiDesc{}) = CIMultiDesc
582 checkExplanationId (UnknownFile{}) = CIUnknownFile
583 checkExplanationId (MissingSetupFile{}) = CIMissingSetupFile
584 checkExplanationId (MissingConfigureScript{}) = CIMissingConfigureScript
585 checkExplanationId (UnknownDirectory{}) = CIUnknownDirectory
586 checkExplanationId (MissingSourceControl{}) = CIMissingSourceControl
587 checkExplanationId (MissingExpectedDocFiles{}) = CIMissingExpectedDocFiles
588 checkExplanationId (WrongFieldForExpectedDocFiles{}) = CIWrongFieldForExpectedDocFiles
590 type CheckExplanationIDString = String
592 -- A one-word identifier for each CheckExplanation
594 -- ☞ N.B: if you modify anything here, remeber to change the documentation
595 -- in @doc/cabal-commands.rst@!
596 ppCheckExplanationId :: CheckExplanationID -> CheckExplanationIDString
597 ppCheckExplanationId CIParseWarning = "parser-warning"
598 ppCheckExplanationId CINoNameField = "no-name-field"
599 ppCheckExplanationId CINoVersionField = "no-version-field"
600 ppCheckExplanationId CINoTarget = "no-target"
601 ppCheckExplanationId CIUnnamedInternal = "unnamed-internal-library"
602 ppCheckExplanationId CIDuplicateSections = "duplicate-sections"
603 ppCheckExplanationId CIIllegalLibraryName = "illegal-library-name"
604 ppCheckExplanationId CINoModulesExposed = "no-modules-exposed"
605 ppCheckExplanationId CISignaturesCabal2 = "signatures"
606 ppCheckExplanationId CIAutogenNotExposed = "autogen-not-exposed"
607 ppCheckExplanationId CIAutogenIncludesNotIncluded = "autogen-not-included"
608 ppCheckExplanationId CINoMainIs = "no-main-is"
609 ppCheckExplanationId CINoHsLhsMain = "unknown-extension-main"
610 ppCheckExplanationId CIMainCCabal1_18 = "c-like-main"
611 ppCheckExplanationId CIAutogenNoOther = "autogen-other-modules"
612 ppCheckExplanationId CIAutogenIncludesNotIncludedExe = "autogen-exe"
613 ppCheckExplanationId CITestsuiteTypeNotKnown = "unknown-testsuite-type"
614 ppCheckExplanationId CITestsuiteNotSupported = "unsupported-testsuite"
615 ppCheckExplanationId CIBenchmarkTypeNotKnown = "unknown-bench"
616 ppCheckExplanationId CIBenchmarkNotSupported = "unsupported-bench"
617 ppCheckExplanationId CINoHsLhsMainBench = "bench-unknown-extension"
618 ppCheckExplanationId CIInvalidNameWin = "invalid-name-win"
619 ppCheckExplanationId CIZPrefix = "reserved-z-prefix"
620 ppCheckExplanationId CINoBuildType = "no-build-type"
621 ppCheckExplanationId CINoCustomSetup = "undeclared-custom-setup"
622 ppCheckExplanationId CIUnknownCompilers = "unknown-compiler-tested"
623 ppCheckExplanationId CIUnknownLanguages = "unknown-languages"
624 ppCheckExplanationId CIUnknownExtensions = "unknown-extension"
625 ppCheckExplanationId CILanguagesAsExtension = "languages-as-extensions"
626 ppCheckExplanationId CIDeprecatedExtensions = "deprecated-extensions"
627 ppCheckExplanationId CIMissingFieldCategory = "no-category"
628 ppCheckExplanationId CIMissingFieldMaintainer = "no-maintainer"
629 ppCheckExplanationId CIMissingFieldSynopsis = "no-synopsis"
630 ppCheckExplanationId CIMissingFieldDescription = "no-description"
631 ppCheckExplanationId CIMissingFieldSynOrDesc = "no-syn-desc"
632 ppCheckExplanationId CISynopsisTooLong = "long-synopsis"
633 ppCheckExplanationId CIShortDesc = "short-description"
634 ppCheckExplanationId CIInvalidTestWith = "invalid-range-tested"
635 ppCheckExplanationId CIImpossibleInternalDep = "impossible-dep"
636 ppCheckExplanationId CIImpossibleInternalExe = "impossible-dep-exe"
637 ppCheckExplanationId CIMissingInternalExe = "no-internal-exe"
638 ppCheckExplanationId CINONELicense = "license-none"
639 ppCheckExplanationId CINoLicense = "no-license"
640 ppCheckExplanationId CIAllRightsReservedLicense = "all-rights-reserved"
641 ppCheckExplanationId CILicenseMessParse = "license-parse"
642 ppCheckExplanationId CIUnrecognisedLicense = "unknown-license"
643 ppCheckExplanationId CIUncommonBSD4 = "bsd4-license"
644 ppCheckExplanationId CIUnknownLicenseVersion = "unknown-license-version"
645 ppCheckExplanationId CINoLicenseFile = "no-license-file"
646 ppCheckExplanationId CIUnrecognisedSourceRepo = "unrecognised-repo-type"
647 ppCheckExplanationId CIMissingType = "repo-no-type"
648 ppCheckExplanationId CIMissingLocation = "repo-no-location"
649 ppCheckExplanationId CIMissingModule = "repo-no-module"
650 ppCheckExplanationId CIMissingTag = "repo-no-tag"
651 ppCheckExplanationId CISubdirRelPath = "repo-relative-dir"
652 ppCheckExplanationId CISubdirGoodRelPath = "repo-malformed-subdir"
653 ppCheckExplanationId CIOptFasm = "option-fasm"
654 ppCheckExplanationId CIOptHpc = "option-fhpc"
655 ppCheckExplanationId CIOptProf = "option-prof"
656 ppCheckExplanationId CIOptO = "option-o"
657 ppCheckExplanationId CIOptHide = "option-hide-package"
658 ppCheckExplanationId CIOptMake = "option-make"
659 ppCheckExplanationId CIOptONot = "option-optimize"
660 ppCheckExplanationId CIOptOOne = "option-o1"
661 ppCheckExplanationId CIOptOTwo = "option-o2"
662 ppCheckExplanationId CIOptSplitSections = "option-split-section"
663 ppCheckExplanationId CIOptSplitObjs = "option-split-objs"
664 ppCheckExplanationId CIOptWls = "option-optl-wl"
665 ppCheckExplanationId CIOptExts = "use-extension"
666 ppCheckExplanationId CIOptRts = "option-rtsopts"
667 ppCheckExplanationId CIOptWithRts = "option-with-rtsopts"
668 ppCheckExplanationId CICOptONumber = "option-opt-c"
669 ppCheckExplanationId CICOptCPP = "cpp-options"
670 ppCheckExplanationId CIOptAlternatives = "misplaced-c-opt"
671 ppCheckExplanationId CIRelativeOutside = "relative-path-outside"
672 ppCheckExplanationId CIAbsolutePath = "absolute-path"
673 ppCheckExplanationId CIBadRelativePath = "malformed-relative-path"
674 ppCheckExplanationId CIDistPoint = "unreliable-dist-path"
675 ppCheckExplanationId CIGlobSyntaxError = "glob-syntax-error"
676 ppCheckExplanationId CIRecursiveGlobInRoot = "recursive-glob"
677 ppCheckExplanationId CIInvalidOnWin = "invalid-path-win"
678 ppCheckExplanationId CIFilePathTooLong = "long-path"
679 ppCheckExplanationId CIFilePathNameTooLong = "long-name"
680 ppCheckExplanationId CIFilePathSplitTooLong = "name-not-portable"
681 ppCheckExplanationId CIFilePathEmpty = "empty-path"
682 ppCheckExplanationId CICVTestSuite = "test-cabal-ver"
683 ppCheckExplanationId CICVDefaultLanguage = "default-language"
684 ppCheckExplanationId CICVDefaultLanguageComponent = "no-default-language"
685 ppCheckExplanationId CICVDefaultLanguageComponentSoft = "add-language"
686 ppCheckExplanationId CICVExtraDocFiles = "extra-doc-files"
687 ppCheckExplanationId CICVMultiLib = "multilib"
688 ppCheckExplanationId CICVReexported = "reexported-modules"
689 ppCheckExplanationId CICVMixins = "mixins"
690 ppCheckExplanationId CICVExtraFrameworkDirs = "extra-framework-dirs"
691 ppCheckExplanationId CICVDefaultExtensions = "default-extensions"
692 ppCheckExplanationId CICVExtensionsDeprecated = "extensions-field"
693 ppCheckExplanationId CICVSources = "unsupported-sources"
694 ppCheckExplanationId CICVExtraDynamic = "extra-dynamic"
695 ppCheckExplanationId CICVVirtualModules = "virtual-modules"
696 ppCheckExplanationId CICVSourceRepository = "source-repository"
697 ppCheckExplanationId CICVExtensions = "incompatible-extension"
698 ppCheckExplanationId CICVCustomSetup = "no-setup-depends"
699 ppCheckExplanationId CICVExpliticDepsCustomSetup = "dependencies-setup"
700 ppCheckExplanationId CICVAutogenPaths = "no-autogen-paths"
701 ppCheckExplanationId CICVAutogenPackageInfo = "no-autogen-pinfo"
702 ppCheckExplanationId CICVAutogenPackageInfoGuard = "autogen-guard"
703 ppCheckExplanationId CIGlobNoMatch = "no-glob-match"
704 ppCheckExplanationId CIGlobExactMatch = "glob-no-extension"
705 ppCheckExplanationId CIGlobNoDir = "glob-missing-dir"
706 ppCheckExplanationId CIUnknownOS = "unknown-os"
707 ppCheckExplanationId CIUnknownArch = "unknown-arch"
708 ppCheckExplanationId CIUnknownCompiler = "unknown-compiler"
709 ppCheckExplanationId CIBaseNoUpperBounds = "missing-bounds-important"
710 ppCheckExplanationId CIMissingUpperBounds = "missing-upper-bounds"
711 ppCheckExplanationId CISuspiciousFlagName = "suspicious-flag"
712 ppCheckExplanationId CIDeclaredUsedFlags = "unused-flag"
713 ppCheckExplanationId CINonASCIICustomField = "non-ascii"
714 ppCheckExplanationId CIRebindableClashPaths = "rebindable-clash-paths"
715 ppCheckExplanationId CIRebindableClashPackageInfo = "rebindable-clash-info"
716 ppCheckExplanationId CIWErrorUnneeded = "werror"
717 ppCheckExplanationId CIJUnneeded = "unneeded-j"
718 ppCheckExplanationId CIFDeferTypeErrorsUnneeded = "fdefer-type-errors"
719 ppCheckExplanationId CIDynamicUnneeded = "debug-flag"
720 ppCheckExplanationId CIProfilingUnneeded = "fprof-flag"
721 ppCheckExplanationId CIUpperBoundSetup = "missing-bounds-setup"
722 ppCheckExplanationId CIDuplicateModule = "duplicate-modules"
723 ppCheckExplanationId CIPotentialDupModule = "maybe-duplicate-modules"
724 ppCheckExplanationId CIBOMStart = "bom"
725 ppCheckExplanationId CINotPackageName = "name-no-match"
726 ppCheckExplanationId CINoDesc = "no-cabal-file"
727 ppCheckExplanationId CIMultiDesc = "multiple-cabal-file"
728 ppCheckExplanationId CIUnknownFile = "unknown-file"
729 ppCheckExplanationId CIMissingSetupFile = "missing-setup"
730 ppCheckExplanationId CIMissingConfigureScript = "missing-conf-script"
731 ppCheckExplanationId CIUnknownDirectory = "unknown-directory"
732 ppCheckExplanationId CIMissingSourceControl = "no-repository"
733 ppCheckExplanationId CIMissingExpectedDocFiles = "no-docs"
734 ppCheckExplanationId CIWrongFieldForExpectedDocFiles = "doc-place"
736 -- String: the unrecognised 'CheckExplanationIDString' itself.
737 readExplanationID
738 :: CheckExplanationIDString
739 -> Either String CheckExplanationID
740 readExplanationID s = maybe (Left s) Right (lookup s idsDict)
741 where
742 idsDict :: [(CheckExplanationIDString, CheckExplanationID)]
743 idsDict = map (\i -> (ppCheckExplanationId i, i)) [minBound .. maxBound]
745 -- | Which stanza does `CheckExplanation` refer to?
746 data CEType
747 = CETLibrary LibraryName
748 | CETForeignLibrary UnqualComponentName
749 | CETExecutable UnqualComponentName
750 | CETTest UnqualComponentName
751 | CETBenchmark UnqualComponentName
752 | CETSetup
753 deriving (Eq, Ord, Show)
755 -- | Pretty printing `CEType`.
756 ppCET :: CEType -> String
757 ppCET cet = case cet of
758 CETLibrary ln -> showLibraryName ln
759 CETForeignLibrary n -> "foreign library" ++ qn n
760 CETExecutable n -> "executable" ++ qn n
761 CETTest n -> "test suite" ++ qn n
762 CETBenchmark n -> "benchmark" ++ qn n
763 CETSetup -> "custom-setup"
764 where
765 qn :: UnqualComponentName -> String
766 qn wn = (" " ++) . quote . prettyShow $ wn
768 -- | Which language are we referring to in our warning message?
769 data WarnLang = LangC | LangCPlusPlus
770 deriving (Eq, Ord, Show)
772 -- | Pretty printing `WarnLang`.
773 ppWarnLang :: WarnLang -> String
774 ppWarnLang LangC = "C"
775 ppWarnLang LangCPlusPlus = "C++"
777 -- | Pretty printing `CheckExplanation`.
778 ppExplanation :: CheckExplanation -> String
779 ppExplanation (ParseWarning fp pp) = showPWarning fp pp
780 ppExplanation NoNameField = "No 'name' field."
781 ppExplanation NoVersionField = "No 'version' field."
782 ppExplanation NoTarget =
783 "No executables, libraries, tests, or benchmarks found. Nothing to do."
784 ppExplanation UnnamedInternal =
785 "Found one or more unnamed internal libraries. Only the non-internal"
786 ++ " library can have the same name as the package."
787 ppExplanation (DuplicateSections duplicateNames) =
788 "Duplicate sections: "
789 ++ commaSep (map unUnqualComponentName duplicateNames)
790 ++ ". The name of every library, executable, test suite,"
791 ++ " and benchmark section in the package must be unique."
792 ppExplanation (IllegalLibraryName pname) =
793 "Illegal internal library name "
794 ++ prettyShow pname
795 ++ ". Internal libraries cannot have the same name as the package."
796 ++ " Maybe you wanted a non-internal library?"
797 ++ " If so, rewrite the section stanza"
798 ++ " from 'library: '"
799 ++ prettyShow pname
800 ++ "' to 'library'."
801 ppExplanation (NoModulesExposed lName) =
802 showLibraryName lName ++ " does not expose any modules"
803 ppExplanation SignaturesCabal2 =
804 "To use the 'signatures' field the package needs to specify "
805 ++ "at least 'cabal-version: 2.0'."
806 ppExplanation AutogenNotExposed =
807 "An 'autogen-module' is neither on 'exposed-modules' nor 'other-modules'."
808 ppExplanation AutogenIncludesNotIncluded =
809 "An include in 'autogen-includes' is neither in 'includes' nor "
810 ++ "'install-includes'."
811 ppExplanation (NoMainIs eName) =
812 "No 'main-is' field found for executable " ++ prettyShow eName
813 ppExplanation NoHsLhsMain =
814 "The 'main-is' field must specify a '.hs' or '.lhs' file "
815 ++ "(even if it is generated by a preprocessor), "
816 ++ "or it may specify a C/C++/obj-C source file."
817 ppExplanation MainCCabal1_18 =
818 "The package uses a C/C++/obj-C source file for the 'main-is' field. "
819 ++ "To use this feature you need to specify 'cabal-version: 1.18' or"
820 ++ " higher."
821 ppExplanation (AutogenNoOther ct) =
822 "On "
823 ++ ppCET ct
824 ++ " an 'autogen-module'"
825 ++ " is not on 'other-modules'"
826 ppExplanation AutogenIncludesNotIncludedExe =
827 "An include in 'autogen-includes' is not in 'includes'."
828 ppExplanation (TestsuiteTypeNotKnown tt) =
829 quote (prettyShow tt)
830 ++ " is not a known type of test suite. "
831 ++ "Either remove the 'type' field or use a known type. "
832 ++ "The known test suite types are: "
833 ++ commaSep (map prettyShow knownTestTypes)
834 ppExplanation (TestsuiteNotSupported tt) =
835 quote (prettyShow tt)
836 ++ " is not a supported test suite version. "
837 ++ "Either remove the 'type' field or use a known type. "
838 ++ "The known test suite types are: "
839 ++ commaSep (map prettyShow knownTestTypes)
840 ppExplanation (BenchmarkTypeNotKnown tt) =
841 quote (prettyShow tt)
842 ++ " is not a known type of benchmark. "
843 ++ "Either remove the 'type' field or use a known type. "
844 ++ "The known benchmark types are: "
845 ++ commaSep (map prettyShow knownBenchmarkTypes)
846 ppExplanation (BenchmarkNotSupported tt) =
847 quote (prettyShow tt)
848 ++ " is not a supported benchmark version. "
849 ++ "Either remove the 'type' field or use a known type. "
850 ++ "The known benchmark types are: "
851 ++ commaSep (map prettyShow knownBenchmarkTypes)
852 ppExplanation NoHsLhsMainBench =
853 "The 'main-is' field must specify a '.hs' or '.lhs' file "
854 ++ "(even if it is generated by a preprocessor)."
855 ppExplanation (InvalidNameWin pkg) =
856 "The package name '"
857 ++ prettyShow pkg
858 ++ "' is "
859 ++ "invalid on Windows. Many tools need to convert package names to "
860 ++ "file names, so using this name would cause problems."
861 ppExplanation ZPrefix =
862 "Package names with the prefix 'z-' are reserved by Cabal and "
863 ++ "cannot be used."
864 ppExplanation NoBuildType =
865 "No 'build-type' specified. If you do not need a custom Setup.hs or "
866 ++ "./configure script then use 'build-type: Simple'."
867 ppExplanation NoCustomSetup =
868 "Ignoring the 'custom-setup' section because the 'build-type' is "
869 ++ "not 'Custom'. Use 'build-type: Custom' if you need to use a "
870 ++ "custom Setup.hs script."
871 ppExplanation (UnknownCompilers unknownCompilers) =
872 "Unknown compiler "
873 ++ commaSep (map quote unknownCompilers)
874 ++ " in 'tested-with' field."
875 ppExplanation (UnknownLanguages unknownLanguages) =
876 "Unknown languages: " ++ commaSep unknownLanguages
877 ppExplanation (UnknownExtensions unknownExtensions) =
878 "Unknown extensions: " ++ commaSep unknownExtensions
879 ppExplanation (LanguagesAsExtension languagesUsedAsExtensions) =
880 "Languages listed as extensions: "
881 ++ commaSep languagesUsedAsExtensions
882 ++ ". Languages must be specified in either the 'default-language' "
883 ++ " or the 'other-languages' field."
884 ppExplanation (DeprecatedExtensions ourDeprecatedExtensions) =
885 "Deprecated extensions: "
886 ++ commaSep (map (quote . prettyShow . fst) ourDeprecatedExtensions)
887 ++ ". "
888 ++ unwords
889 [ "Instead of '"
890 ++ prettyShow ext
891 ++ "' use '"
892 ++ prettyShow replacement
893 ++ "'."
894 | (ext, Just replacement) <- ourDeprecatedExtensions
896 ppExplanation MissingFieldCategory = "No 'category' field."
897 ppExplanation MissingFieldMaintainer = "No 'maintainer' field."
898 ppExplanation MissingFieldSynopsis = "No 'synopsis' field."
899 ppExplanation MissingFieldDescription = "No 'description' field."
900 ppExplanation MissingFieldSynOrDesc = "No 'synopsis' or 'description' field."
901 ppExplanation SynopsisTooLong =
902 "The 'synopsis' field is rather long (max 80 chars is recommended)."
903 ppExplanation ShortDesc =
904 "The 'description' field should be longer than the 'synopsis' field. "
905 ++ "It's useful to provide an informative 'description' to allow "
906 ++ "Haskell programmers who have never heard about your package to "
907 ++ "understand the purpose of your package. "
908 ++ "The 'description' field content is typically shown by tooling "
909 ++ "(e.g. 'cabal info', Haddock, Hackage) below the 'synopsis' which "
910 ++ "serves as a headline. "
911 ++ "Please refer to <https://cabal.readthedocs.io/en/stable/"
912 ++ "cabal-package.html#package-properties> for more details."
913 ppExplanation (InvalidTestWith testedWithImpossibleRanges) =
914 "Invalid 'tested-with' version range: "
915 ++ commaSep (map prettyShow testedWithImpossibleRanges)
916 ++ ". To indicate that you have tested a package with multiple "
917 ++ "different versions of the same compiler use multiple entries, "
918 ++ "for example 'tested-with: GHC==6.10.4, GHC==6.12.3' and not "
919 ++ "'tested-with: GHC==6.10.4 && ==6.12.3'."
920 ppExplanation (ImpossibleInternalDep depInternalLibWithImpossibleVersion) =
921 "The package has an impossible version range for a dependency on an "
922 ++ "internal library: "
923 ++ commaSep (map prettyShow depInternalLibWithImpossibleVersion)
924 ++ ". This version range does not include the current package, and must "
925 ++ "be removed as the current package's library will always be used."
926 ppExplanation (ImpossibleInternalExe depInternalExecWithImpossibleVersion) =
927 "The package has an impossible version range for a dependency on an "
928 ++ "internal executable: "
929 ++ commaSep (map prettyShow depInternalExecWithImpossibleVersion)
930 ++ ". This version range does not include the current package, and must "
931 ++ "be removed as the current package's executable will always be used."
932 ppExplanation (MissingInternalExe depInternalExeWithImpossibleVersion) =
933 "The package depends on a missing internal executable: "
934 ++ commaSep (map prettyShow depInternalExeWithImpossibleVersion)
935 ppExplanation NONELicense = "The 'license' field is missing or is NONE."
936 ppExplanation NoLicense = "The 'license' field is missing."
937 ppExplanation AllRightsReservedLicense =
938 "The 'license' is AllRightsReserved. Is that really what you want?"
939 ppExplanation (LicenseMessParse lic) =
940 "Unfortunately the license "
941 ++ quote (prettyShow lic)
942 ++ " messes up the parser in earlier Cabal versions so you need to "
943 ++ "specify 'cabal-version: >= 1.4'. Alternatively if you require "
944 ++ "compatibility with earlier Cabal versions then use 'OtherLicense'."
945 ppExplanation (UnrecognisedLicense l) =
946 quote ("license: " ++ l)
947 ++ " is not a recognised license. The "
948 ++ "known licenses are: "
949 ++ commaSep (map prettyShow knownLicenses)
950 ppExplanation UncommonBSD4 =
951 "Using 'license: BSD4' is almost always a misunderstanding. 'BSD4' "
952 ++ "refers to the old 4-clause BSD license with the advertising "
953 ++ "clause. 'BSD3' refers the new 3-clause BSD license."
954 ppExplanation (UnknownLicenseVersion lic known) =
955 "'license: "
956 ++ prettyShow lic
957 ++ "' is not a known "
958 ++ "version of that license. The known versions are "
959 ++ commaSep (map prettyShow known)
960 ++ ". If this is not a mistake and you think it should be a known "
961 ++ "version then please file a ticket."
962 ppExplanation NoLicenseFile = "A 'license-file' is not specified."
963 ppExplanation (UnrecognisedSourceRepo kind) =
964 quote kind
965 ++ " is not a recognised kind of source-repository. "
966 ++ "The repo kind is usually 'head' or 'this'"
967 ppExplanation MissingType =
968 "The source-repository 'type' is a required field."
969 ppExplanation MissingLocation =
970 "The source-repository 'location' is a required field."
971 ppExplanation MissingModule =
972 "For a CVS source-repository, the 'module' is a required field."
973 ppExplanation MissingTag =
974 "For the 'this' kind of source-repository, the 'tag' is a required "
975 ++ "field. It should specify the tag corresponding to this version "
976 ++ "or release of the package."
977 ppExplanation SubdirRelPath =
978 "The 'subdir' field of a source-repository must be a relative path."
979 ppExplanation (SubdirGoodRelPath err) =
980 "The 'subdir' field of a source-repository is not a good relative path: "
981 ++ show err
982 ppExplanation (OptFasm fieldName) =
984 ++ fieldName
985 ++ ": -fasm' is unnecessary and will not work on CPU "
986 ++ "architectures other than x86, x86-64, ppc or sparc."
987 ppExplanation (OptHpc fieldName) =
989 ++ fieldName
990 ++ ": -fhpc' is not necessary. Use the configure flag "
991 ++ " --enable-coverage instead."
992 ppExplanation (OptProf fieldName) =
994 ++ fieldName
995 ++ ": -prof' is not necessary and will lead to problems "
996 ++ "when used on a library. Use the configure flag "
997 ++ "--enable-library-profiling and/or --enable-profiling."
998 ppExplanation (OptO fieldName) =
1000 ++ fieldName
1001 ++ ": -o' is not needed. "
1002 ++ "The output files are named automatically."
1003 ppExplanation (OptHide fieldName) =
1005 ++ fieldName
1006 ++ ": -hide-package' is never needed. "
1007 ++ "Cabal hides all packages."
1008 ppExplanation (OptMake fieldName) =
1010 ++ fieldName
1011 ++ ": --make' is never needed. Cabal uses this automatically."
1012 ppExplanation (OptONot fieldName) =
1014 ++ fieldName
1015 ++ ": -O0' is not needed. "
1016 ++ "Use the --disable-optimization configure flag."
1017 ppExplanation (OptOOne fieldName) =
1019 ++ fieldName
1020 ++ ": -O' is not needed. "
1021 ++ "Cabal automatically adds the '-O' flag. "
1022 ++ "Setting it yourself interferes with the --disable-optimization flag."
1023 ppExplanation (OptOTwo fieldName) =
1025 ++ fieldName
1026 ++ ": -O2' is rarely needed. "
1027 ++ "Check that it is giving a real benefit "
1028 ++ "and not just imposing longer compile times on your users."
1029 ppExplanation (OptSplitSections fieldName) =
1031 ++ fieldName
1032 ++ ": -split-sections' is not needed. "
1033 ++ "Use the --enable-split-sections configure flag."
1034 ppExplanation (OptSplitObjs fieldName) =
1036 ++ fieldName
1037 ++ ": -split-objs' is not needed. "
1038 ++ "Use the --enable-split-objs configure flag."
1039 ppExplanation (OptWls fieldName) =
1041 ++ fieldName
1042 ++ ": -optl-Wl,-s' is not needed and is not portable to"
1043 ++ " all operating systems. Cabal 1.4 and later automatically strip"
1044 ++ " executables. Cabal also has a flag --disable-executable-stripping"
1045 ++ " which is necessary when building packages for some Linux"
1046 ++ " distributions and using '-optl-Wl,-s' prevents that from working."
1047 ppExplanation (OptExts fieldName) =
1048 "Instead of '"
1049 ++ fieldName
1050 ++ ": -fglasgow-exts' it is preferable to use "
1051 ++ "the 'extensions' field."
1052 ppExplanation (OptRts fieldName) =
1054 ++ fieldName
1055 ++ ": -rtsopts' has no effect for libraries. It should "
1056 ++ "only be used for executables."
1057 ppExplanation (OptWithRts fieldName) =
1059 ++ fieldName
1060 ++ ": -with-rtsopts' has no effect for libraries. It "
1061 ++ "should only be used for executables."
1062 ppExplanation (COptONumber prefix label) =
1064 ++ prefix
1065 ++ ": -O[n]' is generally not needed. When building with "
1066 ++ " optimisations Cabal automatically adds '-O2' for "
1067 ++ ppWarnLang label
1068 ++ " code. Setting it yourself interferes with the"
1069 ++ " --disable-optimization flag."
1070 ppExplanation (COptCPP opt) =
1071 "'cpp-options: " ++ opt ++ "' is not a portable C-preprocessor flag."
1072 ppExplanation (OptAlternatives badField goodField flags) =
1073 "Instead of "
1074 ++ quote (badField ++ ": " ++ unwords badFlags)
1075 ++ " use "
1076 ++ quote (goodField ++ ": " ++ unwords goodFlags)
1077 where
1078 (badFlags, goodFlags) = unzip flags
1079 ppExplanation (RelativeOutside field path) =
1080 quote (field ++ ": " ++ path)
1081 ++ " is a relative path outside of the source tree. "
1082 ++ "This will not work when generating a tarball with 'sdist'."
1083 ppExplanation (AbsolutePath field path) =
1084 quote (field ++ ": " ++ path)
1085 ++ " specifies an absolute path, but the "
1086 ++ quote field
1087 ++ " field must use relative paths."
1088 ppExplanation (BadRelativePath field path err) =
1089 quote (field ++ ": " ++ path)
1090 ++ " is not a good relative path: "
1091 ++ show err
1092 ppExplanation (DistPoint mfield path) =
1093 incipit
1094 ++ " points inside the 'dist' "
1095 ++ "directory. This is not reliable because the location of this "
1096 ++ "directory is configurable by the user (or package manager). In "
1097 ++ "addition, the layout of the 'dist' directory is subject to change "
1098 ++ "in future versions of Cabal."
1099 where
1100 -- mfiled Nothing -> the path is inside `ghc-options`
1101 incipit =
1102 maybe
1103 ("'ghc-options' path " ++ quote path)
1104 (\field -> quote (field ++ ": " ++ path))
1105 mfield
1106 ppExplanation (GlobSyntaxError field expl) =
1107 "In the '" ++ field ++ "' field: " ++ expl
1108 ppExplanation (RecursiveGlobInRoot field glob) =
1109 "In the '"
1110 ++ field
1111 ++ "': glob '"
1112 ++ glob
1113 ++ "' starts at project root directory, this might "
1114 ++ "include `.git/`, ``dist-newstyle/``, or other large directories!"
1115 ppExplanation (InvalidOnWin paths) =
1116 "The "
1117 ++ quotes paths
1118 ++ " invalid on Windows, which "
1119 ++ "would cause portability problems for this package. Windows file "
1120 ++ "names cannot contain any of the characters \":*?<>|\" and there "
1121 ++ "a few reserved names including \"aux\", \"nul\", \"con\", "
1122 ++ "\"prn\", \"com1-9\", \"lpt1-9\" and \"clock$\"."
1123 where
1124 quotes [failed] = "path " ++ quote failed ++ " is"
1125 quotes failed =
1126 "paths "
1127 ++ commaSep (map quote failed)
1128 ++ " are"
1129 ppExplanation (FilePathTooLong path) =
1130 "The following file name is too long to store in a portable POSIX "
1131 ++ "format tar archive. The maximum length is 255 ASCII characters.\n"
1132 ++ "The file in question is:\n "
1133 ++ path
1134 ppExplanation (FilePathNameTooLong path) =
1135 "The following file name is too long to store in a portable POSIX "
1136 ++ "format tar archive. The maximum length for the name part (including "
1137 ++ "extension) is 100 ASCII characters. The maximum length for any "
1138 ++ "individual directory component is 155.\n"
1139 ++ "The file in question is:\n "
1140 ++ path
1141 ppExplanation (FilePathSplitTooLong path) =
1142 "The following file name is too long to store in a portable POSIX "
1143 ++ "format tar archive. While the total length is less than 255 ASCII "
1144 ++ "characters, there are unfortunately further restrictions. It has to "
1145 ++ "be possible to split the file path on a directory separator into "
1146 ++ "two parts such that the first part fits in 155 characters or less "
1147 ++ "and the second part fits in 100 characters or less. Basically you "
1148 ++ "have to make the file name or directory names shorter, or you could "
1149 ++ "split a long directory name into nested subdirectories with shorter "
1150 ++ "names.\nThe file in question is:\n "
1151 ++ path
1152 ppExplanation FilePathEmpty =
1153 "Encountered a file with an empty name, something is very wrong! "
1154 ++ "Files with an empty name cannot be stored in a tar archive or in "
1155 ++ "standard file systems."
1156 ppExplanation CVTestSuite =
1157 "The 'test-suite' section is new in Cabal 1.10. "
1158 ++ "Unfortunately it messes up the parser in older Cabal versions "
1159 ++ "so you must specify at least 'cabal-version: >= 1.8', but note "
1160 ++ "that only Cabal 1.10 and later can actually run such test suites."
1161 ppExplanation CVDefaultLanguage =
1162 "To use the 'default-language' field the package needs to specify "
1163 ++ "at least 'cabal-version: >= 1.10'."
1164 ppExplanation CVDefaultLanguageComponent =
1165 "Packages using 'cabal-version: >= 1.10' and before 'cabal-version: 3.4' "
1166 ++ "must specify the 'default-language' field for each component (e.g. "
1167 ++ "Haskell98 or Haskell2010). If a component uses different languages "
1168 ++ "in different modules then list the other ones in the "
1169 ++ "'other-languages' field."
1170 ppExplanation CVDefaultLanguageComponentSoft =
1171 "Without `default-language`, cabal will default to Haskell98, which is "
1172 ++ "probably not what you want. Please add `default-language` to all "
1173 ++ "targets."
1174 ppExplanation CVExtraDocFiles =
1175 "To use the 'extra-doc-files' field the package needs to specify "
1176 ++ "'cabal-version: 1.18' or higher."
1177 ppExplanation CVMultiLib =
1178 "To use multiple 'library' sections or a named library section "
1179 ++ "the package needs to specify at least 'cabal-version: 2.0'."
1180 ppExplanation CVReexported =
1181 "To use the 'reexported-module' field the package needs to specify "
1182 ++ "'cabal-version: 1.22' or higher."
1183 ppExplanation CVMixins =
1184 "To use the 'mixins' field the package needs to specify "
1185 ++ "at least 'cabal-version: 2.0'."
1186 ppExplanation CVExtraFrameworkDirs =
1187 "To use the 'extra-framework-dirs' field the package needs to specify"
1188 ++ " 'cabal-version: 1.24' or higher."
1189 ppExplanation CVDefaultExtensions =
1190 "To use the 'default-extensions' field the package needs to specify "
1191 ++ "at least 'cabal-version: >= 1.10'."
1192 ppExplanation CVExtensionsDeprecated =
1193 "For packages using 'cabal-version: >= 1.10' the 'extensions' "
1194 ++ "field is deprecated. The new 'default-extensions' field lists "
1195 ++ "extensions that are used in all modules in the component, while "
1196 ++ "the 'other-extensions' field lists extensions that are used in "
1197 ++ "some modules, e.g. via the {-# LANGUAGE #-} pragma."
1198 ppExplanation CVSources =
1199 "The use of 'asm-sources', 'cmm-sources', 'extra-bundled-libraries' "
1200 ++ " and 'extra-library-flavours' requires the package "
1201 ++ " to specify at least 'cabal-version: 3.0'."
1202 ppExplanation (CVExtraDynamic flavs) =
1203 "The use of 'extra-dynamic-library-flavours' requires the package "
1204 ++ " to specify at least 'cabal-version: 3.0'. The flavours are: "
1205 ++ commaSep (concat flavs)
1206 ppExplanation CVVirtualModules =
1207 "The use of 'virtual-modules' requires the package "
1208 ++ " to specify at least 'cabal-version: 2.2'."
1209 ppExplanation CVSourceRepository =
1210 "The 'source-repository' section is new in Cabal 1.6. "
1211 ++ "Unfortunately it messes up the parser in earlier Cabal versions "
1212 ++ "so you need to specify 'cabal-version: >= 1.6'."
1213 ppExplanation (CVExtensions version extCab12) =
1214 "Unfortunately the language extensions "
1215 ++ commaSep (map (quote . prettyShow) extCab12)
1216 ++ " break the parser in earlier Cabal versions so you need to "
1217 ++ "specify 'cabal-version: >= "
1218 ++ showCabalSpecVersion version
1219 ++ "'. Alternatively if you require compatibility with earlier "
1220 ++ "Cabal versions then you may be able to use an equivalent "
1221 ++ "compiler-specific flag."
1222 ppExplanation CVCustomSetup =
1223 "Packages using 'cabal-version: 1.24' or higher with 'build-type: Custom' "
1224 ++ "must use a 'custom-setup' section with a 'setup-depends' field "
1225 ++ "that specifies the dependencies of the Setup.hs script itself. "
1226 ++ "The 'setup-depends' field uses the same syntax as 'build-depends', "
1227 ++ "so a simple example would be 'setup-depends: base, Cabal'."
1228 ppExplanation CVExpliticDepsCustomSetup =
1229 "From version 1.24 cabal supports specifying explicit dependencies "
1230 ++ "for Custom setup scripts. Consider using 'cabal-version: 1.24' or "
1231 ++ "higher and adding a 'custom-setup' section with a 'setup-depends' "
1232 ++ "field that specifies the dependencies of the Setup.hs script "
1233 ++ "itself. The 'setup-depends' field uses the same syntax as "
1234 ++ "'build-depends', so a simple example would be 'setup-depends: base, "
1235 ++ "Cabal'."
1236 ppExplanation CVAutogenPaths =
1237 "Packages using 'cabal-version: 2.0' and the autogenerated "
1238 ++ "module Paths_* must include it also on the 'autogen-modules' field "
1239 ++ "besides 'exposed-modules' and 'other-modules'. This specifies that "
1240 ++ "the module does not come with the package and is generated on "
1241 ++ "setup. Modules built with a custom Setup.hs script also go here "
1242 ++ "to ensure that commands like sdist don't fail."
1243 ppExplanation CVAutogenPackageInfo =
1244 "Packages using 'cabal-version: 2.0' and the autogenerated "
1245 ++ "module PackageInfo_* must include it in 'autogen-modules' as well as"
1246 ++ " 'exposed-modules' and 'other-modules'. This specifies that "
1247 ++ "the module does not come with the package and is generated on "
1248 ++ "setup. Modules built with a custom Setup.hs script also go here "
1249 ++ "to ensure that commands like sdist don't fail."
1250 ppExplanation CVAutogenPackageInfoGuard =
1251 "To use the autogenerated module PackageInfo_* you need to specify "
1252 ++ "`cabal-version: 3.12` or higher."
1253 ppExplanation (GlobNoMatch field glob) =
1254 "In '"
1255 ++ field
1256 ++ "': the pattern '"
1257 ++ glob
1258 ++ "' does not"
1259 ++ " match any files."
1260 ppExplanation (GlobExactMatch field glob file) =
1261 "In '"
1262 ++ field
1263 ++ "': the pattern '"
1264 ++ glob
1265 ++ "' does not"
1266 ++ " match the file '"
1267 ++ file
1268 ++ "' because the extensions do not"
1269 ++ " exactly match (e.g., foo.en.html does not exactly match *.html)."
1270 ++ " To enable looser suffix-only matching, set 'cabal-version: 2.4' or"
1271 ++ " higher."
1272 ppExplanation (GlobNoDir field glob dir) =
1273 "In '"
1274 ++ field
1275 ++ "': the pattern '"
1276 ++ glob
1277 ++ "' attempts to"
1278 ++ " match files in the directory '"
1279 ++ dir
1280 ++ "', but there is no"
1281 ++ " directory by that name."
1282 ppExplanation (UnknownOS unknownOSs) =
1283 "Unknown operating system name " ++ commaSep (map quote unknownOSs)
1284 ppExplanation (UnknownArch unknownArches) =
1285 "Unknown architecture name " ++ commaSep (map quote unknownArches)
1286 ppExplanation (UnknownCompiler unknownImpls) =
1287 "Unknown compiler name " ++ commaSep (map quote unknownImpls)
1288 ppExplanation BaseNoUpperBounds =
1289 "The dependency 'build-depends: base' does not specify an upper "
1290 ++ "bound on the version number. Each major release of the 'base' "
1291 ++ "package changes the API in various ways and most packages will "
1292 ++ "need some changes to compile with it. The recommended practice "
1293 ++ "is to specify an upper bound on the version of the 'base' "
1294 ++ "package. This ensures your package will continue to build when a "
1295 ++ "new major version of the 'base' package is released. If you are "
1296 ++ "not sure what upper bound to use then use the next major "
1297 ++ "version. For example if you have tested your package with 'base' "
1298 ++ "version 4.5 and 4.6 then use 'build-depends: base >= 4.5 && < 4.7'."
1299 ppExplanation (MissingUpperBounds ct names) =
1300 let separator = "\n - "
1301 in "On "
1302 ++ ppCET ct
1303 ++ ", "
1304 ++ "these packages miss upper bounds:"
1305 ++ separator
1306 ++ List.intercalate separator names
1307 ++ "\n"
1308 ++ "Please add them. There is more information at https://pvp.haskell.org/"
1309 ppExplanation (SuspiciousFlagName invalidFlagNames) =
1310 "Suspicious flag names: "
1311 ++ unwords invalidFlagNames
1312 ++ ". "
1313 ++ "To avoid ambiguity in command line interfaces, a flag shouldn't "
1314 ++ "start with a dash. Also for better compatibility, flag names "
1315 ++ "shouldn't contain non-ascii characters."
1316 ppExplanation (DeclaredUsedFlags declared used) =
1317 "Declared and used flag sets differ: "
1318 ++ s declared
1319 ++ " /= "
1320 ++ s used
1321 ++ ". "
1322 where
1323 s :: Set.Set FlagName -> String
1324 s = commaSep . map unFlagName . Set.toList
1325 ppExplanation (NonASCIICustomField nonAsciiXFields) =
1326 "Non ascii custom fields: "
1327 ++ unwords nonAsciiXFields
1328 ++ ". "
1329 ++ "For better compatibility, custom field names "
1330 ++ "shouldn't contain non-ascii characters."
1331 ppExplanation RebindableClashPaths =
1332 "Packages using RebindableSyntax with OverloadedStrings or"
1333 ++ " OverloadedLists in default-extensions, in conjunction with the"
1334 ++ " autogenerated module Paths_*, are known to cause compile failures"
1335 ++ " with Cabal < 2.2. To use these default-extensions with a Paths_*"
1336 ++ " autogen module, specify at least 'cabal-version: 2.2'."
1337 ppExplanation RebindableClashPackageInfo =
1338 "Packages using RebindableSyntax with OverloadedStrings or"
1339 ++ " OverloadedLists in default-extensions, in conjunction with the"
1340 ++ " autogenerated module PackageInfo_*, are known to cause compile failures"
1341 ++ " with Cabal < 2.2. To use these default-extensions with a PackageInfo_*"
1342 ++ " autogen module, specify at least 'cabal-version: 2.2'."
1343 ppExplanation (WErrorUnneeded fieldName) =
1344 addConditionalExp $
1346 ++ fieldName
1347 ++ ": -Werror' makes the package easy to "
1348 ++ "break with future GHC versions because new GHC versions often "
1349 ++ "add new warnings."
1350 ppExplanation (JUnneeded fieldName) =
1351 addConditionalExp $
1353 ++ fieldName
1354 ++ ": -j[N]' can make sense for a particular user's setup,"
1355 ++ " but it is not appropriate for a distributed package."
1356 ppExplanation (FDeferTypeErrorsUnneeded fieldName) =
1357 addConditionalExp $
1359 ++ fieldName
1360 ++ ": -fdefer-type-errors' is fine during development "
1361 ++ "but is not appropriate for a distributed package."
1362 ppExplanation (DynamicUnneeded fieldName) =
1363 addConditionalExp $
1365 ++ fieldName
1366 ++ ": -d*' debug flags are not appropriate "
1367 ++ "for a distributed package."
1368 ppExplanation (ProfilingUnneeded fieldName) =
1369 addConditionalExp $
1371 ++ fieldName
1372 ++ ": -fprof*' profiling flags are typically not "
1373 ++ "appropriate for a distributed library package. These flags are "
1374 ++ "useful to profile this package, but when profiling other packages "
1375 ++ "that use this one these flags clutter the profile output with "
1376 ++ "excessive detail. If you think other packages really want to see "
1377 ++ "cost centres from this package then use '-fprof-auto-exported' "
1378 ++ "which puts cost centres only on exported functions."
1379 ppExplanation (UpperBoundSetup nm) =
1380 "The dependency 'setup-depends: '"
1381 ++ nm
1382 ++ "' does not specify an "
1383 ++ "upper bound on the version number. Each major release of the "
1384 ++ "'"
1385 ++ nm
1386 ++ "' package changes the API in various ways and most "
1387 ++ "packages will need some changes to compile with it. If you are "
1388 ++ "not sure what upper bound to use then use the next major "
1389 ++ "version."
1390 ppExplanation (DuplicateModule s dupLibsLax) =
1391 "Duplicate modules in "
1392 ++ s
1393 ++ ": "
1394 ++ commaSep (map prettyShow dupLibsLax)
1395 ppExplanation (PotentialDupModule s dupLibsStrict) =
1396 "Potential duplicate modules (subject to conditionals) in "
1397 ++ s
1398 ++ ": "
1399 ++ commaSep (map prettyShow dupLibsStrict)
1400 ppExplanation (BOMStart pdfile) =
1401 pdfile
1402 ++ " starts with an Unicode byte order mark (BOM)."
1403 ++ " This may cause problems with older cabal versions."
1404 ppExplanation (NotPackageName pdfile expectedCabalname) =
1405 "The filename "
1406 ++ quote pdfile
1407 ++ " does not match package name "
1408 ++ "(expected: "
1409 ++ quote expectedCabalname
1410 ++ ")"
1411 ppExplanation NoDesc =
1412 "No cabal file found.\n"
1413 ++ "Please create a package description file <pkgname>.cabal"
1414 ppExplanation (MultiDesc multiple) =
1415 "Multiple cabal files found while checking.\n"
1416 ++ "Please use only one of: "
1417 ++ commaSep multiple
1418 ppExplanation (UnknownFile fieldname file) =
1419 "The '"
1420 ++ fieldname
1421 ++ "' field refers to the file "
1422 ++ quote (getSymbolicPath file)
1423 ++ " which does not exist."
1424 ppExplanation MissingSetupFile =
1425 "The package is missing a Setup.hs or Setup.lhs script."
1426 ppExplanation MissingConfigureScript =
1427 "The 'build-type' is 'Configure' but there is no 'configure' script. "
1428 ++ "You probably need to run 'autoreconf -i' to generate it."
1429 ppExplanation (UnknownDirectory kind dir) =
1430 quote (kind ++ ": " ++ dir)
1431 ++ " specifies a directory which does not exist."
1432 ppExplanation MissingSourceControl =
1433 "When distributing packages, it is encouraged to specify source "
1434 ++ "control information in the .cabal file using one or more "
1435 ++ "'source-repository' sections. See the Cabal user guide for "
1436 ++ "details."
1437 ppExplanation (MissingExpectedDocFiles extraDocFileSupport paths) =
1438 "Please consider including the "
1439 ++ quotes paths
1440 ++ " in the '"
1441 ++ targetField
1442 ++ "' section of the .cabal file "
1443 ++ "if it contains useful information for users of the package."
1444 where
1445 quotes [p] = "file " ++ quote p
1446 quotes ps = "files " ++ commaSep (map quote ps)
1447 targetField =
1448 if extraDocFileSupport
1449 then "extra-doc-files"
1450 else "extra-source-files"
1451 ppExplanation (WrongFieldForExpectedDocFiles extraDocFileSupport field paths) =
1452 "Please consider moving the "
1453 ++ quotes paths
1454 ++ " from the '"
1455 ++ field
1456 ++ "' section of the .cabal file "
1457 ++ "to the section '"
1458 ++ targetField
1459 ++ "'."
1460 where
1461 quotes [p] = "file " ++ quote p
1462 quotes ps = "files " ++ commaSep (map quote ps)
1463 targetField =
1464 if extraDocFileSupport
1465 then "extra-doc-files"
1466 else "extra-source-files"
1468 -- * Formatting utilities
1470 commaSep :: [String] -> String
1471 commaSep = List.intercalate ", "
1473 quote :: String -> String
1474 quote s = "'" ++ s ++ "'"
1476 addConditionalExp :: String -> String
1477 addConditionalExp expl =
1478 expl
1479 ++ " Alternatively, if you want to use this, make it conditional based "
1480 ++ "on a Cabal configuration flag (with 'manual: True' and 'default: "
1481 ++ "False') and enable that flag during development."