Copyright | Lennart Kolmodin 2008 Francesco Ariis 2022 |
---|---|
License | BSD3 |
Maintainer | cabal-devel@haskell.org |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
This has code for checking for various problems in packages. There is one
set of checks that just looks at a PackageDescription
in isolation and
another set of checks that also looks at files in the package. Some of the
checks are basic sanity checks, others are portability standards that we'd
like to encourage. There is a PackageCheck
type that distinguishes the
different kinds of checks so we can see which ones are appropriate to report
in different situations. This code gets used when configuring a package when
we consider only basic problems. The higher standard is used when
preparing a source tarball and by Hackage when uploading new packages. The
reason for this is that we want to hold packages that are expected to be
distributed to a higher standard than packages that are only ever expected
to be used on the author's own environment.
Synopsis
- data CheckExplanation
- = ParseWarning FilePath PWarning
- | NoNameField
- | NoVersionField
- | NoTarget
- | UnnamedInternal
- | DuplicateSections [UnqualComponentName]
- | IllegalLibraryName PackageName
- | NoModulesExposed LibraryName
- | SignaturesCabal2
- | AutogenNotExposed
- | AutogenIncludesNotIncluded
- | NoMainIs UnqualComponentName
- | NoHsLhsMain
- | MainCCabal1_18
- | AutogenNoOther CEType
- | AutogenIncludesNotIncludedExe
- | TestsuiteTypeNotKnown TestType
- | TestsuiteNotSupported TestType
- | BenchmarkTypeNotKnown BenchmarkType
- | BenchmarkNotSupported BenchmarkType
- | NoHsLhsMainBench
- | InvalidNameWin PackageName
- | ZPrefix
- | NoBuildType
- | NoCustomSetup
- | UnknownCompilers [String]
- | UnknownLanguages [String]
- | UnknownExtensions [String]
- | LanguagesAsExtension [String]
- | DeprecatedExtensions [(Extension, Maybe Extension)]
- | MissingFieldCategory
- | MissingFieldMaintainer
- | MissingFieldSynopsis
- | MissingFieldDescription
- | MissingFieldSynOrDesc
- | SynopsisTooLong
- | ShortDesc
- | InvalidTestWith [Dependency]
- | ImpossibleInternalDep [Dependency]
- | ImpossibleInternalExe [ExeDependency]
- | MissingInternalExe [ExeDependency]
- | NONELicense
- | NoLicense
- | AllRightsReservedLicense
- | LicenseMessParse License
- | UnrecognisedLicense String
- | UncommonBSD4
- | UnknownLicenseVersion License [Version]
- | NoLicenseFile
- | UnrecognisedSourceRepo String
- | MissingType
- | MissingLocation
- | GitProtocol
- | MissingModule
- | MissingTag
- | SubdirRelPath
- | SubdirGoodRelPath String
- | OptFasm String
- | OptHpc String
- | OptProf String
- | OptO String
- | OptHide String
- | OptMake String
- | OptONot String
- | OptOOne String
- | OptOTwo String
- | OptSplitSections String
- | OptSplitObjs String
- | OptWls String
- | OptExts String
- | OptRts String
- | OptWithRts String
- | COptONumber String WarnLang
- | COptCPP String
- | OptAlternatives String String [(String, String)]
- | RelativeOutside String FilePath
- | AbsolutePath String FilePath
- | BadRelativePath String FilePath String
- | DistPoint (Maybe String) FilePath
- | GlobSyntaxError String String
- | RecursiveGlobInRoot String FilePath
- | InvalidOnWin [FilePath]
- | FilePathTooLong FilePath
- | FilePathNameTooLong FilePath
- | FilePathSplitTooLong FilePath
- | FilePathEmpty
- | CVTestSuite
- | CVDefaultLanguage
- | CVDefaultLanguageComponent
- | CVDefaultLanguageComponentSoft
- | CVExtraDocFiles
- | CVMultiLib
- | CVReexported
- | CVMixins
- | CVExtraFrameworkDirs
- | CVDefaultExtensions
- | CVExtensionsDeprecated
- | CVSources
- | CVExtraDynamic [[String]]
- | CVVirtualModules
- | CVSourceRepository
- | CVExtensions CabalSpecVersion [Extension]
- | CVCustomSetup
- | CVExpliticDepsCustomSetup
- | CVAutogenPaths
- | CVAutogenPackageInfo
- | CVAutogenPackageInfoGuard
- | GlobNoMatch String String
- | GlobExactMatch String String FilePath
- | GlobNoDir String String FilePath
- | UnknownOS [String]
- | UnknownArch [String]
- | UnknownCompiler [String]
- | BaseNoUpperBounds
- | MissingUpperBounds CEType [String]
- | SuspiciousFlagName [String]
- | DeclaredUsedFlags (Set FlagName) (Set FlagName)
- | NonASCIICustomField [String]
- | RebindableClashPaths
- | RebindableClashPackageInfo
- | WErrorUnneeded String
- | JUnneeded String
- | FDeferTypeErrorsUnneeded String
- | DynamicUnneeded String
- | ProfilingUnneeded String
- | UpperBoundSetup String
- | DuplicateModule String [ModuleName]
- | PotentialDupModule String [ModuleName]
- | BOMStart FilePath
- | NotPackageName FilePath String
- | NoDesc
- | MultiDesc [String]
- | UnknownFile String (RelativePath Pkg 'File)
- | MissingSetupFile
- | MissingConfigureScript
- | UnknownDirectory String FilePath
- | MissingSourceControl
- | MissingExpectedDocFiles Bool [FilePath]
- | WrongFieldForExpectedDocFiles Bool String [FilePath]
- data CheckExplanationID
- type CheckExplanationIDString = String
- data PackageCheck
- checkPackage :: GenericPackageDescription -> [PackageCheck]
- checkConfiguredPackage :: PackageDescription -> [PackageCheck]
- wrapParseWarning :: FilePath -> PWarning -> PackageCheck
- ppPackageCheck :: PackageCheck -> String
- ppCheckExplanationId :: CheckExplanationID -> CheckExplanationIDString
- isHackageDistError :: PackageCheck -> Bool
- filterPackageChecksById :: [PackageCheck] -> [CheckExplanationID] -> [PackageCheck]
- filterPackageChecksByIdString :: [PackageCheck] -> [CheckExplanationIDString] -> ([PackageCheck], [CheckExplanationIDString])
- checkPackageFiles :: Verbosity -> PackageDescription -> FilePath -> IO [PackageCheck]
- checkPackageFilesGPD :: Verbosity -> GenericPackageDescription -> FilePath -> IO [PackageCheck]
- checkPackageContent :: Monad m => CheckPackageContentOps m -> GenericPackageDescription -> m [PackageCheck]
- data CheckPackageContentOps (m :: Type -> Type) = CheckPackageContentOps {
- doesFileExist :: FilePath -> m Bool
- doesDirectoryExist :: FilePath -> m Bool
- getDirectoryContents :: FilePath -> m [FilePath]
- getFileContents :: FilePath -> m ByteString
Package Checking
data CheckExplanation Source #
Explanations of PackageCheck
's errors/warnings.
Instances
Show CheckExplanation Source # | |
Defined in Distribution.PackageDescription.Check.Warning showsPrec :: Int -> CheckExplanation -> ShowS # show :: CheckExplanation -> String # showList :: [CheckExplanation] -> ShowS # | |
Eq CheckExplanation Source # | |
Defined in Distribution.PackageDescription.Check.Warning (==) :: CheckExplanation -> CheckExplanation -> Bool # (/=) :: CheckExplanation -> CheckExplanation -> Bool # | |
Ord CheckExplanation Source # | |
Defined in Distribution.PackageDescription.Check.Warning compare :: CheckExplanation -> CheckExplanation -> Ordering # (<) :: CheckExplanation -> CheckExplanation -> Bool # (<=) :: CheckExplanation -> CheckExplanation -> Bool # (>) :: CheckExplanation -> CheckExplanation -> Bool # (>=) :: CheckExplanation -> CheckExplanation -> Bool # max :: CheckExplanation -> CheckExplanation -> CheckExplanation # min :: CheckExplanation -> CheckExplanation -> CheckExplanation # |
data CheckExplanationID Source #
Identifier for the speficic CheckExplanation
. This ensures `--ignore`
can output a warning on unrecognised values.
☞ N.B.: should be kept in sync with CheckExplanation
.
Instances
type CheckExplanationIDString = String Source #
data PackageCheck Source #
Results of some kind of failed package check.
There are a range of severities, from merely dubious to totally insane. All of them come with a human readable explanation. In future we may augment them with more machine readable explanations, for example to help an IDE suggest automatic corrections.
PackageBuildImpossible | This package description is no good. There's no way it's going to build sensibly. This should give an error at configure time. |
PackageBuildWarning | A problem that is likely to affect building the package, or an issue that we'd like every package author to be aware of, even if the package is never distributed. |
PackageDistSuspicious | An issue that might not be a problem for the package author but might be annoying or detrimental when the package is distributed to users. We should encourage distributed packages to be free from these issues, but occasionally there are justifiable reasons so we cannot ban them entirely. |
PackageDistSuspiciousWarn | Like PackageDistSuspicious but will only display warnings rather than causing abnormal exit when you run 'cabal check'. |
PackageDistInexcusable | An issue that is OK in the author's environment but is almost certain to be a portability problem for other environments. We can quite legitimately refuse to publicly distribute packages with these problems. |
Instances
Show PackageCheck Source # | Broken |
Defined in Distribution.PackageDescription.Check.Warning showsPrec :: Int -> PackageCheck -> ShowS # show :: PackageCheck -> String # showList :: [PackageCheck] -> ShowS # | |
Eq PackageCheck Source # | |
Defined in Distribution.PackageDescription.Check.Warning (==) :: PackageCheck -> PackageCheck -> Bool # (/=) :: PackageCheck -> PackageCheck -> Bool # | |
Ord PackageCheck Source # | |
Defined in Distribution.PackageDescription.Check.Warning compare :: PackageCheck -> PackageCheck -> Ordering # (<) :: PackageCheck -> PackageCheck -> Bool # (<=) :: PackageCheck -> PackageCheck -> Bool # (>) :: PackageCheck -> PackageCheck -> Bool # (>=) :: PackageCheck -> PackageCheck -> Bool # max :: PackageCheck -> PackageCheck -> PackageCheck # min :: PackageCheck -> PackageCheck -> PackageCheck # |
checkPackage :: GenericPackageDescription -> [PackageCheck] Source #
Check for common mistakes and problems in package descriptions.
This is the standard collection of checks covering all aspects except
for checks that require looking at files within the package. For those
see checkPackageFiles
.
checkConfiguredPackage :: PackageDescription -> [PackageCheck] Source #
This function is an oddity due to the historical
GenericPackageDescription/PackageDescription split. It is only maintained
not to break interface, use checkPackage
if possible.
wrapParseWarning :: FilePath -> PWarning -> PackageCheck Source #
Wraps ParseWarning
into PackageCheck
.
ppPackageCheck :: PackageCheck -> String Source #
Pretty printing PackageCheck
.
isHackageDistError :: PackageCheck -> Bool Source #
Would Hackage refuse a package because of this error?
filterPackageChecksById Source #
:: [PackageCheck] | Original checks. |
-> [CheckExplanationID] | IDs to omit. |
-> [PackageCheck] |
Filter Package Check by CheckExplanationID.
filterPackageChecksByIdString Source #
:: [PackageCheck] | Original checks. |
-> [CheckExplanationIDString] | IDs to omit, in |
-> ([PackageCheck], [CheckExplanationIDString]) |
Filter Package Check by Check explanation string.
Checking package contents
checkPackageFiles :: Verbosity -> PackageDescription -> FilePath -> IO [PackageCheck] Source #
Same as checkPackageFilesGPD
, but working with PackageDescription
.
This function is included for legacy reasons, use checkPackageFilesGPD
if you are working with GenericPackageDescription
.
checkPackageFilesGPD :: Verbosity -> GenericPackageDescription -> FilePath -> IO [PackageCheck] Source #
Sanity checks that require IO. checkPackageFiles
looks at the files
in the package and expects to find the package unpacked at the given
filepath.
checkPackageContent :: Monad m => CheckPackageContentOps m -> GenericPackageDescription -> m [PackageCheck] Source #
Sanity check things that requires looking at files in the package.
This is a generalised version of checkPackageFiles
that can work in any
monad for which you can provide CheckPackageContentOps
operations.
The point of this extra generality is to allow doing checks in some virtual file system, for example a tarball in memory.
data CheckPackageContentOps (m :: Type -> Type) Source #
A record of operations needed to check the contents of packages.
Abstracted over m
to provide flexibility (could be IO, a .tar.gz
file, etc).
CheckPackageContentOps | |
|