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