1 {-# LANGUAGE ScopedTypeVariables #-}
4 -- Module : Distribution.PackageDescription.Check
5 -- Copyright : Lennart Kolmodin 2008, Francesco Ariis 2022
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
27 , CheckExplanationIDString
30 , checkConfiguredPackage
33 , ppCheckExplanationId
35 , filterPackageChecksById
36 , filterPackageChecksByIdString
38 -- ** Checking package contents
40 , checkPackageFilesGPD
42 , CheckPackageContentOps
(..)
45 import Distribution
.Compat
.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
70 import Distribution
.Simple
.Utils
hiding (findPackageDesc
, notice
)
71 import Distribution
.Utils
.Generic
(isAscii)
72 import Distribution
.Utils
.Path
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
97 -- >>> import Control.Arrow ((&&&))
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
108 -- 3. 'PackageCheck' and 'CheckExplanation' are types for warning severity
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,
125 => Bool -- Perform pure checks?
126 -> Maybe (CheckPackageContentOps m
) -- Package content interface.
127 -> Maybe (CheckPreDistributionOps m
) -- Predist checks interface.
128 -> GenericPackageDescription
-- GPD to check.
130 checkPackagePrim b mco mpdo gpd
= do
131 let cm
= checkGenericPackageDescription gpd
132 ci
= CheckInterface b mco mpdo
133 ctx
= pristineCheckCtx ci gpd
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.
158 => CheckPackageContentOps m
159 -> GenericPackageDescription
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
167 :: Verbosity
-- Glob warn message verbosity.
168 -> GenericPackageDescription
169 -> FilePath -- Package root.
171 checkPackageFilesGPD verbosity gpd root
=
172 checkPackagePrim
False (Just checkFilesIO
) (Just checkPreIO
) gpd
175 CheckPackageContentOps
176 { doesFileExist = System
.doesFileExist . relative
177 , doesDirectoryExist = System
.doesDirectoryExist . relative
178 , getDirectoryContents = System
.Directory
.getDirectoryContents . relative
179 , getFileContents
= BS
.readFile . relative
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'.
195 :: Verbosity
-- Glob warn message verbosity.
196 -> PackageDescription
197 -> FilePath -- Package root.
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
225 => GenericPackageDescription
227 checkGenericPackageDescription
228 gpd
@( GenericPackageDescription
240 -- § Description and names.
241 checkPackageDescription packageDescription_
242 -- Targets should be present...
243 let condAllLibraries
=
244 maybeToList condLibrary_
245 ++ (map snd condSubLibraries_
)
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
) <-
269 let names
= concat [nsubs
, nexes
, ntests
, nbenchs
]
272 (not . null $ dups names
)
273 (PackageBuildImpossible
$ DuplicateSections dupes
)
274 -- PackageDescription checks.
275 checkPackageDescription packageDescription_
277 mapM_ checkFlagName genPackageFlags_
282 (not . null $ condSubLibraries_
)
283 (PackageDistInexcusable CVMultiLib
)
286 (not . null $ condTestSuites_
)
287 (PackageDistInexcusable CVTestSuite
)
289 -- § Conditional targets
291 -- Extract dependencies from libraries, to be passed along for
292 -- PVP checks purposes.
295 ( packageNameToUnqualComponentName
301 maybe [] ((: []) . extractAssocDeps pName
) condLibrary_
302 ++ map (uncurry extractAssocDeps
) condSubLibraries_
308 (checkLibrary
False ads
)
315 (checkLibrary
False ads
)
316 (\u l
-> l
{libName
= maybeToLibraryName
(Just u
)})
329 (checkExecutable ads
)
337 (\u l
-> l
{testName
= u
})
344 (\u l
-> l
{benchmarkName
= u
})
348 -- For unused flags it is clearer and more convenient to fold the
349 -- data rather than walk it, an exception to the rule.
351 (decFlags
/= usedFlags
)
352 (PackageDistSuspicious
$ DeclaredUsedFlags decFlags usedFlags
)
354 -- Duplicate modules.
355 mapM_ tellP
(checkDuplicateModules gpd
)
357 -- todo is this caught at parse time?
358 checkFlagName
:: Monad m
=> PackageFlag
-> CheckM m
()
360 let fn
= unFlagName
. flagName
$ pf
362 invalidFlagName
('-' : _
) = True -- starts with dash
363 invalidFlagName cs
= any (not . isAscii) cs
-- non ASCII
366 (PackageDistInexcusable
$ SuspiciousFlagName
[fn
])
368 decFlags
:: Set
.Set FlagName
369 decFlags
= toSetOf
(L
.genPackageFlags
. traverse
. L
.flagName
) gpd
371 usedFlags
:: Set
.Set FlagName
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
417 checkPackageId package_
418 -- TODO `name` is caught at parse level, remove this test.
419 let pn
= packageName package_
421 (null . unPackageName
$ pn
)
422 (PackageBuildImpossible NoNameField
)
423 -- TODO `version` is caught at parse level, remove this test.
425 (nullVersion
== packageVersion package_
)
426 (PackageBuildImpossible NoVersionField
)
427 -- But it is OK for executables to have the same name.
428 nsubs
<- asksCM
(pnSubLibs
. ccNames
)
430 (any (== prettyShow pn
) (prettyShow
<$> nsubs
))
431 (PackageBuildImpossible
$ IllegalLibraryName pn
)
436 (PackageDistSuspicious MissingFieldCategory
)
439 (PackageDistSuspicious MissingFieldMaintainer
)
441 (ShortText
.null synopsis_
&& not (ShortText
.null description_
))
442 (PackageDistSuspicious MissingFieldSynopsis
)
444 (ShortText
.null description_
&& not (ShortText
.null synopsis_
))
445 (PackageDistSuspicious MissingFieldDescription
)
447 (all ShortText
.null [synopsis_
, description_
])
448 (PackageDistInexcusable MissingFieldSynOrDesc
)
450 (ShortText
.length synopsis_
> 80)
451 (PackageDistSuspicious SynopsisTooLong
)
453 ( not (ShortText
.null description_
)
454 && ShortText
.length description_
<= ShortText
.length synopsis_
456 (PackageDistSuspicious ShortDesc
)
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_
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.
476 (catMaybes dataGlobs
)
477 (catMaybes extraGlobs
)
480 -- § Datafield checks.
481 checkSetupBuildInfo setupBuildInfo_
482 mapM_ checkTestedWith testedWith_
485 (checkOldLicense
$ null licenseFiles_
)
487 checkSourceRepos sourceRepos_
488 mapM_ checkCustomField customFieldsPD_
493 (not . null $ extraDocFiles_
)
494 (PackageDistInexcusable CVExtraDocFiles
)
497 (not . null $ sourceRepos_
)
498 (PackageDistInexcusable CVSourceRepository
)
500 ( specVersion_
>= CabalSpecV1_24
501 && isNothing setupBuildInfo_
502 && buildTypeRaw_
== Just Custom
504 (PackageBuildWarning CVCustomSetup
)
507 ( isNothing setupBuildInfo_
508 && buildTypeRaw_
== Just Custom
510 (PackageDistSuspiciousWarn CVExpliticDepsCustomSetup
)
512 (isNothing buildTypeRaw_
&& specVersion_
< CabalSpecV2_2
)
513 (PackageBuildWarning NoBuildType
)
515 (isJust setupBuildInfo_
&& buildType pkg
/= Custom
)
516 (PackageBuildWarning NoCustomSetup
)
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_
528 => ShortText
.ShortText
531 checkNull st c
= checkP
(ShortText
.null st
) c
535 => (CompilerFlavor
, VersionRange
)
537 checkTestedWith
(OtherCompiler n
, _
) =
538 tellP
(PackageBuildWarning
$ UnknownCompilers
[n
])
539 checkTestedWith
(compiler
, versionRange
) =
540 checkVersionRange compiler versionRange
547 checkVersionRange cmp vr
=
552 (mkPackageName
(prettyShow cmp
))
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
566 PackageDistSuspiciousWarn
567 . MissingUpperBounds CETSetup
571 checkPackageId
:: Monad m
=> PackageIdentifier
-> CheckM m
()
572 checkPackageId
(PackageIdentifier pkgName_ _pkgVersion_
) = do
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
583 (PackageDistInexcusable NONELicense
)
587 => Bool -- Flag: no license file?
590 checkOldLicense nullLicFiles lic
= do
592 (lic
== UnspecifiedLicense
)
593 (PackageDistInexcusable NoLicense
)
595 (lic
== AllRightsReserved
)
596 (PackageDistSuspicious AllRightsReservedLicense
)
599 (lic `
notElem` compatLicenses
)
600 (PackageDistInexcusable
(LicenseMessParse lic
))
603 (PackageDistSuspicious UncommonBSD4
)
606 tellP
(PackageBuildWarning
(UnrecognisedLicense l
))
610 `
notElem`
[ AllRightsReserved
615 -- AllRightsReserved and PublicDomain are not strictly
616 -- licenses so don't need license files.
619 $ (PackageDistSuspicious NoLicenseFile
)
620 case unknownLicenseVersion lic
of
621 Just knownVersions
->
623 (PackageDistSuspicious
$ UnknownLicenseVersion lic knownVersions
)
638 unknownLicenseVersion
(GPL
(Just v
))
639 | v `
notElem` knownVersions
= Just knownVersions
641 knownVersions
= [v
' | GPL
(Just v
') <- knownLicenses
]
642 unknownLicenseVersion
(LGPL
(Just v
))
643 | v `
notElem` knownVersions
= Just knownVersions
645 knownVersions
= [v
' | LGPL
(Just v
') <- knownLicenses
]
646 unknownLicenseVersion
(AGPL
(Just v
))
647 | v `
notElem` knownVersions
= Just knownVersions
649 knownVersions
= [v
' | AGPL
(Just v
') <- knownLicenses
]
650 unknownLicenseVersion
(Apache
(Just v
))
651 | v `
notElem` knownVersions
= Just knownVersions
653 knownVersions
= [v
' | Apache
(Just v
') <- knownLicenses
]
654 unknownLicenseVersion _
= Nothing
656 checkSourceRepos
:: Monad m
=> [SourceRepo
] -> CheckM m
()
657 checkSourceRepos rs
= do
659 checkMissingVcsInfo rs
661 -- Single repository checks.
662 repoCheck
:: Monad m
=> SourceRepo
-> CheckM m
()
674 RepoKindUnknown kind
->
676 (PackageDistInexcusable
$ UnrecognisedSourceRepo kind
)
679 (isNothing repoType_
)
680 (PackageDistInexcusable MissingType
)
682 (isNothing repoLocation_
)
683 (PackageDistInexcusable MissingLocation
)
685 ( repoType_
== Just
(KnownRepoType CVS
)
686 && isNothing repoModule_
688 (PackageDistInexcusable MissingModule
)
690 (repoKind_
== RepoThis
&& isNothing repoTag_
)
691 (PackageDistInexcusable MissingTag
)
693 (any isAbsoluteOnAnyPlatform repoSubdir_
)
694 (PackageDistInexcusable SubdirRelPath
)
695 case join . fmap isGoodRelativeDirectoryPath
$ repoSubdir_
of
698 (PackageDistInexcusable
$ SubdirGoodRelPath err
)
701 checkMissingVcsInfo
:: Monad m
=> [SourceRepo
] -> CheckM m
()
702 checkMissingVcsInfo rs
=
703 let rdirs
= concatMap repoTypeDirname knownRepoTypes
706 us
<- or <$> traverse
(doesDirectoryExist ops
) rdirs
707 return (null rs
&& us
)
709 (PackageDistSuspicious MissingSourceControl
)
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
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:
740 , let (name
, ext
) = splitExtension file
741 , not (null name
) && ext
== ".cabal"
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
753 -- 1. Get .cabal files.
754 ds
<- findPackageDesc ops
756 [] -> return [PackageBuildImpossible NoDesc
]
760 return (catMaybes [bc
, noMatch d
])
761 -- BOM + no matching .cabal checks.
762 _
-> return [PackageBuildImpossible
$ MultiDesc ds
]
765 -- Multiple .cabal files.
769 => CheckPackageContentOps m
771 -> m
(Maybe PackageCheck
)
773 b
<- BS
.isPrefixOf bomUtf8
<$> getFileContents wops wfp
775 then (return . Just
) (PackageDistInexcusable
$ BOMStart wfp
)
778 bomUtf8
:: BS
.ByteString
779 bomUtf8
= BS
.pack
[0xef, 0xbb, 0xbf] -- U+FEFF encoded as UTF8
780 noMatch
:: FilePath -> Maybe PackageCheck
782 let expd
= unPackageName pn
<.> "cabal"
783 in if takeFileName wd
/= expd
784 then Just
(PackageDistInexcusable
$ NotPackageName wd expd
)
789 => SymbolicPath PackageDir LicenseFile
791 checkLicFileExist sp
= do
792 let fp
= getSymbolicPath sp
794 (\ops
-> not <$> doesFileExist ops fp
)
795 (PackageBuildWarning
$ UnknownFile
"license-file" sp
)
797 checkConfigureExists
:: Monad m
=> BuildType
-> CheckM m
()
798 checkConfigureExists Configure
=
800 (\ops
-> not <$> doesFileExist ops
"configure")
801 (PackageBuildWarning MissingConfigureScript
)
802 checkConfigureExists _
= return ()
804 checkSetupExists
:: Monad m
=> BuildType
-> CheckM m
()
805 checkSetupExists Simple
= return ()
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!
834 -> FilePath -- Glob pattern.
835 -> FilePath -- Folder to check.
836 -> CabalField
-- .cabal field we are checking.
838 checkGlobFile cv ddir title fp
= do
839 let adjDdir
= if null ddir
then "." else ddir
841 | title
== "data-files" = adjDdir
844 case parseFileGlob cv fp
of
845 -- We just skip over parse errors here; they're reported elsewhere.
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).
854 :: CabalField
-- .cabal field we are checking
855 -> FilePath -- Glob pattern (to show the user
856 -- which pattern is the offending
858 -> [GlobResult
FilePath] -- List of glob results.
860 checkGlobResult title fp rs
= dirCheck
++ catMaybes (map getWarning rs
)
863 |
all (not . withoutNoMatchesWarning
) rs
=
864 [PackageDistSuspiciousWarn
$ GlobNoMatch title fp
]
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 -- ------------------------------------------------------------
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 -- ------------------------------------------------------------
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.
913 :: UnqualComponentName
-- Name of the target library
914 -> CondTree ConfVar
[Dependency
] Library
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
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
932 gpd
:: GenericPackageDescription
934 emptyGenericPackageDescription
935 { packageDescription
= pd
936 , condLibrary
= fmap t2c
(library pd
)
937 , condSubLibraries
= map (t2cName ln
id) (subLibraries pd
)
940 (t2cName foreignLibName
id)
948 (t2cName testName remTest
)
952 (t2cName benchmarkName remBench
)
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'.
965 :: (a
-> UnqualComponentName
)
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
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.
987 => [Glob
] -- data-files globs.
988 -> [Glob
] -- extra-source-files globs.
989 -> [Glob
] -- extra-doc-files globs.
991 checkMissingDocs dgs esgs edgs
= do
992 extraDocSupport
<- (>= CabalSpecV1_18
) <$> asksCM ccSpecVersion
994 -- Everything in this block uses CheckPreDistributionOps interface.
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.
1005 concatMap globMatches
1006 <$> mapM (runDirFileGlobM ops
"") t
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
1021 "extra-source-files"
1025 pcs
= pcsData
++ pcsSource
1031 :: Bool -- Cabal spec ≥ 1.18?
1032 -> [FilePath] -- Desirables.
1033 -> [FilePath] -- Actuals.
1036 let fds
= map ("." </>) $ filter (flip notElem as) ds
1040 [ PackageDistSuspiciousWarn
$
1041 MissingExpectedDocFiles b fds
1045 :: Bool -- Cabal spec ≥ 1.18?
1046 -> CabalField
-- Name of the field.
1047 -> [FilePath] -- Desirables.
1048 -> [FilePath] -- Actuals.
1050 checkDocMove b field ds
as =
1051 let fds
= filter (flip elem as) ds
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
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
)]