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