Merge pull request #10530 from 9999years/no-hide-successes
[cabal.git] / Cabal / src / Distribution / PackageDescription / Check.hs
blob8bab6ec961ab91aff2000675cde45011378ac6d7
1 {-# LANGUAGE DataKinds #-}
2 {-# LANGUAGE ScopedTypeVariables #-}
4 -- |
5 -- Module : Distribution.PackageDescription.Check
6 -- Copyright : Lennart Kolmodin 2008, Francesco Ariis 2022
7 -- License : BSD3
8 --
9 -- Maintainer : cabal-devel@haskell.org
10 -- Portability : portable
12 -- This has code for checking for various problems in packages. There is one
13 -- set of checks that just looks at a 'PackageDescription' in isolation and
14 -- another set of checks that also looks at files in the package. Some of the
15 -- checks are basic sanity checks, others are portability standards that we'd
16 -- like to encourage. There is a 'PackageCheck' type that distinguishes the
17 -- different kinds of checks so we can see which ones are appropriate to report
18 -- in different situations. This code gets used when configuring a package when
19 -- we consider only basic problems. The higher standard is used when
20 -- preparing a source tarball and by Hackage when uploading new packages. The
21 -- reason for this is that we want to hold packages that are expected to be
22 -- distributed to a higher standard than packages that are only ever expected
23 -- to be used on the author's own environment.
24 module Distribution.PackageDescription.Check
25 ( -- * Package Checking
26 CheckExplanation (..)
27 , CheckExplanationID
28 , CheckExplanationIDString
29 , PackageCheck (..)
30 , checkPackage
31 , checkConfiguredPackage
32 , wrapParseWarning
33 , ppPackageCheck
34 , ppCheckExplanationId
35 , isHackageDistError
36 , filterPackageChecksById
37 , filterPackageChecksByIdString
39 -- ** Checking package contents
40 , checkPackageFiles
41 , checkPackageFilesGPD
42 , checkPackageContent
43 , CheckPackageContentOps (..)
44 ) where
46 import Distribution.Compat.Prelude
47 import Prelude ()
49 import Data.List (group)
50 import Distribution.CabalSpecVersion
51 import Distribution.Compat.Lens
52 import Distribution.Compiler
53 import Distribution.License
54 import Distribution.Package
55 import Distribution.PackageDescription
56 import Distribution.PackageDescription.Check.Common
57 import Distribution.PackageDescription.Check.Conditional
58 import Distribution.PackageDescription.Check.Monad
59 import Distribution.PackageDescription.Check.Paths
60 import Distribution.PackageDescription.Check.Target
61 import Distribution.PackageDescription.Check.Warning
62 import Distribution.Parsec.Warning (PWarning)
63 import Distribution.Pretty (prettyShow)
64 import Distribution.Simple.Glob
65 ( Glob
66 , GlobResult (..)
67 , globMatches
68 , parseFileGlob
69 , runDirFileGlob
71 import Distribution.Simple.Utils hiding (findPackageDesc, notice)
72 import Distribution.Utils.Generic (isAscii)
73 import Distribution.Utils.Path
74 import Distribution.Verbosity
75 import Distribution.Version
76 import System.FilePath (splitExtension, takeFileName)
78 import qualified Data.ByteString.Lazy as BS
79 import qualified Distribution.SPDX as SPDX
80 import qualified System.Directory as System
82 import qualified System.Directory (getDirectoryContents)
83 import qualified System.FilePath.Windows as FilePath.Windows (isValid)
85 import qualified Data.Set as Set
86 import qualified Distribution.Utils.ShortText as ShortText
88 import qualified Distribution.Types.GenericPackageDescription.Lens as L
90 import Control.Monad
92 -- $setup
93 -- >>> import Control.Arrow ((&&&))
95 -- ☞ N.B.
97 -- Part of the tools/scaffold used to perform check is found in
98 -- Distribution.PackageDescription.Check.Types. Summary of that module (for
99 -- how we use it here):
100 -- 1. we work inside a 'CheckM m a' monad (where `m` is an abstraction to
101 -- run non-pure checks);
102 -- 2. 'checkP', 'checkPre' functions perform checks (respectively pure and
103 -- non-pure);
104 -- 3. 'PackageCheck' and 'CheckExplanation' are types for warning severity
105 -- and description.
107 -- ------------------------------------------------------------
108 -- Checking interface
109 -- ------------------------------------------------------------
111 -- | 'checkPackagePrim' is the most general way to invoke package checks.
112 -- We pass to it two interfaces (one to check contents of packages, the
113 -- other to inspect working tree for orphan files) and before that a
114 -- Boolean to indicate whether we want pure checks or not. Based on these
115 -- parameters, some checks will be performed, some omitted.
116 -- Generality over @m@ means we could do non pure checks in monads other
117 -- than IO (e.g. a virtual filesystem, like a zip file, a VCS filesystem,
118 -- etc).
119 checkPackagePrim
120 :: Monad m
121 => Bool -- Perform pure checks?
122 -> Maybe (CheckPackageContentOps m) -- Package content interface.
123 -> Maybe (CheckPreDistributionOps m) -- Predist checks interface.
124 -> GenericPackageDescription -- GPD to check.
125 -> m [PackageCheck]
126 checkPackagePrim b mco mpdo gpd = do
127 let cm = checkGenericPackageDescription gpd
128 ci = CheckInterface b mco mpdo
129 ctx = pristineCheckCtx ci gpd
130 execCheckM cm ctx
132 -- | Check for common mistakes and problems in package descriptions.
134 -- This is the standard collection of checks covering all aspects except
135 -- for checks that require looking at files within the package. For those
136 -- see 'checkPackageFiles'.
137 checkPackage :: GenericPackageDescription -> [PackageCheck]
138 checkPackage gpd = runIdentity $ checkPackagePrim True Nothing Nothing gpd
140 -- | This function is an oddity due to the historical
141 -- GenericPackageDescription/PackageDescription split. It is only maintained
142 -- not to break interface, use `checkPackage` if possible.
143 checkConfiguredPackage :: PackageDescription -> [PackageCheck]
144 checkConfiguredPackage pd = checkPackage (pd2gpd pd)
146 -- | Sanity check things that requires looking at files in the package.
147 -- This is a generalised version of 'checkPackageFiles' that can work in any
148 -- monad for which you can provide 'CheckPackageContentOps' operations.
150 -- The point of this extra generality is to allow doing checks in some virtual
151 -- file system, for example a tarball in memory.
152 checkPackageContent
153 :: Monad m
154 => CheckPackageContentOps m
155 -> GenericPackageDescription
156 -> m [PackageCheck]
157 checkPackageContent pops gpd = checkPackagePrim False (Just pops) Nothing gpd
159 -- | Sanity checks that require IO. 'checkPackageFiles' looks at the files
160 -- in the package and expects to find the package unpacked at the given
161 -- filepath.
162 checkPackageFilesGPD
163 :: Verbosity -- Glob warn message verbosity.
164 -> GenericPackageDescription
165 -> FilePath -- Package root.
166 -> IO [PackageCheck]
167 checkPackageFilesGPD verbosity gpd root =
168 checkPackagePrim False (Just checkFilesIO) (Just checkPreIO) gpd
169 where
170 checkFilesIO =
171 CheckPackageContentOps
172 { doesFileExist = System.doesFileExist . relative
173 , doesDirectoryExist = System.doesDirectoryExist . relative
174 , getDirectoryContents = System.Directory.getDirectoryContents . relative
175 , getFileContents = BS.readFile . relative
178 checkPreIO =
179 CheckPreDistributionOps
180 { runDirFileGlobM = \fp g -> runDirFileGlob verbosity (Just . specVersion $ packageDescription gpd) (root </> fp) g
181 , getDirectoryContentsM = System.Directory.getDirectoryContents . relative
184 relative :: FilePath -> FilePath
185 relative path = root </> path
187 -- | Same as 'checkPackageFilesGPD', but working with 'PackageDescription'.
189 -- This function is included for legacy reasons, use 'checkPackageFilesGPD'
190 -- if you are working with 'GenericPackageDescription'.
191 checkPackageFiles
192 :: Verbosity -- Glob warn message verbosity.
193 -> PackageDescription
194 -> FilePath -- Package root.
195 -> IO [PackageCheck]
196 checkPackageFiles verbosity pd oot =
197 checkPackageFilesGPD verbosity (pd2gpd pd) oot
199 -- ------------------------------------------------------------
200 -- Package description
201 -- ------------------------------------------------------------
203 -- Here lies the meat of the module. Starting from 'GenericPackageDescription',
204 -- we walk the data while doing a number of checks.
206 -- Where applicable we do a full pattern match (if the data changes, code will
207 -- break: a gentle reminder to add more checks).
208 -- Pattern matching variables convention: matching accessor + underscore.
209 -- This way it is easier to see which one we are missing if we run into
210 -- an “GPD should have 20 arguments but has been given only 19” error.
212 -- | 'GenericPackageDescription' checks. Remember that for historical quirks
213 -- in the cabal codebase we have both `GenericPackageDescription` and
214 -- `PackageDescription` and that PD is both a *field* of GPD and a concept
215 -- of its own (i.e. a fully realised GPD).
216 -- In this case we are checking (correctly) GPD, so for target info/checks
217 -- you should walk condLibrary_ etc. and *not* the (empty) target info in
218 -- PD. See 'pd2gpd' for a convenient hack when you only have
219 -- 'PackageDescription'.
220 checkGenericPackageDescription
221 :: Monad m
222 => GenericPackageDescription
223 -> CheckM m ()
224 checkGenericPackageDescription
225 gpd@( GenericPackageDescription
226 packageDescription_
227 _gpdScannedVersion_
228 genPackageFlags_
229 condLibrary_
230 condSubLibraries_
231 condForeignLibs_
232 condExecutables_
233 condTestSuites_
234 condBenchmarks_
237 -- § Description and names.
238 checkPackageDescription packageDescription_
239 -- Targets should be present...
240 let condAllLibraries =
241 maybeToList condLibrary_
242 ++ (map snd condSubLibraries_)
243 checkP
244 ( and
245 [ null condExecutables_
246 , null condTestSuites_
247 , null condBenchmarks_
248 , null condAllLibraries
249 , null condForeignLibs_
252 (PackageBuildImpossible NoTarget)
253 -- ... and have unique names (names are not under conditional, it is
254 -- appropriate to check here.
255 (nsubs, nexes, ntests, nbenchs) <-
256 asksCM
257 ( ( \n ->
258 ( pnSubLibs n
259 , pnExecs n
260 , pnTests n
261 , pnBenchs n
264 . ccNames
266 let names = concat [nsubs, nexes, ntests, nbenchs]
267 dupes = dups names
268 checkP
269 (not . null $ dups names)
270 (PackageBuildImpossible $ DuplicateSections dupes)
271 -- PackageDescription checks.
272 checkPackageDescription packageDescription_
273 -- Flag names.
274 mapM_ checkFlagName genPackageFlags_
276 -- § Feature checks.
277 checkSpecVer
278 CabalSpecV2_0
279 (not . null $ condSubLibraries_)
280 (PackageDistInexcusable CVMultiLib)
281 checkSpecVer
282 CabalSpecV1_8
283 (not . null $ condTestSuites_)
284 (PackageDistInexcusable CVTestSuite)
286 -- § Conditional targets
288 -- Extract dependencies from libraries, to be passed along for
289 -- PVP checks purposes.
290 pName <-
291 asksCM
292 ( packageNameToUnqualComponentName
293 . pkgName
294 . pnPackageId
295 . ccNames
297 let ads =
298 maybe [] ((: []) . extractAssocDeps pName) condLibrary_
299 ++ map (uncurry extractAssocDeps) condSubLibraries_
301 case condLibrary_ of
302 Just cl ->
303 checkCondTarget
304 genPackageFlags_
305 (checkLibrary False ads)
306 (const id)
307 (mempty, cl)
308 Nothing -> return ()
309 mapM_
310 ( checkCondTarget
311 genPackageFlags_
312 (checkLibrary False ads)
313 (\u l -> l{libName = maybeToLibraryName (Just u)})
315 condSubLibraries_
316 mapM_
317 ( checkCondTarget
318 genPackageFlags_
319 checkForeignLib
320 (const id)
322 condForeignLibs_
323 mapM_
324 ( checkCondTarget
325 genPackageFlags_
326 (checkExecutable ads)
327 (const id)
329 condExecutables_
330 mapM_
331 ( checkCondTarget
332 genPackageFlags_
333 (checkTestSuite ads)
334 (\u l -> l{testName = u})
336 condTestSuites_
337 mapM_
338 ( checkCondTarget
339 genPackageFlags_
340 (checkBenchmark ads)
341 (\u l -> l{benchmarkName = u})
343 condBenchmarks_
345 -- For unused flags it is clearer and more convenient to fold the
346 -- data rather than walk it, an exception to the rule.
347 checkP
348 (decFlags /= usedFlags)
349 (PackageDistSuspicious $ DeclaredUsedFlags decFlags usedFlags)
351 -- Duplicate modules.
352 mapM_ tellP (checkDuplicateModules gpd)
353 where
354 -- todo is this caught at parse time?
355 checkFlagName :: Monad m => PackageFlag -> CheckM m ()
356 checkFlagName pf =
357 let fn = unFlagName . flagName $ pf
359 invalidFlagName ('-' : _) = True -- starts with dash
360 invalidFlagName cs = any (not . isAscii) cs -- non ASCII
361 in checkP
362 (invalidFlagName fn)
363 (PackageDistInexcusable $ SuspiciousFlagName [fn])
365 decFlags :: Set.Set FlagName
366 decFlags = toSetOf (L.genPackageFlags . traverse . L.flagName) gpd
368 usedFlags :: Set.Set FlagName
369 usedFlags =
370 mconcat
371 [ toSetOf (L.condLibrary . traverse . traverseCondTreeV . L._PackageFlag) gpd
372 , toSetOf (L.condSubLibraries . traverse . _2 . traverseCondTreeV . L._PackageFlag) gpd
373 , toSetOf (L.condForeignLibs . traverse . _2 . traverseCondTreeV . L._PackageFlag) gpd
374 , toSetOf (L.condExecutables . traverse . _2 . traverseCondTreeV . L._PackageFlag) gpd
375 , toSetOf (L.condTestSuites . traverse . _2 . traverseCondTreeV . L._PackageFlag) gpd
376 , toSetOf (L.condBenchmarks . traverse . _2 . traverseCondTreeV . L._PackageFlag) gpd
379 checkPackageDescription :: Monad m => PackageDescription -> CheckM m ()
380 checkPackageDescription
381 pkg@( PackageDescription
382 specVersion_
383 package_
384 licenseRaw_
385 licenseFiles_
386 _copyright_
387 maintainer_
388 _author_
389 _stability_
390 testedWith_
391 _homepage_
392 _pkgUrl_
393 _bugReports_
394 sourceRepos_
395 synopsis_
396 description_
397 category_
398 customFieldsPD_
399 buildTypeRaw_
400 setupBuildInfo_
401 _library_
402 _subLibraries_
403 _executables_
404 _foreignLibs_
405 _testSuites_
406 _benchmarks_
407 dataFiles_
408 dataDir_
409 extraSrcFiles_
410 extraTmpFiles_
411 extraDocFiles_
412 extraFiles_
413 ) = do
414 -- § Sanity checks.
415 checkPackageId package_
416 -- TODO `name` is caught at parse level, remove this test.
417 let pn = packageName package_
418 checkP
419 (null . unPackageName $ pn)
420 (PackageBuildImpossible NoNameField)
421 -- TODO `version` is caught at parse level, remove this test.
422 checkP
423 (nullVersion == packageVersion package_)
424 (PackageBuildImpossible NoVersionField)
425 -- But it is OK for executables to have the same name.
426 nsubs <- asksCM (pnSubLibs . ccNames)
427 checkP
428 (any (== prettyShow pn) (prettyShow <$> nsubs))
429 (PackageBuildImpossible $ IllegalLibraryName pn)
431 -- § Fields check.
432 checkNull
433 category_
434 (PackageDistSuspicious MissingFieldCategory)
435 checkNull
436 maintainer_
437 (PackageDistSuspicious MissingFieldMaintainer)
438 checkP
439 (ShortText.null synopsis_ && not (ShortText.null description_))
440 (PackageDistSuspicious MissingFieldSynopsis)
441 checkP
442 (ShortText.null description_ && not (ShortText.null synopsis_))
443 (PackageDistSuspicious MissingFieldDescription)
444 checkP
445 (all ShortText.null [synopsis_, description_])
446 (PackageDistInexcusable MissingFieldSynOrDesc)
447 checkP
448 (ShortText.length synopsis_ > 80)
449 (PackageDistSuspicious SynopsisTooLong)
450 checkP
451 ( not (ShortText.null description_)
452 && ShortText.length description_ <= ShortText.length synopsis_
454 (PackageDistSuspicious ShortDesc)
456 -- § Paths.
457 mapM_ (checkPath False "extra-source-files" PathKindGlob . getSymbolicPath) extraSrcFiles_
458 mapM_ (checkPath False "extra-tmp-files" PathKindFile . getSymbolicPath) extraTmpFiles_
459 mapM_ (checkPath False "extra-doc-files" PathKindGlob . getSymbolicPath) extraDocFiles_
460 mapM_ (checkPath False "extra-files" PathKindGlob . getSymbolicPath) extraFiles_
461 mapM_ (checkPath False "data-files" PathKindGlob . getSymbolicPath) dataFiles_
462 let rawDataDir = getSymbolicPath dataDir_
463 checkPath True "data-dir" PathKindDirectory rawDataDir
464 let licPaths = map getSymbolicPath licenseFiles_
465 mapM_ (checkPath False "license-file" PathKindFile) licPaths
466 mapM_ checkLicFileExist licenseFiles_
468 -- § Globs.
469 dataGlobs <- mapM (checkGlob "data-files" . getSymbolicPath) dataFiles_
470 extraSrcGlobs <- mapM (checkGlob "extra-source-files" . getSymbolicPath) extraSrcFiles_
471 docGlobs <- mapM (checkGlob "extra-doc-files" . getSymbolicPath) extraDocFiles_
472 extraGlobs <- mapM (checkGlob "extra-files" . getSymbolicPath) extraFiles_
473 -- We collect globs to feed them to checkMissingDocs.
475 -- § Missing documentation.
476 checkMissingDocs
477 (catMaybes dataGlobs)
478 (catMaybes extraSrcGlobs)
479 (catMaybes docGlobs)
480 (catMaybes extraGlobs)
482 -- § Datafield checks.
483 checkSetupBuildInfo setupBuildInfo_
484 mapM_ checkTestedWith testedWith_
485 either
486 checkNewLicense
487 (checkOldLicense $ null licenseFiles_)
488 licenseRaw_
489 checkSourceRepos sourceRepos_
490 mapM_ checkCustomField customFieldsPD_
492 -- Feature checks.
493 checkSpecVer
494 CabalSpecV1_18
495 (not . null $ extraDocFiles_)
496 (PackageDistInexcusable CVExtraDocFiles)
497 checkSpecVer
498 CabalSpecV1_6
499 (not . null $ sourceRepos_)
500 (PackageDistInexcusable CVSourceRepository)
501 checkP
502 ( specVersion_ >= CabalSpecV1_24
503 && isNothing setupBuildInfo_
504 && buildTypeRaw_ == Just Custom
506 (PackageBuildWarning CVCustomSetup)
507 checkSpecVer
508 CabalSpecV1_24
509 ( isNothing setupBuildInfo_
510 && buildTypeRaw_ == Just Custom
512 (PackageDistSuspiciousWarn CVExpliticDepsCustomSetup)
513 checkP
514 (isNothing buildTypeRaw_ && specVersion_ < CabalSpecV2_2)
515 (PackageBuildWarning NoBuildType)
516 checkP
517 (isJust setupBuildInfo_ && buildType pkg `notElem` [Custom, Hooks])
518 (PackageBuildWarning NoCustomSetup)
520 -- Contents.
521 checkConfigureExists (buildType pkg)
522 checkSetupExists (buildType pkg)
523 checkCabalFile (packageName pkg)
524 mapM_ (checkGlobFile specVersion_ "." "extra-source-files" . getSymbolicPath) extraSrcFiles_
525 mapM_ (checkGlobFile specVersion_ "." "extra-doc-files" . getSymbolicPath) extraDocFiles_
526 mapM_ (checkGlobFile specVersion_ "." "extra-files" . getSymbolicPath) extraFiles_
527 mapM_ (checkGlobFile specVersion_ rawDataDir "data-files" . getSymbolicPath) dataFiles_
528 where
529 checkNull
530 :: Monad m
531 => ShortText.ShortText
532 -> PackageCheck
533 -> CheckM m ()
534 checkNull st c = checkP (ShortText.null st) c
536 checkTestedWith
537 :: Monad m
538 => (CompilerFlavor, VersionRange)
539 -> CheckM m ()
540 checkTestedWith (OtherCompiler n, _) =
541 tellP (PackageBuildWarning $ UnknownCompilers [n])
542 checkTestedWith (compiler, versionRange) =
543 checkVersionRange compiler versionRange
545 checkVersionRange
546 :: Monad m
547 => CompilerFlavor
548 -> VersionRange
549 -> CheckM m ()
550 checkVersionRange cmp vr =
551 when
552 (isNoVersion vr)
553 ( let dep =
554 [ Dependency
555 (mkPackageName (prettyShow cmp))
557 mainLibSet
559 in tellP (PackageDistInexcusable (InvalidTestWith dep))
562 checkSetupBuildInfo :: Monad m => Maybe SetupBuildInfo -> CheckM m ()
563 checkSetupBuildInfo Nothing = return ()
564 checkSetupBuildInfo (Just (SetupBuildInfo ds _)) = do
565 let uqs = map mkUnqualComponentName ["base", "Cabal"]
566 (is, rs) <- partitionDeps [] uqs ds
567 let ick = PackageDistInexcusable . UpperBoundSetup
568 rck =
569 PackageDistSuspiciousWarn
570 . MissingUpperBounds CETSetup
571 checkPVP ick is
572 checkPVPs rck rs
574 checkPackageId :: Monad m => PackageIdentifier -> CheckM m ()
575 checkPackageId (PackageIdentifier pkgName_ _pkgVersion_) = do
576 checkP
577 (not . FilePath.Windows.isValid . prettyShow $ pkgName_)
578 (PackageDistInexcusable $ InvalidNameWin pkgName_)
579 checkP (isPrefixOf "z-" . prettyShow $ pkgName_) $
580 (PackageDistInexcusable ZPrefix)
582 checkNewLicense :: Monad m => SPDX.License -> CheckM m ()
583 checkNewLicense lic = do
584 checkP
585 (lic == SPDX.NONE)
586 (PackageDistInexcusable NONELicense)
588 checkOldLicense
589 :: Monad m
590 => Bool -- Flag: no license file?
591 -> License
592 -> CheckM m ()
593 checkOldLicense nullLicFiles lic = do
594 checkP
595 (lic == UnspecifiedLicense)
596 (PackageDistInexcusable NoLicense)
597 checkP
598 (lic == AllRightsReserved)
599 (PackageDistSuspicious AllRightsReservedLicense)
600 checkSpecVer
601 CabalSpecV1_4
602 (lic `notElem` compatLicenses)
603 (PackageDistInexcusable (LicenseMessParse lic))
604 checkP
605 (lic == BSD4)
606 (PackageDistSuspicious UncommonBSD4)
607 case lic of
608 UnknownLicense l ->
609 tellP (PackageBuildWarning (UnrecognisedLicense l))
610 _ -> return ()
611 checkP
612 ( lic
613 `notElem` [ AllRightsReserved
614 , UnspecifiedLicense
615 , PublicDomain
618 -- AllRightsReserved and PublicDomain are not strictly
619 -- licenses so don't need license files.
620 nullLicFiles
622 $ (PackageDistSuspicious NoLicenseFile)
623 case unknownLicenseVersion lic of
624 Just knownVersions ->
625 tellP
626 (PackageDistSuspicious $ UnknownLicenseVersion lic knownVersions)
627 _ -> return ()
628 where
629 compatLicenses =
630 [ GPL Nothing
631 , LGPL Nothing
632 , AGPL Nothing
633 , BSD3
634 , BSD4
635 , PublicDomain
636 , AllRightsReserved
637 , UnspecifiedLicense
638 , OtherLicense
641 unknownLicenseVersion (GPL (Just v))
642 | v `notElem` knownVersions = Just knownVersions
643 where
644 knownVersions = [v' | GPL (Just v') <- knownLicenses]
645 unknownLicenseVersion (LGPL (Just v))
646 | v `notElem` knownVersions = Just knownVersions
647 where
648 knownVersions = [v' | LGPL (Just v') <- knownLicenses]
649 unknownLicenseVersion (AGPL (Just v))
650 | v `notElem` knownVersions = Just knownVersions
651 where
652 knownVersions = [v' | AGPL (Just v') <- knownLicenses]
653 unknownLicenseVersion (Apache (Just v))
654 | v `notElem` knownVersions = Just knownVersions
655 where
656 knownVersions = [v' | Apache (Just v') <- knownLicenses]
657 unknownLicenseVersion _ = Nothing
659 checkSourceRepos :: Monad m => [SourceRepo] -> CheckM m ()
660 checkSourceRepos rs = do
661 mapM_ repoCheck rs
662 checkMissingVcsInfo rs
663 where
664 -- Single repository checks.
665 repoCheck :: Monad m => SourceRepo -> CheckM m ()
666 repoCheck
667 ( SourceRepo
668 repoKind_
669 repoType_
670 repoLocation_
671 repoModule_
672 _repoBranch_
673 repoTag_
674 repoSubdir_
675 ) = do
676 case repoKind_ of
677 RepoKindUnknown kind ->
678 tellP
679 (PackageDistInexcusable $ UnrecognisedSourceRepo kind)
680 _ -> return ()
681 checkP
682 (isNothing repoType_)
683 (PackageDistInexcusable MissingType)
684 checkP
685 (isNothing repoLocation_)
686 (PackageDistInexcusable MissingLocation)
687 checkGitProtocol repoLocation_
688 checkP
689 ( repoType_ == Just (KnownRepoType CVS)
690 && isNothing repoModule_
692 (PackageDistInexcusable MissingModule)
693 checkP
694 (repoKind_ == RepoThis && isNothing repoTag_)
695 (PackageDistInexcusable MissingTag)
696 checkP
697 (any isAbsoluteOnAnyPlatform repoSubdir_)
698 (PackageDistInexcusable SubdirRelPath)
699 case join . fmap isGoodRelativeDirectoryPath $ repoSubdir_ of
700 Just err ->
701 tellP
702 (PackageDistInexcusable $ SubdirGoodRelPath err)
703 Nothing -> return ()
705 checkMissingVcsInfo :: Monad m => [SourceRepo] -> CheckM m ()
706 checkMissingVcsInfo rs =
707 let rdirs = concatMap repoTypeDirname knownRepoTypes
708 in checkPkg
709 ( \ops -> do
710 us <- or <$> traverse (doesDirectoryExist ops) rdirs
711 return (null rs && us)
713 (PackageDistSuspicious MissingSourceControl)
714 where
715 repoTypeDirname :: KnownRepoType -> [FilePath]
716 repoTypeDirname Darcs = ["_darcs"]
717 repoTypeDirname Git = [".git"]
718 repoTypeDirname SVN = [".svn"]
719 repoTypeDirname CVS = ["CVS"]
720 repoTypeDirname Mercurial = [".hg"]
721 repoTypeDirname GnuArch = [".arch-params"]
722 repoTypeDirname Bazaar = [".bzr"]
723 repoTypeDirname Monotone = ["_MTN"]
724 repoTypeDirname Pijul = [".pijul"]
726 -- git:// lacks TLS or other encryption, see
727 -- https://git-scm.com/book/en/v2/Git-on-the-Server-The-Protocols#_the_cons_4
728 checkGitProtocol
729 :: Monad m
730 => Maybe String -- Repository location
731 -> CheckM m ()
732 checkGitProtocol mloc =
733 checkP
734 (fmap (isPrefixOf "git://") mloc == Just True)
735 (PackageBuildWarning GitProtocol)
737 -- ------------------------------------------------------------
738 -- Package and distribution checks
739 -- ------------------------------------------------------------
741 -- | Find a package description file in the given directory. Looks for
742 -- @.cabal@ files. Like 'Distribution.Simple.Utils.findPackageDesc',
743 -- but generalized over monads.
744 findPackageDesc :: Monad m => CheckPackageContentOps m -> m [FilePath]
745 findPackageDesc ops = do
746 let dir = "."
747 files <- getDirectoryContents ops dir
748 -- to make sure we do not mistake a ~/.cabal/ dir for a <name>.cabal
749 -- file we filter to exclude dirs and null base file names:
750 cabalFiles <-
751 filterM
752 (doesFileExist ops)
753 [ dir </> file
754 | file <- files
755 , let (name, ext) = splitExtension file
756 , not (null name) && ext == ".cabal"
758 return cabalFiles
760 checkCabalFile :: Monad m => PackageName -> CheckM m ()
761 checkCabalFile pn = do
762 -- liftInt is a bit more messy than stricter interface, but since
763 -- each of the following check is exclusive, we can simplify the
764 -- condition flow.
765 liftInt
766 ciPackageOps
767 ( \ops -> do
768 -- 1. Get .cabal files.
769 ds <- findPackageDesc ops
770 case ds of
771 [] -> return [PackageBuildImpossible NoDesc]
772 -- No .cabal file.
773 [d] -> do
774 bc <- bomf ops d
775 return (catMaybes [bc, noMatch d])
776 -- BOM + no matching .cabal checks.
777 _ -> return [PackageBuildImpossible $ MultiDesc ds]
779 where
780 -- Multiple .cabal files.
782 bomf
783 :: Monad m
784 => CheckPackageContentOps m
785 -> FilePath
786 -> m (Maybe PackageCheck)
787 bomf wops wfp = do
788 b <- BS.isPrefixOf bomUtf8 <$> getFileContents wops wfp
789 if b
790 then (return . Just) (PackageDistInexcusable $ BOMStart wfp)
791 else return Nothing
793 bomUtf8 :: BS.ByteString
794 bomUtf8 = BS.pack [0xef, 0xbb, 0xbf] -- U+FEFF encoded as UTF8
795 noMatch :: FilePath -> Maybe PackageCheck
796 noMatch wd =
797 let expd = unPackageName pn <.> "cabal"
798 in if takeFileName wd /= expd
799 then Just (PackageDistInexcusable $ NotPackageName wd expd)
800 else Nothing
802 checkLicFileExist
803 :: Monad m
804 => RelativePath Pkg File
805 -> CheckM m ()
806 checkLicFileExist sp = do
807 let fp = getSymbolicPath sp
808 checkPkg
809 (\ops -> not <$> doesFileExist ops fp)
810 (PackageBuildWarning $ UnknownFile "license-file" sp)
812 checkConfigureExists :: Monad m => BuildType -> CheckM m ()
813 checkConfigureExists Configure =
814 checkPkg
815 (\ops -> not <$> doesFileExist ops "configure")
816 (PackageBuildWarning MissingConfigureScript)
817 checkConfigureExists _ = return ()
819 checkSetupExists :: Monad m => BuildType -> CheckM m ()
820 checkSetupExists Simple = return ()
821 checkSetupExists _ =
822 checkPkg
823 ( \ops -> do
824 ba <- doesFileExist ops "Setup.hs"
825 bb <- doesFileExist ops "Setup.lhs"
826 return (not $ ba || bb)
828 (PackageDistInexcusable MissingSetupFile)
830 -- The following functions are similar to 'CheckPackageContentOps m' ones,
831 -- but, as they inspect the files included in the package, but are primarily
832 -- looking for files in the working tree that may have been missed or other
833 -- similar problems that can only be detected pre-distribution.
835 -- Because Hackage necessarily checks the uploaded tarball, it is too late to
836 -- check these on the server; these checks only make sense in the development
837 -- and package-creation environment.
838 -- This most likely means we need to use IO, but a dictionary
839 -- 'CheckPreDistributionOps m' is provided in case in the future such
840 -- information can come from somewhere else (e.g. VCS filesystem).
842 -- Note: this really shouldn't return any 'Inexcusable' warnings,
843 -- because that will make us say that Hackage would reject the package.
844 -- But, because Hackage doesn't yet run these tests, that will be a lie!
846 checkGlobFile
847 :: Monad m
848 => CabalSpecVersion
849 -> FilePath -- Glob pattern.
850 -> FilePath -- Folder to check.
851 -> CabalField -- .cabal field we are checking.
852 -> CheckM m ()
853 checkGlobFile cv ddir title fp = do
854 let adjDdir = if null ddir then "." else ddir
856 | title == "data-files" = adjDdir
857 | otherwise = "."
859 case parseFileGlob cv fp of
860 -- We just skip over parse errors here; they're reported elsewhere.
861 Left _ -> return ()
862 Right parsedGlob -> do
863 liftInt ciPreDistOps $ \po -> do
864 rs <- runDirFileGlobM po dir parsedGlob
865 return $ checkGlobResult title fp rs
867 -- | Checks for matchless globs and too strict matching (<2.4 spec).
868 checkGlobResult
869 :: CabalField -- .cabal field we are checking
870 -> FilePath -- Glob pattern (to show the user
871 -- which pattern is the offending
872 -- one).
873 -> [GlobResult FilePath] -- List of glob results.
874 -> [PackageCheck]
875 checkGlobResult title fp rs = dirCheck ++ catMaybes (map getWarning rs)
876 where
877 dirCheck
878 | all (not . withoutNoMatchesWarning) rs =
879 [PackageDistSuspiciousWarn $ GlobNoMatch title fp]
880 | otherwise = []
882 -- If there's a missing directory in play, since globs in Cabal packages
883 -- don't (currently) support disjunction, that will always mean there are
884 -- no matches. The no matches error in this case is strictly less
885 -- informative than the missing directory error.
886 withoutNoMatchesWarning (GlobMatch _) = True
887 withoutNoMatchesWarning (GlobWarnMultiDot _) = False
888 withoutNoMatchesWarning (GlobMissingDirectory _) = True
889 withoutNoMatchesWarning (GlobMatchesDirectory _) = True
891 getWarning :: GlobResult FilePath -> Maybe PackageCheck
892 getWarning (GlobMatch _) = Nothing
893 -- Before Cabal 2.4, the extensions of globs had to match the file
894 -- exactly. This has been relaxed in 2.4 to allow matching only the
895 -- suffix. This warning detects when pre-2.4 package descriptions
896 -- are omitting files purely because of the stricter check.
897 getWarning (GlobWarnMultiDot file) =
898 Just $ PackageDistSuspiciousWarn (GlobExactMatch title fp file)
899 getWarning (GlobMissingDirectory dir) =
900 Just $ PackageDistSuspiciousWarn (GlobNoDir title fp dir)
901 -- GlobMatchesDirectory is handled elsewhere if relevant;
902 -- we can discard it here.
903 getWarning (GlobMatchesDirectory _) = Nothing
905 -- ------------------------------------------------------------
906 -- Other exports
907 -- ------------------------------------------------------------
909 -- | Wraps `ParseWarning` into `PackageCheck`.
910 wrapParseWarning :: FilePath -> PWarning -> PackageCheck
911 wrapParseWarning fp pw = PackageDistSuspicious (ParseWarning fp pw)
913 -- TODO: as Jul 2022 there is no severity indication attached PWarnType.
914 -- Once that is added, we can output something more appropriate
915 -- than PackageDistSuspicious for every parse warning.
916 -- (see: Cabal-syntax/src/Distribution/Parsec/Warning.hs)
918 -- ------------------------------------------------------------
919 -- Ancillaries
920 -- ------------------------------------------------------------
922 -- Gets a list of dependencies from a Library target to pass to PVP related
923 -- functions. We are not doing checks here: this is not imprecise, as the
924 -- library itself *will* be checked for PVP errors.
925 -- Same for branch merging,
926 -- each of those branch will be checked one by one.
927 extractAssocDeps
928 :: UnqualComponentName -- Name of the target library
929 -> CondTree ConfVar [Dependency] Library
930 -> AssocDep
931 extractAssocDeps n ct =
932 let a = ignoreConditions ct
933 in -- Merging is fine here, remember the specific
934 -- library dependencies will be checked branch
935 -- by branch.
936 (n, snd a)
938 -- | August 2022: this function is an oddity due to the historical
939 -- GenericPackageDescription/PackageDescription split (check
940 -- Distribution.Types.PackageDescription for a description of the relationship
941 -- between GPD and PD.
942 -- It is only maintained not to break interface, should be deprecated in the
943 -- future in favour of `checkPackage` when PD and GPD are refactored sensibly.
944 pd2gpd :: PackageDescription -> GenericPackageDescription
945 pd2gpd pd = gpd
946 where
947 gpd :: GenericPackageDescription
948 gpd =
949 emptyGenericPackageDescription
950 { packageDescription = pd
951 , condLibrary = fmap t2c (library pd)
952 , condSubLibraries = map (t2cName ln id) (subLibraries pd)
953 , condForeignLibs =
955 (t2cName foreignLibName id)
956 (foreignLibs pd)
957 , condExecutables =
959 (t2cName exeName id)
960 (executables pd)
961 , condTestSuites =
963 (t2cName testName remTest)
964 (testSuites pd)
965 , condBenchmarks =
967 (t2cName benchmarkName remBench)
968 (benchmarks pd)
971 -- From target to simple, unconditional CondTree.
972 t2c :: a -> CondTree ConfVar [Dependency] a
973 t2c a = CondNode a [] []
975 -- From named target to unconditional CondTree. Notice we have
976 -- a function to extract the name *and* a function to modify
977 -- the target. This is needed for 'initTargetAnnotation' to work
978 -- properly and to contain all the quirks inside 'pd2gpd'.
979 t2cName
980 :: (a -> UnqualComponentName)
981 -> (a -> a)
982 -> a
983 -> (UnqualComponentName, CondTree ConfVar [Dependency] a)
984 t2cName nf mf a = (nf a, t2c . mf $ a)
986 ln :: Library -> UnqualComponentName
987 ln wl = case libName wl of
988 (LSubLibName u) -> u
989 LMainLibName -> mkUnqualComponentName "main-library"
991 remTest :: TestSuite -> TestSuite
992 remTest t = t{testName = mempty}
994 remBench :: Benchmark -> Benchmark
995 remBench b = b{benchmarkName = mempty}
997 -- checkMissingDocs will check that we don’t have an interesting file
998 -- (changes.txt, Changelog.md, NEWS, etc.) in our work-tree which is not
999 -- present in our .cabal file.
1000 checkMissingDocs
1001 :: Monad m
1002 => [Glob] -- data-files globs.
1003 -> [Glob] -- extra-source-files globs.
1004 -> [Glob] -- extra-doc-files globs.
1005 -> [Glob] -- extra-files globs.
1006 -> CheckM m ()
1007 checkMissingDocs dgs esgs edgs efgs = do
1008 extraDocSupport <- (>= CabalSpecV1_18) <$> asksCM ccSpecVersion
1010 -- Everything in this block uses CheckPreDistributionOps interface.
1011 liftInt
1012 ciPreDistOps
1013 ( \ops -> do
1014 -- 1. Get root files, see if they are interesting to us.
1015 rootContents <- getDirectoryContentsM ops "."
1016 -- Recall getDirectoryContentsM arg is relative to root path.
1017 let des = filter isDesirableExtraDocFile rootContents
1019 -- 2. Realise Globs.
1020 let realGlob t =
1021 concatMap globMatches
1022 <$> mapM (runDirFileGlobM ops "") t
1023 rgs <- realGlob dgs
1024 res <- realGlob esgs
1025 red <- realGlob edgs
1026 ref <- realGlob efgs
1028 -- 3. Check if anything in 1. is missing in 2.
1029 let mcs = checkDoc extraDocSupport des (rgs ++ res ++ red ++ ref)
1031 -- 4. Check if files are present but in the wrong field.
1032 let pcsData = checkDocMove extraDocSupport "data-files" des rgs
1033 pcsSource =
1034 if extraDocSupport
1035 then
1036 checkDocMove
1037 extraDocSupport
1038 "extra-source-files"
1041 else []
1042 pcs = pcsData ++ pcsSource
1044 return (mcs ++ pcs)
1046 where
1047 checkDoc
1048 :: Bool -- Cabal spec ≥ 1.18?
1049 -> [FilePath] -- Desirables.
1050 -> [FilePath] -- Actuals.
1051 -> [PackageCheck]
1052 checkDoc b ds as =
1053 let fds = map ("." </>) $ filter (flip notElem as) ds
1054 in if null fds
1055 then []
1056 else
1057 [ PackageDistSuspiciousWarn $
1058 MissingExpectedDocFiles b fds
1061 checkDocMove
1062 :: Bool -- Cabal spec ≥ 1.18?
1063 -> CabalField -- Name of the field.
1064 -> [FilePath] -- Desirables.
1065 -> [FilePath] -- Actuals.
1066 -> [PackageCheck]
1067 checkDocMove b field ds as =
1068 let fds = filter (flip elem as) ds
1069 in if null fds
1070 then []
1071 else
1072 [ PackageDistSuspiciousWarn $
1073 WrongFieldForExpectedDocFiles b field fds
1076 -- Predicate for desirable documentation file on Hackage server.
1077 isDesirableExtraDocFile :: FilePath -> Bool
1078 isDesirableExtraDocFile path =
1079 basename `elem` desirableChangeLog
1080 && ext `elem` desirableChangeLogExtensions
1081 where
1082 (basename, ext) = splitExtension (map toLower path)
1084 -- Changelog patterns (basenames & extensions)
1085 -- Source: hackage-server/src/Distribution/Server/Packages/ChangeLog.hs
1086 desirableChangeLog = ["news", "changelog", "change_log", "changes"]
1087 desirableChangeLogExtensions = ["", ".txt", ".md", ".markdown", ".rst"]
1089 -- [TODO] Check readme. Observations:
1090 -- • Readme is not necessary if package description is good.
1091 -- • Some readmes exists only for repository browsing.
1092 -- • There is currently no reliable way to check what a good
1093 -- description is; there will be complains if the criterion
1094 -- is based on the length or number of words (can of worms).
1095 -- -- Readme patterns
1096 -- -- Source: hackage-server/src/Distribution/Server/Packages/Readme.hs
1097 -- desirableReadme = ["readme"]
1099 -- Remove duplicates from list.
1100 dups :: Ord a => [a] -> [a]
1101 dups xs = [x | (x : _ : _) <- group (sort xs)]