Add “Ignore warning” option to cabal check
[cabal.git] / Cabal / src / Distribution / PackageDescription / Check / Warning.hs
blobf7a048f7913a9e255ba00025424118f6a66b8011
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 | CVExtraDocFiles
237 | CVMultiLib
238 | CVReexported
239 | CVMixins
240 | CVExtraFrameworkDirs
241 | CVDefaultExtensions
242 | CVExtensionsDeprecated
243 | CVSources
244 | CVExtraDynamic [[String]]
245 | CVVirtualModules
246 | CVSourceRepository
247 | CVExtensions CabalSpecVersion [Extension]
248 | CVCustomSetup
249 | CVExpliticDepsCustomSetup
250 | CVAutogenPaths
251 | CVAutogenPackageInfo
252 | CVAutogenPackageInfoGuard
253 | GlobNoMatch String String
254 | GlobExactMatch String String FilePath
255 | GlobNoDir String String FilePath
256 | UnknownOS [String]
257 | UnknownArch [String]
258 | UnknownCompiler [String]
259 | BaseNoUpperBounds
260 | MissingUpperBounds CEType [String]
261 | SuspiciousFlagName [String]
262 | DeclaredUsedFlags (Set.Set FlagName) (Set.Set FlagName)
263 | NonASCIICustomField [String]
264 | RebindableClashPaths
265 | RebindableClashPackageInfo
266 | WErrorUnneeded String
267 | JUnneeded String
268 | FDeferTypeErrorsUnneeded String
269 | DynamicUnneeded String
270 | ProfilingUnneeded String
271 | UpperBoundSetup String
272 | DuplicateModule String [ModuleName]
273 | PotentialDupModule String [ModuleName]
274 | BOMStart FilePath
275 | NotPackageName FilePath String
276 | NoDesc
277 | MultiDesc [String]
278 | UnknownFile String (SymbolicPath PackageDir LicenseFile)
279 | MissingSetupFile
280 | MissingConfigureScript
281 | UnknownDirectory String FilePath
282 | MissingSourceControl
283 | MissingExpectedDocFiles Bool [FilePath]
284 | WrongFieldForExpectedDocFiles Bool String [FilePath]
285 deriving (Eq, Ord, Show)
287 -- TODO Some checks have a constructor in list form
288 -- (e.g. `SomeWarn [n]`), CheckM m () correctly catches warnings in
289 -- different stanzas in different checks (so it is not one soup).
291 -- Ideally [SomeWar [a], SomeWar [b]] would be translated into
292 -- SomeWar [a,b] in the few cases where it is appropriate for UX
293 -- and left separated otherwise.
294 -- To achieve this the Writer part of CheckM could be modified
295 -- to be a ad hoc monoid.
297 -- Convenience.
298 extractCheckExplantion :: PackageCheck -> CheckExplanation
299 extractCheckExplantion (PackageBuildImpossible e) = e
300 extractCheckExplantion (PackageBuildWarning e) = e
301 extractCheckExplantion (PackageDistSuspicious e) = e
302 extractCheckExplantion (PackageDistSuspiciousWarn e) = e
303 extractCheckExplantion (PackageDistInexcusable e) = e
305 -- | Identifier for the speficic 'CheckExplanation'. This ensures `--ignore`
306 -- can output a warning on unrecognised values.
307 -- ☞ N.B.: should be kept in sync with 'CheckExplanation'.
308 data CheckExplanationID
309 = CIParseWarning
310 | CINoNameField
311 | CINoVersionField
312 | CINoTarget
313 | CIUnnamedInternal
314 | CIDuplicateSections
315 | CIIllegalLibraryName
316 | CINoModulesExposed
317 | CISignaturesCabal2
318 | CIAutogenNotExposed
319 | CIAutogenIncludesNotIncluded
320 | CINoMainIs
321 | CINoHsLhsMain
322 | CIMainCCabal1_18
323 | CIAutogenNoOther
324 | CIAutogenIncludesNotIncludedExe
325 | CITestsuiteTypeNotKnown
326 | CITestsuiteNotSupported
327 | CIBenchmarkTypeNotKnown
328 | CIBenchmarkNotSupported
329 | CINoHsLhsMainBench
330 | CIInvalidNameWin
331 | CIZPrefix
332 | CINoBuildType
333 | CINoCustomSetup
334 | CIUnknownCompilers
335 | CIUnknownLanguages
336 | CIUnknownExtensions
337 | CILanguagesAsExtension
338 | CIDeprecatedExtensions
339 | CIMissingFieldCategory
340 | CIMissingFieldMaintainer
341 | CIMissingFieldSynopsis
342 | CIMissingFieldDescription
343 | CIMissingFieldSynOrDesc
344 | CISynopsisTooLong
345 | CIShortDesc
346 | CIInvalidTestWith
347 | CIImpossibleInternalDep
348 | CIImpossibleInternalExe
349 | CIMissingInternalExe
350 | CINONELicense
351 | CINoLicense
352 | CIAllRightsReservedLicense
353 | CILicenseMessParse
354 | CIUnrecognisedLicense
355 | CIUncommonBSD4
356 | CIUnknownLicenseVersion
357 | CINoLicenseFile
358 | CIUnrecognisedSourceRepo
359 | CIMissingType
360 | CIMissingLocation
361 | CIMissingModule
362 | CIMissingTag
363 | CISubdirRelPath
364 | CISubdirGoodRelPath
365 | CIOptFasm
366 | CIOptHpc
367 | CIOptProf
368 | CIOptO
369 | CIOptHide
370 | CIOptMake
371 | CIOptONot
372 | CIOptOOne
373 | CIOptOTwo
374 | CIOptSplitSections
375 | CIOptSplitObjs
376 | CIOptWls
377 | CIOptExts
378 | CIOptRts
379 | CIOptWithRts
380 | CICOptONumber
381 | CICOptCPP
382 | CIOptAlternatives
383 | CIRelativeOutside
384 | CIAbsolutePath
385 | CIBadRelativePath
386 | CIDistPoint
387 | CIGlobSyntaxError
388 | CIRecursiveGlobInRoot
389 | CIInvalidOnWin
390 | CIFilePathTooLong
391 | CIFilePathNameTooLong
392 | CIFilePathSplitTooLong
393 | CIFilePathEmpty
394 | CICVTestSuite
395 | CICVDefaultLanguage
396 | CICVDefaultLanguageComponent
397 | CICVExtraDocFiles
398 | CICVMultiLib
399 | CICVReexported
400 | CICVMixins
401 | CICVExtraFrameworkDirs
402 | CICVDefaultExtensions
403 | CICVExtensionsDeprecated
404 | CICVSources
405 | CICVExtraDynamic
406 | CICVVirtualModules
407 | CICVSourceRepository
408 | CICVExtensions
409 | CICVCustomSetup
410 | CICVExpliticDepsCustomSetup
411 | CICVAutogenPaths
412 | CICVAutogenPackageInfo
413 | CICVAutogenPackageInfoGuard
414 | CIGlobNoMatch
415 | CIGlobExactMatch
416 | CIGlobNoDir
417 | CIUnknownOS
418 | CIUnknownArch
419 | CIUnknownCompiler
420 | CIBaseNoUpperBounds
421 | CIMissingUpperBounds
422 | CISuspiciousFlagName
423 | CIDeclaredUsedFlags
424 | CINonASCIICustomField
425 | CIRebindableClashPaths
426 | CIRebindableClashPackageInfo
427 | CIWErrorUnneeded
428 | CIJUnneeded
429 | CIFDeferTypeErrorsUnneeded
430 | CIDynamicUnneeded
431 | CIProfilingUnneeded
432 | CIUpperBoundSetup
433 | CIDuplicateModule
434 | CIPotentialDupModule
435 | CIBOMStart
436 | CINotPackageName
437 | CINoDesc
438 | CIMultiDesc
439 | CIUnknownFile
440 | CIMissingSetupFile
441 | CIMissingConfigureScript
442 | CIUnknownDirectory
443 | CIMissingSourceControl
444 | CIMissingExpectedDocFiles
445 | CIWrongFieldForExpectedDocFiles
446 deriving (Eq, Ord, Show, Enum, Bounded)
448 checkExplanationId :: CheckExplanation -> CheckExplanationID
449 checkExplanationId (ParseWarning{}) = CIParseWarning
450 checkExplanationId (NoNameField{}) = CINoNameField
451 checkExplanationId (NoVersionField{}) = CINoVersionField
452 checkExplanationId (NoTarget{}) = CINoTarget
453 checkExplanationId (UnnamedInternal{}) = CIUnnamedInternal
454 checkExplanationId (DuplicateSections{}) = CIDuplicateSections
455 checkExplanationId (IllegalLibraryName{}) = CIIllegalLibraryName
456 checkExplanationId (NoModulesExposed{}) = CINoModulesExposed
457 checkExplanationId (SignaturesCabal2{}) = CISignaturesCabal2
458 checkExplanationId (AutogenNotExposed{}) = CIAutogenNotExposed
459 checkExplanationId (AutogenIncludesNotIncluded{}) = CIAutogenIncludesNotIncluded
460 checkExplanationId (NoMainIs{}) = CINoMainIs
461 checkExplanationId (NoHsLhsMain{}) = CINoHsLhsMain
462 checkExplanationId (MainCCabal1_18{}) = CIMainCCabal1_18
463 checkExplanationId (AutogenNoOther{}) = CIAutogenNoOther
464 checkExplanationId (AutogenIncludesNotIncludedExe{}) = CIAutogenIncludesNotIncludedExe
465 checkExplanationId (TestsuiteTypeNotKnown{}) = CITestsuiteTypeNotKnown
466 checkExplanationId (TestsuiteNotSupported{}) = CITestsuiteNotSupported
467 checkExplanationId (BenchmarkTypeNotKnown{}) = CIBenchmarkTypeNotKnown
468 checkExplanationId (BenchmarkNotSupported{}) = CIBenchmarkNotSupported
469 checkExplanationId (NoHsLhsMainBench{}) = CINoHsLhsMainBench
470 checkExplanationId (InvalidNameWin{}) = CIInvalidNameWin
471 checkExplanationId (ZPrefix{}) = CIZPrefix
472 checkExplanationId (NoBuildType{}) = CINoBuildType
473 checkExplanationId (NoCustomSetup{}) = CINoCustomSetup
474 checkExplanationId (UnknownCompilers{}) = CIUnknownCompilers
475 checkExplanationId (UnknownLanguages{}) = CIUnknownLanguages
476 checkExplanationId (UnknownExtensions{}) = CIUnknownExtensions
477 checkExplanationId (LanguagesAsExtension{}) = CILanguagesAsExtension
478 checkExplanationId (DeprecatedExtensions{}) = CIDeprecatedExtensions
479 checkExplanationId (MissingFieldCategory{}) = CIMissingFieldCategory
480 checkExplanationId (MissingFieldMaintainer{}) = CIMissingFieldMaintainer
481 checkExplanationId (MissingFieldSynopsis{}) = CIMissingFieldSynopsis
482 checkExplanationId (MissingFieldDescription{}) = CIMissingFieldDescription
483 checkExplanationId (MissingFieldSynOrDesc{}) = CIMissingFieldSynOrDesc
484 checkExplanationId (SynopsisTooLong{}) = CISynopsisTooLong
485 checkExplanationId (ShortDesc{}) = CIShortDesc
486 checkExplanationId (InvalidTestWith{}) = CIInvalidTestWith
487 checkExplanationId (ImpossibleInternalDep{}) = CIImpossibleInternalDep
488 checkExplanationId (ImpossibleInternalExe{}) = CIImpossibleInternalExe
489 checkExplanationId (MissingInternalExe{}) = CIMissingInternalExe
490 checkExplanationId (NONELicense{}) = CINONELicense
491 checkExplanationId (NoLicense{}) = CINoLicense
492 checkExplanationId (AllRightsReservedLicense{}) = CIAllRightsReservedLicense
493 checkExplanationId (LicenseMessParse{}) = CILicenseMessParse
494 checkExplanationId (UnrecognisedLicense{}) = CIUnrecognisedLicense
495 checkExplanationId (UncommonBSD4{}) = CIUncommonBSD4
496 checkExplanationId (UnknownLicenseVersion{}) = CIUnknownLicenseVersion
497 checkExplanationId (NoLicenseFile{}) = CINoLicenseFile
498 checkExplanationId (UnrecognisedSourceRepo{}) = CIUnrecognisedSourceRepo
499 checkExplanationId (MissingType{}) = CIMissingType
500 checkExplanationId (MissingLocation{}) = CIMissingLocation
501 checkExplanationId (MissingModule{}) = CIMissingModule
502 checkExplanationId (MissingTag{}) = CIMissingTag
503 checkExplanationId (SubdirRelPath{}) = CISubdirRelPath
504 checkExplanationId (SubdirGoodRelPath{}) = CISubdirGoodRelPath
505 checkExplanationId (OptFasm{}) = CIOptFasm
506 checkExplanationId (OptHpc{}) = CIOptHpc
507 checkExplanationId (OptProf{}) = CIOptProf
508 checkExplanationId (OptO{}) = CIOptO
509 checkExplanationId (OptHide{}) = CIOptHide
510 checkExplanationId (OptMake{}) = CIOptMake
511 checkExplanationId (OptONot{}) = CIOptONot
512 checkExplanationId (OptOOne{}) = CIOptOOne
513 checkExplanationId (OptOTwo{}) = CIOptOTwo
514 checkExplanationId (OptSplitSections{}) = CIOptSplitSections
515 checkExplanationId (OptSplitObjs{}) = CIOptSplitObjs
516 checkExplanationId (OptWls{}) = CIOptWls
517 checkExplanationId (OptExts{}) = CIOptExts
518 checkExplanationId (OptRts{}) = CIOptRts
519 checkExplanationId (OptWithRts{}) = CIOptWithRts
520 checkExplanationId (COptONumber{}) = CICOptONumber
521 checkExplanationId (COptCPP{}) = CICOptCPP
522 checkExplanationId (OptAlternatives{}) = CIOptAlternatives
523 checkExplanationId (RelativeOutside{}) = CIRelativeOutside
524 checkExplanationId (AbsolutePath{}) = CIAbsolutePath
525 checkExplanationId (BadRelativePath{}) = CIBadRelativePath
526 checkExplanationId (DistPoint{}) = CIDistPoint
527 checkExplanationId (GlobSyntaxError{}) = CIGlobSyntaxError
528 checkExplanationId (RecursiveGlobInRoot{}) = CIRecursiveGlobInRoot
529 checkExplanationId (InvalidOnWin{}) = CIInvalidOnWin
530 checkExplanationId (FilePathTooLong{}) = CIFilePathTooLong
531 checkExplanationId (FilePathNameTooLong{}) = CIFilePathNameTooLong
532 checkExplanationId (FilePathSplitTooLong{}) = CIFilePathSplitTooLong
533 checkExplanationId (FilePathEmpty{}) = CIFilePathEmpty
534 checkExplanationId (CVTestSuite{}) = CICVTestSuite
535 checkExplanationId (CVDefaultLanguage{}) = CICVDefaultLanguage
536 checkExplanationId (CVDefaultLanguageComponent{}) = CICVDefaultLanguageComponent
537 checkExplanationId (CVExtraDocFiles{}) = CICVExtraDocFiles
538 checkExplanationId (CVMultiLib{}) = CICVMultiLib
539 checkExplanationId (CVReexported{}) = CICVReexported
540 checkExplanationId (CVMixins{}) = CICVMixins
541 checkExplanationId (CVExtraFrameworkDirs{}) = CICVExtraFrameworkDirs
542 checkExplanationId (CVDefaultExtensions{}) = CICVDefaultExtensions
543 checkExplanationId (CVExtensionsDeprecated{}) = CICVExtensionsDeprecated
544 checkExplanationId (CVSources{}) = CICVSources
545 checkExplanationId (CVExtraDynamic{}) = CICVExtraDynamic
546 checkExplanationId (CVVirtualModules{}) = CICVVirtualModules
547 checkExplanationId (CVSourceRepository{}) = CICVSourceRepository
548 checkExplanationId (CVExtensions{}) = CICVExtensions
549 checkExplanationId (CVCustomSetup{}) = CICVCustomSetup
550 checkExplanationId (CVExpliticDepsCustomSetup{}) = CICVExpliticDepsCustomSetup
551 checkExplanationId (CVAutogenPaths{}) = CICVAutogenPaths
552 checkExplanationId (CVAutogenPackageInfo{}) = CICVAutogenPackageInfo
553 checkExplanationId (CVAutogenPackageInfoGuard{}) = CICVAutogenPackageInfoGuard
554 checkExplanationId (GlobNoMatch{}) = CIGlobNoMatch
555 checkExplanationId (GlobExactMatch{}) = CIGlobExactMatch
556 checkExplanationId (GlobNoDir{}) = CIGlobNoDir
557 checkExplanationId (UnknownOS{}) = CIUnknownOS
558 checkExplanationId (UnknownArch{}) = CIUnknownArch
559 checkExplanationId (UnknownCompiler{}) = CIUnknownCompiler
560 checkExplanationId (BaseNoUpperBounds{}) = CIBaseNoUpperBounds
561 checkExplanationId (MissingUpperBounds{}) = CIMissingUpperBounds
562 checkExplanationId (SuspiciousFlagName{}) = CISuspiciousFlagName
563 checkExplanationId (DeclaredUsedFlags{}) = CIDeclaredUsedFlags
564 checkExplanationId (NonASCIICustomField{}) = CINonASCIICustomField
565 checkExplanationId (RebindableClashPaths{}) = CIRebindableClashPaths
566 checkExplanationId (RebindableClashPackageInfo{}) = CIRebindableClashPackageInfo
567 checkExplanationId (WErrorUnneeded{}) = CIWErrorUnneeded
568 checkExplanationId (JUnneeded{}) = CIJUnneeded
569 checkExplanationId (FDeferTypeErrorsUnneeded{}) = CIFDeferTypeErrorsUnneeded
570 checkExplanationId (DynamicUnneeded{}) = CIDynamicUnneeded
571 checkExplanationId (ProfilingUnneeded{}) = CIProfilingUnneeded
572 checkExplanationId (UpperBoundSetup{}) = CIUpperBoundSetup
573 checkExplanationId (DuplicateModule{}) = CIDuplicateModule
574 checkExplanationId (PotentialDupModule{}) = CIPotentialDupModule
575 checkExplanationId (BOMStart{}) = CIBOMStart
576 checkExplanationId (NotPackageName{}) = CINotPackageName
577 checkExplanationId (NoDesc{}) = CINoDesc
578 checkExplanationId (MultiDesc{}) = CIMultiDesc
579 checkExplanationId (UnknownFile{}) = CIUnknownFile
580 checkExplanationId (MissingSetupFile{}) = CIMissingSetupFile
581 checkExplanationId (MissingConfigureScript{}) = CIMissingConfigureScript
582 checkExplanationId (UnknownDirectory{}) = CIUnknownDirectory
583 checkExplanationId (MissingSourceControl{}) = CIMissingSourceControl
584 checkExplanationId (MissingExpectedDocFiles{}) = CIMissingExpectedDocFiles
585 checkExplanationId (WrongFieldForExpectedDocFiles{}) = CIWrongFieldForExpectedDocFiles
587 type CheckExplanationIDString = String
589 -- A one-word identifier for each CheckExplanation
591 -- ☞ N.B: if you modify anything here, remeber to change the documentation
592 -- in @doc/cabal-commands.rst@!
593 ppCheckExplanationId :: CheckExplanationID -> CheckExplanationIDString
594 ppCheckExplanationId CIParseWarning = "parser-warning"
595 ppCheckExplanationId CINoNameField = "no-name-field"
596 ppCheckExplanationId CINoVersionField = "no-version-field"
597 ppCheckExplanationId CINoTarget = "no-target"
598 ppCheckExplanationId CIUnnamedInternal = "unnamed-internal-library"
599 ppCheckExplanationId CIDuplicateSections = "duplicate-sections"
600 ppCheckExplanationId CIIllegalLibraryName = "illegal-library-name"
601 ppCheckExplanationId CINoModulesExposed = "no-modules-exposed"
602 ppCheckExplanationId CISignaturesCabal2 = "signatures"
603 ppCheckExplanationId CIAutogenNotExposed = "autogen-not-exposed"
604 ppCheckExplanationId CIAutogenIncludesNotIncluded = "autogen-not-included"
605 ppCheckExplanationId CINoMainIs = "no-main-is"
606 ppCheckExplanationId CINoHsLhsMain = "unknown-extension-main"
607 ppCheckExplanationId CIMainCCabal1_18 = "c-like-main"
608 ppCheckExplanationId CIAutogenNoOther = "autogen-other-modules"
609 ppCheckExplanationId CIAutogenIncludesNotIncludedExe = "autogen-exe"
610 ppCheckExplanationId CITestsuiteTypeNotKnown = "unknown-testsuite-type"
611 ppCheckExplanationId CITestsuiteNotSupported = "unsupported-testsuite"
612 ppCheckExplanationId CIBenchmarkTypeNotKnown = "unknown-bench"
613 ppCheckExplanationId CIBenchmarkNotSupported = "unsupported-bench"
614 ppCheckExplanationId CINoHsLhsMainBench = "bench-unknown-extension"
615 ppCheckExplanationId CIInvalidNameWin = "invalid-name-win"
616 ppCheckExplanationId CIZPrefix = "reserved-z-prefix"
617 ppCheckExplanationId CINoBuildType = "no-build-type"
618 ppCheckExplanationId CINoCustomSetup = "undeclared-custom-setup"
619 ppCheckExplanationId CIUnknownCompilers = "unknown-compiler-tested"
620 ppCheckExplanationId CIUnknownLanguages = "unknown-languages"
621 ppCheckExplanationId CIUnknownExtensions = "unknown-extension"
622 ppCheckExplanationId CILanguagesAsExtension = "languages-as-extensions"
623 ppCheckExplanationId CIDeprecatedExtensions = "deprecated-extensions"
624 ppCheckExplanationId CIMissingFieldCategory = "no-category"
625 ppCheckExplanationId CIMissingFieldMaintainer = "no-maintainer"
626 ppCheckExplanationId CIMissingFieldSynopsis = "no-synopsis"
627 ppCheckExplanationId CIMissingFieldDescription = "no-description"
628 ppCheckExplanationId CIMissingFieldSynOrDesc = "no-syn-desc"
629 ppCheckExplanationId CISynopsisTooLong = "long-synopsis"
630 ppCheckExplanationId CIShortDesc = "short-description"
631 ppCheckExplanationId CIInvalidTestWith = "invalid-range-tested"
632 ppCheckExplanationId CIImpossibleInternalDep = "impossible-dep"
633 ppCheckExplanationId CIImpossibleInternalExe = "impossible-dep-exe"
634 ppCheckExplanationId CIMissingInternalExe = "no-internal-exe"
635 ppCheckExplanationId CINONELicense = "license-none"
636 ppCheckExplanationId CINoLicense = "no-license"
637 ppCheckExplanationId CIAllRightsReservedLicense = "all-rights-reserved"
638 ppCheckExplanationId CILicenseMessParse = "license-parse"
639 ppCheckExplanationId CIUnrecognisedLicense = "unknown-license"
640 ppCheckExplanationId CIUncommonBSD4 = "bsd4-license"
641 ppCheckExplanationId CIUnknownLicenseVersion = "unknown-license-version"
642 ppCheckExplanationId CINoLicenseFile = "no-license-file"
643 ppCheckExplanationId CIUnrecognisedSourceRepo = "unrecognised-repo-type"
644 ppCheckExplanationId CIMissingType = "repo-no-type"
645 ppCheckExplanationId CIMissingLocation = "repo-no-location"
646 ppCheckExplanationId CIMissingModule = "repo-no-module"
647 ppCheckExplanationId CIMissingTag = "repo-no-tag"
648 ppCheckExplanationId CISubdirRelPath = "repo-relative-dir"
649 ppCheckExplanationId CISubdirGoodRelPath = "repo-malformed-subdir"
650 ppCheckExplanationId CIOptFasm = "option-fasm"
651 ppCheckExplanationId CIOptHpc = "option-fhpc"
652 ppCheckExplanationId CIOptProf = "option-prof"
653 ppCheckExplanationId CIOptO = "option-o"
654 ppCheckExplanationId CIOptHide = "option-hide-package"
655 ppCheckExplanationId CIOptMake = "option-make"
656 ppCheckExplanationId CIOptONot = "option-optimize"
657 ppCheckExplanationId CIOptOOne = "option-o1"
658 ppCheckExplanationId CIOptOTwo = "option-o2"
659 ppCheckExplanationId CIOptSplitSections = "option-split-section"
660 ppCheckExplanationId CIOptSplitObjs = "option-split-objs"
661 ppCheckExplanationId CIOptWls = "option-optl-wl"
662 ppCheckExplanationId CIOptExts = "use-extension"
663 ppCheckExplanationId CIOptRts = "option-rtsopts"
664 ppCheckExplanationId CIOptWithRts = "option-with-rtsopts"
665 ppCheckExplanationId CICOptONumber = "option-opt-c"
666 ppCheckExplanationId CICOptCPP = "cpp-options"
667 ppCheckExplanationId CIOptAlternatives = "misplaced-c-opt"
668 ppCheckExplanationId CIRelativeOutside = "relative-path-outside"
669 ppCheckExplanationId CIAbsolutePath = "absolute-path"
670 ppCheckExplanationId CIBadRelativePath = "malformed-relative-path"
671 ppCheckExplanationId CIDistPoint = "unreliable-dist-path"
672 ppCheckExplanationId CIGlobSyntaxError = "glob-syntax-error"
673 ppCheckExplanationId CIRecursiveGlobInRoot = "recursive-glob"
674 ppCheckExplanationId CIInvalidOnWin = "invalid-path-win"
675 ppCheckExplanationId CIFilePathTooLong = "long-path"
676 ppCheckExplanationId CIFilePathNameTooLong = "long-name"
677 ppCheckExplanationId CIFilePathSplitTooLong = "name-not-portable"
678 ppCheckExplanationId CIFilePathEmpty = "empty-path"
679 ppCheckExplanationId CICVTestSuite = "test-cabal-ver"
680 ppCheckExplanationId CICVDefaultLanguage = "default-language"
681 ppCheckExplanationId CICVDefaultLanguageComponent = "no-default-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 ++ "a few reserved names including \"aux\", \"nul\", \"con\", "
1118 ++ "\"prn\", \"com1-9\", \"lpt1-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 CVExtraDocFiles =
1167 "To use the 'extra-doc-files' field the package needs to specify "
1168 ++ "'cabal-version: 1.18' or higher."
1169 ppExplanation CVMultiLib =
1170 "To use multiple 'library' sections or a named library section "
1171 ++ "the package needs to specify at least 'cabal-version: 2.0'."
1172 ppExplanation CVReexported =
1173 "To use the 'reexported-module' field the package needs to specify "
1174 ++ "'cabal-version: 1.22' or higher."
1175 ppExplanation CVMixins =
1176 "To use the 'mixins' field the package needs to specify "
1177 ++ "at least 'cabal-version: 2.0'."
1178 ppExplanation CVExtraFrameworkDirs =
1179 "To use the 'extra-framework-dirs' field the package needs to specify"
1180 ++ " 'cabal-version: 1.24' or higher."
1181 ppExplanation CVDefaultExtensions =
1182 "To use the 'default-extensions' field the package needs to specify "
1183 ++ "at least 'cabal-version: >= 1.10'."
1184 ppExplanation CVExtensionsDeprecated =
1185 "For packages using 'cabal-version: >= 1.10' the 'extensions' "
1186 ++ "field is deprecated. The new 'default-extensions' field lists "
1187 ++ "extensions that are used in all modules in the component, while "
1188 ++ "the 'other-extensions' field lists extensions that are used in "
1189 ++ "some modules, e.g. via the {-# LANGUAGE #-} pragma."
1190 ppExplanation CVSources =
1191 "The use of 'asm-sources', 'cmm-sources', 'extra-bundled-libraries' "
1192 ++ " and 'extra-library-flavours' requires the package "
1193 ++ " to specify at least 'cabal-version: 3.0'."
1194 ppExplanation (CVExtraDynamic flavs) =
1195 "The use of 'extra-dynamic-library-flavours' requires the package "
1196 ++ " to specify at least 'cabal-version: 3.0'. The flavours are: "
1197 ++ commaSep (concat flavs)
1198 ppExplanation CVVirtualModules =
1199 "The use of 'virtual-modules' requires the package "
1200 ++ " to specify at least 'cabal-version: 2.2'."
1201 ppExplanation CVSourceRepository =
1202 "The 'source-repository' section is new in Cabal 1.6. "
1203 ++ "Unfortunately it messes up the parser in earlier Cabal versions "
1204 ++ "so you need to specify 'cabal-version: >= 1.6'."
1205 ppExplanation (CVExtensions version extCab12) =
1206 "Unfortunately the language extensions "
1207 ++ commaSep (map (quote . prettyShow) extCab12)
1208 ++ " break the parser in earlier Cabal versions so you need to "
1209 ++ "specify 'cabal-version: >= "
1210 ++ showCabalSpecVersion version
1211 ++ "'. Alternatively if you require compatibility with earlier "
1212 ++ "Cabal versions then you may be able to use an equivalent "
1213 ++ "compiler-specific flag."
1214 ppExplanation CVCustomSetup =
1215 "Packages using 'cabal-version: 1.24' or higher with 'build-type: Custom' "
1216 ++ "must use a 'custom-setup' section with a 'setup-depends' field "
1217 ++ "that specifies the dependencies of the Setup.hs script itself. "
1218 ++ "The 'setup-depends' field uses the same syntax as 'build-depends', "
1219 ++ "so a simple example would be 'setup-depends: base, Cabal'."
1220 ppExplanation CVExpliticDepsCustomSetup =
1221 "From version 1.24 cabal supports specifying explicit dependencies "
1222 ++ "for Custom setup scripts. Consider using 'cabal-version: 1.24' or "
1223 ++ "higher and adding a 'custom-setup' section with a 'setup-depends' "
1224 ++ "field that specifies the dependencies of the Setup.hs script "
1225 ++ "itself. The 'setup-depends' field uses the same syntax as "
1226 ++ "'build-depends', so a simple example would be 'setup-depends: base, "
1227 ++ "Cabal'."
1228 ppExplanation CVAutogenPaths =
1229 "Packages using 'cabal-version: 2.0' and the autogenerated "
1230 ++ "module Paths_* must include it also on the 'autogen-modules' field "
1231 ++ "besides 'exposed-modules' and 'other-modules'. This specifies that "
1232 ++ "the module does not come with the package and is generated on "
1233 ++ "setup. Modules built with a custom Setup.hs script also go here "
1234 ++ "to ensure that commands like sdist don't fail."
1235 ppExplanation CVAutogenPackageInfo =
1236 "Packages using 'cabal-version: 2.0' and the autogenerated "
1237 ++ "module PackageInfo_* must include it in 'autogen-modules' as well as"
1238 ++ " 'exposed-modules' and 'other-modules'. This specifies that "
1239 ++ "the module does not come with the package and is generated on "
1240 ++ "setup. Modules built with a custom Setup.hs script also go here "
1241 ++ "to ensure that commands like sdist don't fail."
1242 ppExplanation CVAutogenPackageInfoGuard =
1243 "To use the autogenerated module PackageInfo_* you need to specify "
1244 ++ "`cabal-version: 3.12` or higher."
1245 ppExplanation (GlobNoMatch field glob) =
1246 "In '"
1247 ++ field
1248 ++ "': the pattern '"
1249 ++ glob
1250 ++ "' does not"
1251 ++ " match any files."
1252 ppExplanation (GlobExactMatch field glob file) =
1253 "In '"
1254 ++ field
1255 ++ "': the pattern '"
1256 ++ glob
1257 ++ "' does not"
1258 ++ " match the file '"
1259 ++ file
1260 ++ "' because the extensions do not"
1261 ++ " exactly match (e.g., foo.en.html does not exactly match *.html)."
1262 ++ " To enable looser suffix-only matching, set 'cabal-version: 2.4' or"
1263 ++ " higher."
1264 ppExplanation (GlobNoDir field glob dir) =
1265 "In '"
1266 ++ field
1267 ++ "': the pattern '"
1268 ++ glob
1269 ++ "' attempts to"
1270 ++ " match files in the directory '"
1271 ++ dir
1272 ++ "', but there is no"
1273 ++ " directory by that name."
1274 ppExplanation (UnknownOS unknownOSs) =
1275 "Unknown operating system name " ++ commaSep (map quote unknownOSs)
1276 ppExplanation (UnknownArch unknownArches) =
1277 "Unknown architecture name " ++ commaSep (map quote unknownArches)
1278 ppExplanation (UnknownCompiler unknownImpls) =
1279 "Unknown compiler name " ++ commaSep (map quote unknownImpls)
1280 ppExplanation BaseNoUpperBounds =
1281 "The dependency 'build-depends: base' does not specify an upper "
1282 ++ "bound on the version number. Each major release of the 'base' "
1283 ++ "package changes the API in various ways and most packages will "
1284 ++ "need some changes to compile with it. The recommended practice "
1285 ++ "is to specify an upper bound on the version of the 'base' "
1286 ++ "package. This ensures your package will continue to build when a "
1287 ++ "new major version of the 'base' package is released. If you are "
1288 ++ "not sure what upper bound to use then use the next major "
1289 ++ "version. For example if you have tested your package with 'base' "
1290 ++ "version 4.5 and 4.6 then use 'build-depends: base >= 4.5 && < 4.7'."
1291 ppExplanation (MissingUpperBounds ct names) =
1292 let separator = "\n - "
1293 in "On "
1294 ++ ppCET ct
1295 ++ ", "
1296 ++ "these packages miss upper bounds:"
1297 ++ separator
1298 ++ List.intercalate separator names
1299 ++ "\n"
1300 ++ "Please add them. There is more information at https://pvp.haskell.org/"
1301 ppExplanation (SuspiciousFlagName invalidFlagNames) =
1302 "Suspicious flag names: "
1303 ++ unwords invalidFlagNames
1304 ++ ". "
1305 ++ "To avoid ambiguity in command line interfaces, a flag shouldn't "
1306 ++ "start with a dash. Also for better compatibility, flag names "
1307 ++ "shouldn't contain non-ascii characters."
1308 ppExplanation (DeclaredUsedFlags declared used) =
1309 "Declared and used flag sets differ: "
1310 ++ s declared
1311 ++ " /= "
1312 ++ s used
1313 ++ ". "
1314 where
1315 s :: Set.Set FlagName -> String
1316 s = commaSep . map unFlagName . Set.toList
1317 ppExplanation (NonASCIICustomField nonAsciiXFields) =
1318 "Non ascii custom fields: "
1319 ++ unwords nonAsciiXFields
1320 ++ ". "
1321 ++ "For better compatibility, custom field names "
1322 ++ "shouldn't contain non-ascii characters."
1323 ppExplanation RebindableClashPaths =
1324 "Packages using RebindableSyntax with OverloadedStrings or"
1325 ++ " OverloadedLists in default-extensions, in conjunction with the"
1326 ++ " autogenerated module Paths_*, are known to cause compile failures"
1327 ++ " with Cabal < 2.2. To use these default-extensions with a Paths_*"
1328 ++ " autogen module, specify at least 'cabal-version: 2.2'."
1329 ppExplanation RebindableClashPackageInfo =
1330 "Packages using RebindableSyntax with OverloadedStrings or"
1331 ++ " OverloadedLists in default-extensions, in conjunction with the"
1332 ++ " autogenerated module PackageInfo_*, are known to cause compile failures"
1333 ++ " with Cabal < 2.2. To use these default-extensions with a PackageInfo_*"
1334 ++ " autogen module, specify at least 'cabal-version: 2.2'."
1335 ppExplanation (WErrorUnneeded fieldName) =
1336 addConditionalExp $
1338 ++ fieldName
1339 ++ ": -Werror' makes the package easy to "
1340 ++ "break with future GHC versions because new GHC versions often "
1341 ++ "add new warnings."
1342 ppExplanation (JUnneeded fieldName) =
1343 addConditionalExp $
1345 ++ fieldName
1346 ++ ": -j[N]' can make sense for a particular user's setup,"
1347 ++ " but it is not appropriate for a distributed package."
1348 ppExplanation (FDeferTypeErrorsUnneeded fieldName) =
1349 addConditionalExp $
1351 ++ fieldName
1352 ++ ": -fdefer-type-errors' is fine during development "
1353 ++ "but is not appropriate for a distributed package."
1354 ppExplanation (DynamicUnneeded fieldName) =
1355 addConditionalExp $
1357 ++ fieldName
1358 ++ ": -d*' debug flags are not appropriate "
1359 ++ "for a distributed package."
1360 ppExplanation (ProfilingUnneeded fieldName) =
1361 addConditionalExp $
1363 ++ fieldName
1364 ++ ": -fprof*' profiling flags are typically not "
1365 ++ "appropriate for a distributed library package. These flags are "
1366 ++ "useful to profile this package, but when profiling other packages "
1367 ++ "that use this one these flags clutter the profile output with "
1368 ++ "excessive detail. If you think other packages really want to see "
1369 ++ "cost centres from this package then use '-fprof-auto-exported' "
1370 ++ "which puts cost centres only on exported functions."
1371 ppExplanation (UpperBoundSetup nm) =
1372 "The dependency 'setup-depends: '"
1373 ++ nm
1374 ++ "' does not specify an "
1375 ++ "upper bound on the version number. Each major release of the "
1376 ++ "'"
1377 ++ nm
1378 ++ "' package changes the API in various ways and most "
1379 ++ "packages will need some changes to compile with it. If you are "
1380 ++ "not sure what upper bound to use then use the next major "
1381 ++ "version."
1382 ppExplanation (DuplicateModule s dupLibsLax) =
1383 "Duplicate modules in "
1384 ++ s
1385 ++ ": "
1386 ++ commaSep (map prettyShow dupLibsLax)
1387 ppExplanation (PotentialDupModule s dupLibsStrict) =
1388 "Potential duplicate modules (subject to conditionals) in "
1389 ++ s
1390 ++ ": "
1391 ++ commaSep (map prettyShow dupLibsStrict)
1392 ppExplanation (BOMStart pdfile) =
1393 pdfile
1394 ++ " starts with an Unicode byte order mark (BOM)."
1395 ++ " This may cause problems with older cabal versions."
1396 ppExplanation (NotPackageName pdfile expectedCabalname) =
1397 "The filename "
1398 ++ quote pdfile
1399 ++ " does not match package name "
1400 ++ "(expected: "
1401 ++ quote expectedCabalname
1402 ++ ")"
1403 ppExplanation NoDesc =
1404 "No cabal file found.\n"
1405 ++ "Please create a package description file <pkgname>.cabal"
1406 ppExplanation (MultiDesc multiple) =
1407 "Multiple cabal files found while checking.\n"
1408 ++ "Please use only one of: "
1409 ++ commaSep multiple
1410 ppExplanation (UnknownFile fieldname file) =
1411 "The '"
1412 ++ fieldname
1413 ++ "' field refers to the file "
1414 ++ quote (getSymbolicPath file)
1415 ++ " which does not exist."
1416 ppExplanation MissingSetupFile =
1417 "The package is missing a Setup.hs or Setup.lhs script."
1418 ppExplanation MissingConfigureScript =
1419 "The 'build-type' is 'Configure' but there is no 'configure' script. "
1420 ++ "You probably need to run 'autoreconf -i' to generate it."
1421 ppExplanation (UnknownDirectory kind dir) =
1422 quote (kind ++ ": " ++ dir)
1423 ++ " specifies a directory which does not exist."
1424 ppExplanation MissingSourceControl =
1425 "When distributing packages, it is encouraged to specify source "
1426 ++ "control information in the .cabal file using one or more "
1427 ++ "'source-repository' sections. See the Cabal user guide for "
1428 ++ "details."
1429 ppExplanation (MissingExpectedDocFiles extraDocFileSupport paths) =
1430 "Please consider including the "
1431 ++ quotes paths
1432 ++ " in the '"
1433 ++ targetField
1434 ++ "' section of the .cabal file "
1435 ++ "if it contains useful information for users of the package."
1436 where
1437 quotes [p] = "file " ++ quote p
1438 quotes ps = "files " ++ commaSep (map quote ps)
1439 targetField =
1440 if extraDocFileSupport
1441 then "extra-doc-files"
1442 else "extra-source-files"
1443 ppExplanation (WrongFieldForExpectedDocFiles extraDocFileSupport field paths) =
1444 "Please consider moving the "
1445 ++ quotes paths
1446 ++ " from the '"
1447 ++ field
1448 ++ "' section of the .cabal file "
1449 ++ "to the section '"
1450 ++ targetField
1451 ++ "'."
1452 where
1453 quotes [p] = "file " ++ quote p
1454 quotes ps = "files " ++ commaSep (map quote ps)
1455 targetField =
1456 if extraDocFileSupport
1457 then "extra-doc-files"
1458 else "extra-source-files"
1460 -- * Formatting utilities
1462 commaSep :: [String] -> String
1463 commaSep = List.intercalate ", "
1465 quote :: String -> String
1466 quote s = "'" ++ s ++ "'"
1468 addConditionalExp :: String -> String
1469 addConditionalExp expl =
1470 expl
1471 ++ " Alternatively, if you want to use this, make it conditional based "
1472 ++ "on a Cabal configuration flag (with 'manual: True' and 'default: "
1473 ++ "False') and enable that flag during development."