{-# LANGUAGE DataKinds #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Distribution.PackageDescription.Check.Warning
(
PackageCheck (..)
, CheckExplanation (..)
, CheckExplanationID
, CheckExplanationIDString
, CEType (..)
, WarnLang (..)
, ppPackageCheck
, ppCheckExplanationId
, isHackageDistError
, extractCheckExplanation
, filterPackageChecksById
, filterPackageChecksByIdString
) where
import Distribution.Compat.Prelude
import Prelude ()
import Distribution.CabalSpecVersion (CabalSpecVersion, showCabalSpecVersion)
import Distribution.License (License, knownLicenses)
import Distribution.ModuleName (ModuleName)
import Distribution.Parsec.Warning (PWarning, showPWarning)
import Distribution.Pretty (prettyShow)
import Distribution.Types.BenchmarkType (BenchmarkType, knownBenchmarkTypes)
import Distribution.Types.Dependency (Dependency (..))
import Distribution.Types.ExeDependency (ExeDependency)
import Distribution.Types.Flag (FlagName, unFlagName)
import Distribution.Types.LibraryName (LibraryName (..), showLibraryName)
import Distribution.Types.PackageName (PackageName)
import Distribution.Types.TestType (TestType, knownTestTypes)
import Distribution.Types.UnqualComponentName
import Distribution.Types.Version (Version)
import Distribution.Utils.Path (FileOrDir (..), Pkg, RelativePath, getSymbolicPath)
import Language.Haskell.Extension (Extension)
import qualified Data.Either as Either
import qualified Data.List as List
import qualified Data.Set as Set
data PackageCheck
=
PackageBuildImpossible {PackageCheck -> CheckExplanation
explanation :: CheckExplanation}
|
PackageBuildWarning {explanation :: CheckExplanation}
|
PackageDistSuspicious {explanation :: CheckExplanation}
|
PackageDistSuspiciousWarn {explanation :: CheckExplanation}
|
PackageDistInexcusable {explanation :: CheckExplanation}
deriving (PackageCheck -> PackageCheck -> Bool
(PackageCheck -> PackageCheck -> Bool)
-> (PackageCheck -> PackageCheck -> Bool) -> Eq PackageCheck
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PackageCheck -> PackageCheck -> Bool
== :: PackageCheck -> PackageCheck -> Bool
$c/= :: PackageCheck -> PackageCheck -> Bool
/= :: PackageCheck -> PackageCheck -> Bool
Eq, Eq PackageCheck
Eq PackageCheck =>
(PackageCheck -> PackageCheck -> Ordering)
-> (PackageCheck -> PackageCheck -> Bool)
-> (PackageCheck -> PackageCheck -> Bool)
-> (PackageCheck -> PackageCheck -> Bool)
-> (PackageCheck -> PackageCheck -> Bool)
-> (PackageCheck -> PackageCheck -> PackageCheck)
-> (PackageCheck -> PackageCheck -> PackageCheck)
-> Ord PackageCheck
PackageCheck -> PackageCheck -> Bool
PackageCheck -> PackageCheck -> Ordering
PackageCheck -> PackageCheck -> PackageCheck
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PackageCheck -> PackageCheck -> Ordering
compare :: PackageCheck -> PackageCheck -> Ordering
$c< :: PackageCheck -> PackageCheck -> Bool
< :: PackageCheck -> PackageCheck -> Bool
$c<= :: PackageCheck -> PackageCheck -> Bool
<= :: PackageCheck -> PackageCheck -> Bool
$c> :: PackageCheck -> PackageCheck -> Bool
> :: PackageCheck -> PackageCheck -> Bool
$c>= :: PackageCheck -> PackageCheck -> Bool
>= :: PackageCheck -> PackageCheck -> Bool
$cmax :: PackageCheck -> PackageCheck -> PackageCheck
max :: PackageCheck -> PackageCheck -> PackageCheck
$cmin :: PackageCheck -> PackageCheck -> PackageCheck
min :: PackageCheck -> PackageCheck -> PackageCheck
Ord)
ppPackageCheck :: PackageCheck -> String
ppPackageCheck :: PackageCheck -> [Char]
ppPackageCheck PackageCheck
e =
let ex :: CheckExplanation
ex = PackageCheck -> CheckExplanation
explanation PackageCheck
e
in [Char]
"["
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ (CheckExplanationID -> [Char]
ppCheckExplanationId (CheckExplanationID -> [Char])
-> (CheckExplanation -> CheckExplanationID)
-> CheckExplanation
-> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CheckExplanation -> CheckExplanationID
checkExplanationId) CheckExplanation
ex
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"] "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ CheckExplanation -> [Char]
ppExplanation CheckExplanation
ex
instance Show PackageCheck where
show :: PackageCheck -> [Char]
show PackageCheck
notice = PackageCheck -> [Char]
ppPackageCheck PackageCheck
notice
isHackageDistError :: PackageCheck -> Bool
isHackageDistError :: PackageCheck -> Bool
isHackageDistError = \case
(PackageBuildImpossible{}) -> Bool
True
(PackageBuildWarning{}) -> Bool
True
(PackageDistInexcusable{}) -> Bool
True
(PackageDistSuspicious{}) -> Bool
False
(PackageDistSuspiciousWarn{}) -> Bool
False
filterPackageChecksById
:: [PackageCheck]
-> [CheckExplanationID]
-> [PackageCheck]
filterPackageChecksById :: [PackageCheck] -> [CheckExplanationID] -> [PackageCheck]
filterPackageChecksById [PackageCheck]
cs [CheckExplanationID]
is = (PackageCheck -> Bool) -> [PackageCheck] -> [PackageCheck]
forall a. (a -> Bool) -> [a] -> [a]
filter PackageCheck -> Bool
ff [PackageCheck]
cs
where
ff :: PackageCheck -> Bool
ff :: PackageCheck -> Bool
ff PackageCheck
c =
(CheckExplanationID -> [CheckExplanationID] -> Bool)
-> [CheckExplanationID] -> CheckExplanationID -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip CheckExplanationID -> [CheckExplanationID] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
notElem [CheckExplanationID]
is
(CheckExplanationID -> Bool)
-> (PackageCheck -> CheckExplanationID) -> PackageCheck -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CheckExplanation -> CheckExplanationID
checkExplanationId
(CheckExplanation -> CheckExplanationID)
-> (PackageCheck -> CheckExplanation)
-> PackageCheck
-> CheckExplanationID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageCheck -> CheckExplanation
extractCheckExplanation
(PackageCheck -> Bool) -> PackageCheck -> Bool
forall a b. (a -> b) -> a -> b
$ PackageCheck
c
filterPackageChecksByIdString
:: [PackageCheck]
-> [CheckExplanationIDString]
-> ([PackageCheck], [CheckExplanationIDString])
filterPackageChecksByIdString :: [PackageCheck] -> [[Char]] -> ([PackageCheck], [[Char]])
filterPackageChecksByIdString [PackageCheck]
cs [[Char]]
ss =
let ([[Char]]
es, [CheckExplanationID]
is) = [Either [Char] CheckExplanationID]
-> ([[Char]], [CheckExplanationID])
forall a b. [Either a b] -> ([a], [b])
Either.partitionEithers ([Either [Char] CheckExplanationID]
-> ([[Char]], [CheckExplanationID]))
-> [Either [Char] CheckExplanationID]
-> ([[Char]], [CheckExplanationID])
forall a b. (a -> b) -> a -> b
$ ([Char] -> Either [Char] CheckExplanationID)
-> [[Char]] -> [Either [Char] CheckExplanationID]
forall a b. (a -> b) -> [a] -> [b]
map [Char] -> Either [Char] CheckExplanationID
readExplanationID [[Char]]
ss
in ([PackageCheck] -> [CheckExplanationID] -> [PackageCheck]
filterPackageChecksById [PackageCheck]
cs [CheckExplanationID]
is, [[Char]]
es)
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
| OptJSPP 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
|
| CVMultiLib
| CVReexported
| CVMixins
|
| CVDefaultExtensions
| CVExtensionsDeprecated
| CVSources
| [[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]
| LEUpperBounds CEType [String]
| TrailingZeroUpperBounds CEType [String]
| GTLowerBounds CEType [String]
| SuspiciousFlagName [String]
| DeclaredUsedFlags (Set.Set FlagName) (Set.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]
deriving (CheckExplanation -> CheckExplanation -> Bool
(CheckExplanation -> CheckExplanation -> Bool)
-> (CheckExplanation -> CheckExplanation -> Bool)
-> Eq CheckExplanation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CheckExplanation -> CheckExplanation -> Bool
== :: CheckExplanation -> CheckExplanation -> Bool
$c/= :: CheckExplanation -> CheckExplanation -> Bool
/= :: CheckExplanation -> CheckExplanation -> Bool
Eq, Eq CheckExplanation
Eq CheckExplanation =>
(CheckExplanation -> CheckExplanation -> Ordering)
-> (CheckExplanation -> CheckExplanation -> Bool)
-> (CheckExplanation -> CheckExplanation -> Bool)
-> (CheckExplanation -> CheckExplanation -> Bool)
-> (CheckExplanation -> CheckExplanation -> Bool)
-> (CheckExplanation -> CheckExplanation -> CheckExplanation)
-> (CheckExplanation -> CheckExplanation -> CheckExplanation)
-> Ord CheckExplanation
CheckExplanation -> CheckExplanation -> Bool
CheckExplanation -> CheckExplanation -> Ordering
CheckExplanation -> CheckExplanation -> CheckExplanation
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: CheckExplanation -> CheckExplanation -> Ordering
compare :: CheckExplanation -> CheckExplanation -> Ordering
$c< :: CheckExplanation -> CheckExplanation -> Bool
< :: CheckExplanation -> CheckExplanation -> Bool
$c<= :: CheckExplanation -> CheckExplanation -> Bool
<= :: CheckExplanation -> CheckExplanation -> Bool
$c> :: CheckExplanation -> CheckExplanation -> Bool
> :: CheckExplanation -> CheckExplanation -> Bool
$c>= :: CheckExplanation -> CheckExplanation -> Bool
>= :: CheckExplanation -> CheckExplanation -> Bool
$cmax :: CheckExplanation -> CheckExplanation -> CheckExplanation
max :: CheckExplanation -> CheckExplanation -> CheckExplanation
$cmin :: CheckExplanation -> CheckExplanation -> CheckExplanation
min :: CheckExplanation -> CheckExplanation -> CheckExplanation
Ord, Int -> CheckExplanation -> [Char] -> [Char]
[CheckExplanation] -> [Char] -> [Char]
CheckExplanation -> [Char]
(Int -> CheckExplanation -> [Char] -> [Char])
-> (CheckExplanation -> [Char])
-> ([CheckExplanation] -> [Char] -> [Char])
-> Show CheckExplanation
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> CheckExplanation -> [Char] -> [Char]
showsPrec :: Int -> CheckExplanation -> [Char] -> [Char]
$cshow :: CheckExplanation -> [Char]
show :: CheckExplanation -> [Char]
$cshowList :: [CheckExplanation] -> [Char] -> [Char]
showList :: [CheckExplanation] -> [Char] -> [Char]
Show)
extractCheckExplanation :: PackageCheck -> CheckExplanation
(PackageBuildImpossible CheckExplanation
e) = CheckExplanation
e
extractCheckExplanation (PackageBuildWarning CheckExplanation
e) = CheckExplanation
e
extractCheckExplanation (PackageDistSuspicious CheckExplanation
e) = CheckExplanation
e
extractCheckExplanation (PackageDistSuspiciousWarn CheckExplanation
e) = CheckExplanation
e
extractCheckExplanation (PackageDistInexcusable CheckExplanation
e) = CheckExplanation
e
data CheckExplanationID
= CIParseWarning
| CINoNameField
| CINoVersionField
| CINoTarget
| CIUnnamedInternal
| CIDuplicateSections
| CIIllegalLibraryName
| CINoModulesExposed
| CISignaturesCabal2
| CIAutogenNotExposed
| CIAutogenIncludesNotIncluded
| CINoMainIs
| CINoHsLhsMain
| CIMainCCabal1_18
| CIAutogenNoOther
| CIAutogenIncludesNotIncludedExe
| CITestsuiteTypeNotKnown
| CITestsuiteNotSupported
| CIBenchmarkTypeNotKnown
| CIBenchmarkNotSupported
| CINoHsLhsMainBench
| CIInvalidNameWin
| CIZPrefix
| CINoBuildType
| CINoCustomSetup
| CIUnknownCompilers
| CIUnknownLanguages
| CIUnknownExtensions
| CILanguagesAsExtension
| CIDeprecatedExtensions
| CIMissingFieldCategory
| CIMissingFieldMaintainer
| CIMissingFieldSynopsis
| CIMissingFieldDescription
| CIMissingFieldSynOrDesc
| CISynopsisTooLong
| CIShortDesc
| CIInvalidTestWith
| CIImpossibleInternalDep
| CIImpossibleInternalExe
| CIMissingInternalExe
| CINONELicense
| CINoLicense
| CIAllRightsReservedLicense
| CILicenseMessParse
| CIUnrecognisedLicense
| CIUncommonBSD4
| CIUnknownLicenseVersion
| CINoLicenseFile
| CIUnrecognisedSourceRepo
| CIMissingType
| CIMissingLocation
| CIGitProtocol
| CIMissingModule
| CIMissingTag
| CISubdirRelPath
| CISubdirGoodRelPath
| CIOptFasm
| CIOptHpc
| CIOptProf
| CIOptO
| CIOptHide
| CIOptMake
| CIOptONot
| CIOptOOne
| CIOptOTwo
| CIOptSplitSections
| CIOptSplitObjs
| CIOptWls
| CIOptExts
| CIOptRts
| CIOptWithRts
| CICOptONumber
| CICOptCPP
| CIOptJSPP
| CIOptAlternatives
| CIRelativeOutside
| CIAbsolutePath
| CIBadRelativePath
| CIDistPoint
| CIGlobSyntaxError
| CIRecursiveGlobInRoot
| CIInvalidOnWin
| CIFilePathTooLong
| CIFilePathNameTooLong
| CIFilePathSplitTooLong
| CIFilePathEmpty
| CICVTestSuite
| CICVDefaultLanguage
| CICVDefaultLanguageComponent
| CICVDefaultLanguageComponentSoft
|
| CICVMultiLib
| CICVReexported
| CICVMixins
|
| CICVDefaultExtensions
| CICVExtensionsDeprecated
| CICVSources
|
| CICVVirtualModules
| CICVSourceRepository
| CICVExtensions
| CICVCustomSetup
| CICVExpliticDepsCustomSetup
| CICVAutogenPaths
| CICVAutogenPackageInfo
| CICVAutogenPackageInfoGuard
| CIGlobNoMatch
| CIGlobExactMatch
| CIGlobNoDir
| CIUnknownOS
| CIUnknownArch
| CIUnknownCompiler
| CIBaseNoUpperBounds
| CIMissingUpperBounds
| CILEUpperBounds
| CITrailingZeroUpperBounds
| CIGTLowerBounds
| CISuspiciousFlagName
| CIDeclaredUsedFlags
| CINonASCIICustomField
| CIRebindableClashPaths
| CIRebindableClashPackageInfo
| CIWErrorUnneeded
| CIJUnneeded
| CIFDeferTypeErrorsUnneeded
| CIDynamicUnneeded
| CIProfilingUnneeded
| CIUpperBoundSetup
| CIDuplicateModule
| CIPotentialDupModule
| CIBOMStart
| CINotPackageName
| CINoDesc
| CIMultiDesc
| CIUnknownFile
| CIMissingSetupFile
| CIMissingConfigureScript
| CIUnknownDirectory
| CIMissingSourceControl
| CIMissingExpectedDocFiles
| CIWrongFieldForExpectedDocFiles
deriving (CheckExplanationID -> CheckExplanationID -> Bool
(CheckExplanationID -> CheckExplanationID -> Bool)
-> (CheckExplanationID -> CheckExplanationID -> Bool)
-> Eq CheckExplanationID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CheckExplanationID -> CheckExplanationID -> Bool
== :: CheckExplanationID -> CheckExplanationID -> Bool
$c/= :: CheckExplanationID -> CheckExplanationID -> Bool
/= :: CheckExplanationID -> CheckExplanationID -> Bool
Eq, Eq CheckExplanationID
Eq CheckExplanationID =>
(CheckExplanationID -> CheckExplanationID -> Ordering)
-> (CheckExplanationID -> CheckExplanationID -> Bool)
-> (CheckExplanationID -> CheckExplanationID -> Bool)
-> (CheckExplanationID -> CheckExplanationID -> Bool)
-> (CheckExplanationID -> CheckExplanationID -> Bool)
-> (CheckExplanationID -> CheckExplanationID -> CheckExplanationID)
-> (CheckExplanationID -> CheckExplanationID -> CheckExplanationID)
-> Ord CheckExplanationID
CheckExplanationID -> CheckExplanationID -> Bool
CheckExplanationID -> CheckExplanationID -> Ordering
CheckExplanationID -> CheckExplanationID -> CheckExplanationID
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: CheckExplanationID -> CheckExplanationID -> Ordering
compare :: CheckExplanationID -> CheckExplanationID -> Ordering
$c< :: CheckExplanationID -> CheckExplanationID -> Bool
< :: CheckExplanationID -> CheckExplanationID -> Bool
$c<= :: CheckExplanationID -> CheckExplanationID -> Bool
<= :: CheckExplanationID -> CheckExplanationID -> Bool
$c> :: CheckExplanationID -> CheckExplanationID -> Bool
> :: CheckExplanationID -> CheckExplanationID -> Bool
$c>= :: CheckExplanationID -> CheckExplanationID -> Bool
>= :: CheckExplanationID -> CheckExplanationID -> Bool
$cmax :: CheckExplanationID -> CheckExplanationID -> CheckExplanationID
max :: CheckExplanationID -> CheckExplanationID -> CheckExplanationID
$cmin :: CheckExplanationID -> CheckExplanationID -> CheckExplanationID
min :: CheckExplanationID -> CheckExplanationID -> CheckExplanationID
Ord, Int -> CheckExplanationID -> [Char] -> [Char]
[CheckExplanationID] -> [Char] -> [Char]
CheckExplanationID -> [Char]
(Int -> CheckExplanationID -> [Char] -> [Char])
-> (CheckExplanationID -> [Char])
-> ([CheckExplanationID] -> [Char] -> [Char])
-> Show CheckExplanationID
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> CheckExplanationID -> [Char] -> [Char]
showsPrec :: Int -> CheckExplanationID -> [Char] -> [Char]
$cshow :: CheckExplanationID -> [Char]
show :: CheckExplanationID -> [Char]
$cshowList :: [CheckExplanationID] -> [Char] -> [Char]
showList :: [CheckExplanationID] -> [Char] -> [Char]
Show, Int -> CheckExplanationID
CheckExplanationID -> Int
CheckExplanationID -> [CheckExplanationID]
CheckExplanationID -> CheckExplanationID
CheckExplanationID -> CheckExplanationID -> [CheckExplanationID]
CheckExplanationID
-> CheckExplanationID -> CheckExplanationID -> [CheckExplanationID]
(CheckExplanationID -> CheckExplanationID)
-> (CheckExplanationID -> CheckExplanationID)
-> (Int -> CheckExplanationID)
-> (CheckExplanationID -> Int)
-> (CheckExplanationID -> [CheckExplanationID])
-> (CheckExplanationID
-> CheckExplanationID -> [CheckExplanationID])
-> (CheckExplanationID
-> CheckExplanationID -> [CheckExplanationID])
-> (CheckExplanationID
-> CheckExplanationID
-> CheckExplanationID
-> [CheckExplanationID])
-> Enum CheckExplanationID
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: CheckExplanationID -> CheckExplanationID
succ :: CheckExplanationID -> CheckExplanationID
$cpred :: CheckExplanationID -> CheckExplanationID
pred :: CheckExplanationID -> CheckExplanationID
$ctoEnum :: Int -> CheckExplanationID
toEnum :: Int -> CheckExplanationID
$cfromEnum :: CheckExplanationID -> Int
fromEnum :: CheckExplanationID -> Int
$cenumFrom :: CheckExplanationID -> [CheckExplanationID]
enumFrom :: CheckExplanationID -> [CheckExplanationID]
$cenumFromThen :: CheckExplanationID -> CheckExplanationID -> [CheckExplanationID]
enumFromThen :: CheckExplanationID -> CheckExplanationID -> [CheckExplanationID]
$cenumFromTo :: CheckExplanationID -> CheckExplanationID -> [CheckExplanationID]
enumFromTo :: CheckExplanationID -> CheckExplanationID -> [CheckExplanationID]
$cenumFromThenTo :: CheckExplanationID
-> CheckExplanationID -> CheckExplanationID -> [CheckExplanationID]
enumFromThenTo :: CheckExplanationID
-> CheckExplanationID -> CheckExplanationID -> [CheckExplanationID]
Enum, CheckExplanationID
CheckExplanationID
-> CheckExplanationID -> Bounded CheckExplanationID
forall a. a -> a -> Bounded a
$cminBound :: CheckExplanationID
minBound :: CheckExplanationID
$cmaxBound :: CheckExplanationID
maxBound :: CheckExplanationID
Bounded)
checkExplanationId :: CheckExplanation -> CheckExplanationID
checkExplanationId :: CheckExplanation -> CheckExplanationID
checkExplanationId (ParseWarning{}) = CheckExplanationID
CIParseWarning
checkExplanationId (NoNameField{}) = CheckExplanationID
CINoNameField
checkExplanationId (NoVersionField{}) = CheckExplanationID
CINoVersionField
checkExplanationId (NoTarget{}) = CheckExplanationID
CINoTarget
checkExplanationId (UnnamedInternal{}) = CheckExplanationID
CIUnnamedInternal
checkExplanationId (DuplicateSections{}) = CheckExplanationID
CIDuplicateSections
checkExplanationId (IllegalLibraryName{}) = CheckExplanationID
CIIllegalLibraryName
checkExplanationId (NoModulesExposed{}) = CheckExplanationID
CINoModulesExposed
checkExplanationId (SignaturesCabal2{}) = CheckExplanationID
CISignaturesCabal2
checkExplanationId (AutogenNotExposed{}) = CheckExplanationID
CIAutogenNotExposed
checkExplanationId (AutogenIncludesNotIncluded{}) = CheckExplanationID
CIAutogenIncludesNotIncluded
checkExplanationId (NoMainIs{}) = CheckExplanationID
CINoMainIs
checkExplanationId (NoHsLhsMain{}) = CheckExplanationID
CINoHsLhsMain
checkExplanationId (MainCCabal1_18{}) = CheckExplanationID
CIMainCCabal1_18
checkExplanationId (AutogenNoOther{}) = CheckExplanationID
CIAutogenNoOther
checkExplanationId (AutogenIncludesNotIncludedExe{}) = CheckExplanationID
CIAutogenIncludesNotIncludedExe
checkExplanationId (TestsuiteTypeNotKnown{}) = CheckExplanationID
CITestsuiteTypeNotKnown
checkExplanationId (TestsuiteNotSupported{}) = CheckExplanationID
CITestsuiteNotSupported
checkExplanationId (BenchmarkTypeNotKnown{}) = CheckExplanationID
CIBenchmarkTypeNotKnown
checkExplanationId (BenchmarkNotSupported{}) = CheckExplanationID
CIBenchmarkNotSupported
checkExplanationId (NoHsLhsMainBench{}) = CheckExplanationID
CINoHsLhsMainBench
checkExplanationId (InvalidNameWin{}) = CheckExplanationID
CIInvalidNameWin
checkExplanationId (ZPrefix{}) = CheckExplanationID
CIZPrefix
checkExplanationId (NoBuildType{}) = CheckExplanationID
CINoBuildType
checkExplanationId (NoCustomSetup{}) = CheckExplanationID
CINoCustomSetup
checkExplanationId (UnknownCompilers{}) = CheckExplanationID
CIUnknownCompilers
checkExplanationId (UnknownLanguages{}) = CheckExplanationID
CIUnknownLanguages
checkExplanationId (UnknownExtensions{}) = CheckExplanationID
CIUnknownExtensions
checkExplanationId (LanguagesAsExtension{}) = CheckExplanationID
CILanguagesAsExtension
checkExplanationId (DeprecatedExtensions{}) = CheckExplanationID
CIDeprecatedExtensions
checkExplanationId (MissingFieldCategory{}) = CheckExplanationID
CIMissingFieldCategory
checkExplanationId (MissingFieldMaintainer{}) = CheckExplanationID
CIMissingFieldMaintainer
checkExplanationId (MissingFieldSynopsis{}) = CheckExplanationID
CIMissingFieldSynopsis
checkExplanationId (MissingFieldDescription{}) = CheckExplanationID
CIMissingFieldDescription
checkExplanationId (MissingFieldSynOrDesc{}) = CheckExplanationID
CIMissingFieldSynOrDesc
checkExplanationId (SynopsisTooLong{}) = CheckExplanationID
CISynopsisTooLong
checkExplanationId (ShortDesc{}) = CheckExplanationID
CIShortDesc
checkExplanationId (InvalidTestWith{}) = CheckExplanationID
CIInvalidTestWith
checkExplanationId (ImpossibleInternalDep{}) = CheckExplanationID
CIImpossibleInternalDep
checkExplanationId (ImpossibleInternalExe{}) = CheckExplanationID
CIImpossibleInternalExe
checkExplanationId (MissingInternalExe{}) = CheckExplanationID
CIMissingInternalExe
checkExplanationId (NONELicense{}) = CheckExplanationID
CINONELicense
checkExplanationId (NoLicense{}) = CheckExplanationID
CINoLicense
checkExplanationId (AllRightsReservedLicense{}) = CheckExplanationID
CIAllRightsReservedLicense
checkExplanationId (LicenseMessParse{}) = CheckExplanationID
CILicenseMessParse
checkExplanationId (UnrecognisedLicense{}) = CheckExplanationID
CIUnrecognisedLicense
checkExplanationId (UncommonBSD4{}) = CheckExplanationID
CIUncommonBSD4
checkExplanationId (UnknownLicenseVersion{}) = CheckExplanationID
CIUnknownLicenseVersion
checkExplanationId (NoLicenseFile{}) = CheckExplanationID
CINoLicenseFile
checkExplanationId (UnrecognisedSourceRepo{}) = CheckExplanationID
CIUnrecognisedSourceRepo
checkExplanationId (MissingType{}) = CheckExplanationID
CIMissingType
checkExplanationId (MissingLocation{}) = CheckExplanationID
CIMissingLocation
checkExplanationId (GitProtocol{}) = CheckExplanationID
CIGitProtocol
checkExplanationId (MissingModule{}) = CheckExplanationID
CIMissingModule
checkExplanationId (MissingTag{}) = CheckExplanationID
CIMissingTag
checkExplanationId (SubdirRelPath{}) = CheckExplanationID
CISubdirRelPath
checkExplanationId (SubdirGoodRelPath{}) = CheckExplanationID
CISubdirGoodRelPath
checkExplanationId (OptFasm{}) = CheckExplanationID
CIOptFasm
checkExplanationId (OptHpc{}) = CheckExplanationID
CIOptHpc
checkExplanationId (OptProf{}) = CheckExplanationID
CIOptProf
checkExplanationId (OptO{}) = CheckExplanationID
CIOptO
checkExplanationId (OptHide{}) = CheckExplanationID
CIOptHide
checkExplanationId (OptMake{}) = CheckExplanationID
CIOptMake
checkExplanationId (OptONot{}) = CheckExplanationID
CIOptONot
checkExplanationId (OptOOne{}) = CheckExplanationID
CIOptOOne
checkExplanationId (OptOTwo{}) = CheckExplanationID
CIOptOTwo
checkExplanationId (OptSplitSections{}) = CheckExplanationID
CIOptSplitSections
checkExplanationId (OptSplitObjs{}) = CheckExplanationID
CIOptSplitObjs
checkExplanationId (OptWls{}) = CheckExplanationID
CIOptWls
checkExplanationId (OptExts{}) = CheckExplanationID
CIOptExts
checkExplanationId (OptRts{}) = CheckExplanationID
CIOptRts
checkExplanationId (OptWithRts{}) = CheckExplanationID
CIOptWithRts
checkExplanationId (COptONumber{}) = CheckExplanationID
CICOptONumber
checkExplanationId (COptCPP{}) = CheckExplanationID
CICOptCPP
checkExplanationId (OptJSPP{}) = CheckExplanationID
CIOptJSPP
checkExplanationId (OptAlternatives{}) = CheckExplanationID
CIOptAlternatives
checkExplanationId (RelativeOutside{}) = CheckExplanationID
CIRelativeOutside
checkExplanationId (AbsolutePath{}) = CheckExplanationID
CIAbsolutePath
checkExplanationId (BadRelativePath{}) = CheckExplanationID
CIBadRelativePath
checkExplanationId (DistPoint{}) = CheckExplanationID
CIDistPoint
checkExplanationId (GlobSyntaxError{}) = CheckExplanationID
CIGlobSyntaxError
checkExplanationId (RecursiveGlobInRoot{}) = CheckExplanationID
CIRecursiveGlobInRoot
checkExplanationId (InvalidOnWin{}) = CheckExplanationID
CIInvalidOnWin
checkExplanationId (FilePathTooLong{}) = CheckExplanationID
CIFilePathTooLong
checkExplanationId (FilePathNameTooLong{}) = CheckExplanationID
CIFilePathNameTooLong
checkExplanationId (FilePathSplitTooLong{}) = CheckExplanationID
CIFilePathSplitTooLong
checkExplanationId (FilePathEmpty{}) = CheckExplanationID
CIFilePathEmpty
checkExplanationId (CVTestSuite{}) = CheckExplanationID
CICVTestSuite
checkExplanationId (CVDefaultLanguage{}) = CheckExplanationID
CICVDefaultLanguage
checkExplanationId (CVDefaultLanguageComponent{}) = CheckExplanationID
CICVDefaultLanguageComponent
checkExplanationId (CVDefaultLanguageComponentSoft{}) = CheckExplanationID
CICVDefaultLanguageComponentSoft
checkExplanationId (CVExtraDocFiles{}) = CheckExplanationID
CICVExtraDocFiles
checkExplanationId (CVMultiLib{}) = CheckExplanationID
CICVMultiLib
checkExplanationId (CVReexported{}) = CheckExplanationID
CICVReexported
checkExplanationId (CVMixins{}) = CheckExplanationID
CICVMixins
checkExplanationId (CVExtraFrameworkDirs{}) = CheckExplanationID
CICVExtraFrameworkDirs
checkExplanationId (CVDefaultExtensions{}) = CheckExplanationID
CICVDefaultExtensions
checkExplanationId (CVExtensionsDeprecated{}) = CheckExplanationID
CICVExtensionsDeprecated
checkExplanationId (CVSources{}) = CheckExplanationID
CICVSources
checkExplanationId (CVExtraDynamic{}) = CheckExplanationID
CICVExtraDynamic
checkExplanationId (CVVirtualModules{}) = CheckExplanationID
CICVVirtualModules
checkExplanationId (CVSourceRepository{}) = CheckExplanationID
CICVSourceRepository
checkExplanationId (CVExtensions{}) = CheckExplanationID
CICVExtensions
checkExplanationId (CVCustomSetup{}) = CheckExplanationID
CICVCustomSetup
checkExplanationId (CVExpliticDepsCustomSetup{}) = CheckExplanationID
CICVExpliticDepsCustomSetup
checkExplanationId (CVAutogenPaths{}) = CheckExplanationID
CICVAutogenPaths
checkExplanationId (CVAutogenPackageInfo{}) = CheckExplanationID
CICVAutogenPackageInfo
checkExplanationId (CVAutogenPackageInfoGuard{}) = CheckExplanationID
CICVAutogenPackageInfoGuard
checkExplanationId (GlobNoMatch{}) = CheckExplanationID
CIGlobNoMatch
checkExplanationId (GlobExactMatch{}) = CheckExplanationID
CIGlobExactMatch
checkExplanationId (GlobNoDir{}) = CheckExplanationID
CIGlobNoDir
checkExplanationId (UnknownOS{}) = CheckExplanationID
CIUnknownOS
checkExplanationId (UnknownArch{}) = CheckExplanationID
CIUnknownArch
checkExplanationId (UnknownCompiler{}) = CheckExplanationID
CIUnknownCompiler
checkExplanationId (BaseNoUpperBounds{}) = CheckExplanationID
CIBaseNoUpperBounds
checkExplanationId (MissingUpperBounds{}) = CheckExplanationID
CIMissingUpperBounds
checkExplanationId (LEUpperBounds{}) = CheckExplanationID
CILEUpperBounds
checkExplanationId (TrailingZeroUpperBounds{}) = CheckExplanationID
CITrailingZeroUpperBounds
checkExplanationId (GTLowerBounds{}) = CheckExplanationID
CIGTLowerBounds
checkExplanationId (SuspiciousFlagName{}) = CheckExplanationID
CISuspiciousFlagName
checkExplanationId (DeclaredUsedFlags{}) = CheckExplanationID
CIDeclaredUsedFlags
checkExplanationId (NonASCIICustomField{}) = CheckExplanationID
CINonASCIICustomField
checkExplanationId (RebindableClashPaths{}) = CheckExplanationID
CIRebindableClashPaths
checkExplanationId (RebindableClashPackageInfo{}) = CheckExplanationID
CIRebindableClashPackageInfo
checkExplanationId (WErrorUnneeded{}) = CheckExplanationID
CIWErrorUnneeded
checkExplanationId (JUnneeded{}) = CheckExplanationID
CIJUnneeded
checkExplanationId (FDeferTypeErrorsUnneeded{}) = CheckExplanationID
CIFDeferTypeErrorsUnneeded
checkExplanationId (DynamicUnneeded{}) = CheckExplanationID
CIDynamicUnneeded
checkExplanationId (ProfilingUnneeded{}) = CheckExplanationID
CIProfilingUnneeded
checkExplanationId (UpperBoundSetup{}) = CheckExplanationID
CIUpperBoundSetup
checkExplanationId (DuplicateModule{}) = CheckExplanationID
CIDuplicateModule
checkExplanationId (PotentialDupModule{}) = CheckExplanationID
CIPotentialDupModule
checkExplanationId (BOMStart{}) = CheckExplanationID
CIBOMStart
checkExplanationId (NotPackageName{}) = CheckExplanationID
CINotPackageName
checkExplanationId (NoDesc{}) = CheckExplanationID
CINoDesc
checkExplanationId (MultiDesc{}) = CheckExplanationID
CIMultiDesc
checkExplanationId (UnknownFile{}) = CheckExplanationID
CIUnknownFile
checkExplanationId (MissingSetupFile{}) = CheckExplanationID
CIMissingSetupFile
checkExplanationId (MissingConfigureScript{}) = CheckExplanationID
CIMissingConfigureScript
checkExplanationId (UnknownDirectory{}) = CheckExplanationID
CIUnknownDirectory
checkExplanationId (MissingSourceControl{}) = CheckExplanationID
CIMissingSourceControl
checkExplanationId (MissingExpectedDocFiles{}) = CheckExplanationID
CIMissingExpectedDocFiles
checkExplanationId (WrongFieldForExpectedDocFiles{}) = CheckExplanationID
CIWrongFieldForExpectedDocFiles
type CheckExplanationIDString = String
ppCheckExplanationId :: CheckExplanationID -> CheckExplanationIDString
ppCheckExplanationId :: CheckExplanationID -> [Char]
ppCheckExplanationId CheckExplanationID
CIParseWarning = [Char]
"parser-warning"
ppCheckExplanationId CheckExplanationID
CINoNameField = [Char]
"no-name-field"
ppCheckExplanationId CheckExplanationID
CINoVersionField = [Char]
"no-version-field"
ppCheckExplanationId CheckExplanationID
CINoTarget = [Char]
"no-target"
ppCheckExplanationId CheckExplanationID
CIUnnamedInternal = [Char]
"unnamed-internal-library"
ppCheckExplanationId CheckExplanationID
CIDuplicateSections = [Char]
"duplicate-sections"
ppCheckExplanationId CheckExplanationID
CIIllegalLibraryName = [Char]
"illegal-library-name"
ppCheckExplanationId CheckExplanationID
CINoModulesExposed = [Char]
"no-modules-exposed"
ppCheckExplanationId CheckExplanationID
CISignaturesCabal2 = [Char]
"signatures"
ppCheckExplanationId CheckExplanationID
CIAutogenNotExposed = [Char]
"autogen-not-exposed"
ppCheckExplanationId CheckExplanationID
CIAutogenIncludesNotIncluded = [Char]
"autogen-not-included"
ppCheckExplanationId CheckExplanationID
CINoMainIs = [Char]
"no-main-is"
ppCheckExplanationId CheckExplanationID
CINoHsLhsMain = [Char]
"unknown-extension-main"
ppCheckExplanationId CheckExplanationID
CIMainCCabal1_18 = [Char]
"c-like-main"
ppCheckExplanationId CheckExplanationID
CIAutogenNoOther = [Char]
"autogen-other-modules"
ppCheckExplanationId CheckExplanationID
CIAutogenIncludesNotIncludedExe = [Char]
"autogen-exe"
ppCheckExplanationId CheckExplanationID
CITestsuiteTypeNotKnown = [Char]
"unknown-testsuite-type"
ppCheckExplanationId CheckExplanationID
CITestsuiteNotSupported = [Char]
"unsupported-testsuite"
ppCheckExplanationId CheckExplanationID
CIBenchmarkTypeNotKnown = [Char]
"unknown-bench"
ppCheckExplanationId CheckExplanationID
CIBenchmarkNotSupported = [Char]
"unsupported-bench"
ppCheckExplanationId CheckExplanationID
CINoHsLhsMainBench = [Char]
"bench-unknown-extension"
ppCheckExplanationId CheckExplanationID
CIInvalidNameWin = [Char]
"invalid-name-win"
ppCheckExplanationId CheckExplanationID
CIZPrefix = [Char]
"reserved-z-prefix"
ppCheckExplanationId CheckExplanationID
CINoBuildType = [Char]
"no-build-type"
ppCheckExplanationId CheckExplanationID
CINoCustomSetup = [Char]
"undeclared-custom-setup"
ppCheckExplanationId CheckExplanationID
CIUnknownCompilers = [Char]
"unknown-compiler-tested"
ppCheckExplanationId CheckExplanationID
CIUnknownLanguages = [Char]
"unknown-languages"
ppCheckExplanationId CheckExplanationID
CIUnknownExtensions = [Char]
"unknown-extension"
ppCheckExplanationId CheckExplanationID
CILanguagesAsExtension = [Char]
"languages-as-extensions"
ppCheckExplanationId CheckExplanationID
CIDeprecatedExtensions = [Char]
"deprecated-extensions"
ppCheckExplanationId CheckExplanationID
CIMissingFieldCategory = [Char]
"no-category"
ppCheckExplanationId CheckExplanationID
CIMissingFieldMaintainer = [Char]
"no-maintainer"
ppCheckExplanationId CheckExplanationID
CIMissingFieldSynopsis = [Char]
"no-synopsis"
ppCheckExplanationId CheckExplanationID
CIMissingFieldDescription = [Char]
"no-description"
ppCheckExplanationId CheckExplanationID
CIMissingFieldSynOrDesc = [Char]
"no-syn-desc"
ppCheckExplanationId CheckExplanationID
CISynopsisTooLong = [Char]
"long-synopsis"
ppCheckExplanationId CheckExplanationID
CIShortDesc = [Char]
"short-description"
ppCheckExplanationId CheckExplanationID
CIInvalidTestWith = [Char]
"invalid-range-tested"
ppCheckExplanationId CheckExplanationID
CIImpossibleInternalDep = [Char]
"impossible-dep"
ppCheckExplanationId CheckExplanationID
CIImpossibleInternalExe = [Char]
"impossible-dep-exe"
ppCheckExplanationId CheckExplanationID
CIMissingInternalExe = [Char]
"no-internal-exe"
ppCheckExplanationId CheckExplanationID
CINONELicense = [Char]
"license-none"
ppCheckExplanationId CheckExplanationID
CINoLicense = [Char]
"no-license"
ppCheckExplanationId CheckExplanationID
CIAllRightsReservedLicense = [Char]
"all-rights-reserved"
ppCheckExplanationId CheckExplanationID
CILicenseMessParse = [Char]
"license-parse"
ppCheckExplanationId CheckExplanationID
CIUnrecognisedLicense = [Char]
"unknown-license"
ppCheckExplanationId CheckExplanationID
CIUncommonBSD4 = [Char]
"bsd4-license"
ppCheckExplanationId CheckExplanationID
CIUnknownLicenseVersion = [Char]
"unknown-license-version"
ppCheckExplanationId CheckExplanationID
CINoLicenseFile = [Char]
"no-license-file"
ppCheckExplanationId CheckExplanationID
CIUnrecognisedSourceRepo = [Char]
"unrecognised-repo-type"
ppCheckExplanationId CheckExplanationID
CIMissingType = [Char]
"repo-no-type"
ppCheckExplanationId CheckExplanationID
CIMissingLocation = [Char]
"repo-no-location"
ppCheckExplanationId CheckExplanationID
CIGitProtocol = [Char]
"git-protocol"
ppCheckExplanationId CheckExplanationID
CIMissingModule = [Char]
"repo-no-module"
ppCheckExplanationId CheckExplanationID
CIMissingTag = [Char]
"repo-no-tag"
ppCheckExplanationId CheckExplanationID
CISubdirRelPath = [Char]
"repo-relative-dir"
ppCheckExplanationId CheckExplanationID
CISubdirGoodRelPath = [Char]
"repo-malformed-subdir"
ppCheckExplanationId CheckExplanationID
CIOptFasm = [Char]
"option-fasm"
ppCheckExplanationId CheckExplanationID
CIOptHpc = [Char]
"option-fhpc"
ppCheckExplanationId CheckExplanationID
CIOptProf = [Char]
"option-prof"
ppCheckExplanationId CheckExplanationID
CIOptO = [Char]
"option-o"
ppCheckExplanationId CheckExplanationID
CIOptHide = [Char]
"option-hide-package"
ppCheckExplanationId CheckExplanationID
CIOptMake = [Char]
"option-make"
ppCheckExplanationId CheckExplanationID
CIOptONot = [Char]
"option-optimize"
ppCheckExplanationId CheckExplanationID
CIOptOOne = [Char]
"option-o1"
ppCheckExplanationId CheckExplanationID
CIOptOTwo = [Char]
"option-o2"
ppCheckExplanationId CheckExplanationID
CIOptSplitSections = [Char]
"option-split-section"
ppCheckExplanationId CheckExplanationID
CIOptSplitObjs = [Char]
"option-split-objs"
ppCheckExplanationId CheckExplanationID
CIOptWls = [Char]
"option-optl-wl"
ppCheckExplanationId CheckExplanationID
CIOptExts = [Char]
"use-extension"
ppCheckExplanationId CheckExplanationID
CIOptRts = [Char]
"option-rtsopts"
ppCheckExplanationId CheckExplanationID
CIOptWithRts = [Char]
"option-with-rtsopts"
ppCheckExplanationId CheckExplanationID
CICOptONumber = [Char]
"option-opt-c"
ppCheckExplanationId CheckExplanationID
CICOptCPP = [Char]
"cpp-options"
ppCheckExplanationId CheckExplanationID
CIOptJSPP = [Char]
"jspp-options"
ppCheckExplanationId CheckExplanationID
CIOptAlternatives = [Char]
"misplaced-c-opt"
ppCheckExplanationId CheckExplanationID
CIRelativeOutside = [Char]
"relative-path-outside"
ppCheckExplanationId CheckExplanationID
CIAbsolutePath = [Char]
"absolute-path"
ppCheckExplanationId CheckExplanationID
CIBadRelativePath = [Char]
"malformed-relative-path"
ppCheckExplanationId CheckExplanationID
CIDistPoint = [Char]
"unreliable-dist-path"
ppCheckExplanationId CheckExplanationID
CIGlobSyntaxError = [Char]
"glob-syntax-error"
ppCheckExplanationId CheckExplanationID
CIRecursiveGlobInRoot = [Char]
"recursive-glob"
ppCheckExplanationId CheckExplanationID
CIInvalidOnWin = [Char]
"invalid-path-win"
ppCheckExplanationId CheckExplanationID
CIFilePathTooLong = [Char]
"long-path"
ppCheckExplanationId CheckExplanationID
CIFilePathNameTooLong = [Char]
"long-name"
ppCheckExplanationId CheckExplanationID
CIFilePathSplitTooLong = [Char]
"name-not-portable"
ppCheckExplanationId CheckExplanationID
CIFilePathEmpty = [Char]
"empty-path"
ppCheckExplanationId CheckExplanationID
CICVTestSuite = [Char]
"test-cabal-ver"
ppCheckExplanationId CheckExplanationID
CICVDefaultLanguage = [Char]
"default-language"
ppCheckExplanationId CheckExplanationID
CICVDefaultLanguageComponent = [Char]
"no-default-language"
ppCheckExplanationId CheckExplanationID
CICVDefaultLanguageComponentSoft = [Char]
"add-language"
ppCheckExplanationId CheckExplanationID
CICVExtraDocFiles = [Char]
"extra-doc-files"
ppCheckExplanationId CheckExplanationID
CICVMultiLib = [Char]
"multilib"
ppCheckExplanationId CheckExplanationID
CICVReexported = [Char]
"reexported-modules"
ppCheckExplanationId CheckExplanationID
CICVMixins = [Char]
"mixins"
ppCheckExplanationId CheckExplanationID
CICVExtraFrameworkDirs = [Char]
"extra-framework-dirs"
ppCheckExplanationId CheckExplanationID
CICVDefaultExtensions = [Char]
"default-extensions"
ppCheckExplanationId CheckExplanationID
CICVExtensionsDeprecated = [Char]
"extensions-field"
ppCheckExplanationId CheckExplanationID
CICVSources = [Char]
"unsupported-sources"
ppCheckExplanationId CheckExplanationID
CICVExtraDynamic = [Char]
"extra-dynamic"
ppCheckExplanationId CheckExplanationID
CICVVirtualModules = [Char]
"virtual-modules"
ppCheckExplanationId CheckExplanationID
CICVSourceRepository = [Char]
"source-repository"
ppCheckExplanationId CheckExplanationID
CICVExtensions = [Char]
"incompatible-extension"
ppCheckExplanationId CheckExplanationID
CICVCustomSetup = [Char]
"no-setup-depends"
ppCheckExplanationId CheckExplanationID
CICVExpliticDepsCustomSetup = [Char]
"dependencies-setup"
ppCheckExplanationId CheckExplanationID
CICVAutogenPaths = [Char]
"no-autogen-paths"
ppCheckExplanationId CheckExplanationID
CICVAutogenPackageInfo = [Char]
"no-autogen-pinfo"
ppCheckExplanationId CheckExplanationID
CICVAutogenPackageInfoGuard = [Char]
"autogen-guard"
ppCheckExplanationId CheckExplanationID
CIGlobNoMatch = [Char]
"no-glob-match"
ppCheckExplanationId CheckExplanationID
CIGlobExactMatch = [Char]
"glob-no-extension"
ppCheckExplanationId CheckExplanationID
CIGlobNoDir = [Char]
"glob-missing-dir"
ppCheckExplanationId CheckExplanationID
CIUnknownOS = [Char]
"unknown-os"
ppCheckExplanationId CheckExplanationID
CIUnknownArch = [Char]
"unknown-arch"
ppCheckExplanationId CheckExplanationID
CIUnknownCompiler = [Char]
"unknown-compiler"
ppCheckExplanationId CheckExplanationID
CIBaseNoUpperBounds = [Char]
"missing-bounds-important"
ppCheckExplanationId CheckExplanationID
CIMissingUpperBounds = [Char]
"missing-upper-bounds"
ppCheckExplanationId CheckExplanationID
CILEUpperBounds = [Char]
"le-upper-bounds"
ppCheckExplanationId CheckExplanationID
CITrailingZeroUpperBounds = [Char]
"tz-upper-bounds"
ppCheckExplanationId CheckExplanationID
CIGTLowerBounds = [Char]
"gt-lower-bounds"
ppCheckExplanationId CheckExplanationID
CISuspiciousFlagName = [Char]
"suspicious-flag"
ppCheckExplanationId CheckExplanationID
CIDeclaredUsedFlags = [Char]
"unused-flag"
ppCheckExplanationId CheckExplanationID
CINonASCIICustomField = [Char]
"non-ascii"
ppCheckExplanationId CheckExplanationID
CIRebindableClashPaths = [Char]
"rebindable-clash-paths"
ppCheckExplanationId CheckExplanationID
CIRebindableClashPackageInfo = [Char]
"rebindable-clash-info"
ppCheckExplanationId CheckExplanationID
CIWErrorUnneeded = [Char]
"werror"
ppCheckExplanationId CheckExplanationID
CIJUnneeded = [Char]
"unneeded-j"
ppCheckExplanationId CheckExplanationID
CIFDeferTypeErrorsUnneeded = [Char]
"fdefer-type-errors"
ppCheckExplanationId CheckExplanationID
CIDynamicUnneeded = [Char]
"debug-flag"
ppCheckExplanationId CheckExplanationID
CIProfilingUnneeded = [Char]
"fprof-flag"
ppCheckExplanationId CheckExplanationID
CIUpperBoundSetup = [Char]
"missing-bounds-setup"
ppCheckExplanationId CheckExplanationID
CIDuplicateModule = [Char]
"duplicate-modules"
ppCheckExplanationId CheckExplanationID
CIPotentialDupModule = [Char]
"maybe-duplicate-modules"
ppCheckExplanationId CheckExplanationID
CIBOMStart = [Char]
"bom"
ppCheckExplanationId CheckExplanationID
CINotPackageName = [Char]
"name-no-match"
ppCheckExplanationId CheckExplanationID
CINoDesc = [Char]
"no-cabal-file"
ppCheckExplanationId CheckExplanationID
CIMultiDesc = [Char]
"multiple-cabal-file"
ppCheckExplanationId CheckExplanationID
CIUnknownFile = [Char]
"unknown-file"
ppCheckExplanationId CheckExplanationID
CIMissingSetupFile = [Char]
"missing-setup"
ppCheckExplanationId CheckExplanationID
CIMissingConfigureScript = [Char]
"missing-conf-script"
ppCheckExplanationId CheckExplanationID
CIUnknownDirectory = [Char]
"unknown-directory"
ppCheckExplanationId CheckExplanationID
CIMissingSourceControl = [Char]
"no-repository"
ppCheckExplanationId CheckExplanationID
CIMissingExpectedDocFiles = [Char]
"no-docs"
ppCheckExplanationId CheckExplanationID
CIWrongFieldForExpectedDocFiles = [Char]
"doc-place"
readExplanationID
:: CheckExplanationIDString
-> Either String CheckExplanationID
readExplanationID :: [Char] -> Either [Char] CheckExplanationID
readExplanationID [Char]
s = Either [Char] CheckExplanationID
-> (CheckExplanationID -> Either [Char] CheckExplanationID)
-> Maybe CheckExplanationID
-> Either [Char] CheckExplanationID
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([Char] -> Either [Char] CheckExplanationID
forall a b. a -> Either a b
Left [Char]
s) CheckExplanationID -> Either [Char] CheckExplanationID
forall a b. b -> Either a b
Right ([Char]
-> [([Char], CheckExplanationID)] -> Maybe CheckExplanationID
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup [Char]
s [([Char], CheckExplanationID)]
idsDict)
where
idsDict :: [(CheckExplanationIDString, CheckExplanationID)]
idsDict :: [([Char], CheckExplanationID)]
idsDict = (CheckExplanationID -> ([Char], CheckExplanationID))
-> [CheckExplanationID] -> [([Char], CheckExplanationID)]
forall a b. (a -> b) -> [a] -> [b]
map (\CheckExplanationID
i -> (CheckExplanationID -> [Char]
ppCheckExplanationId CheckExplanationID
i, CheckExplanationID
i)) [CheckExplanationID
forall a. Bounded a => a
minBound .. CheckExplanationID
forall a. Bounded a => a
maxBound]
data CEType
= CETLibrary LibraryName
| CETForeignLibrary UnqualComponentName
| CETExecutable UnqualComponentName
| CETTest UnqualComponentName
| CETBenchmark UnqualComponentName
| CETSetup
deriving (CEType -> CEType -> Bool
(CEType -> CEType -> Bool)
-> (CEType -> CEType -> Bool) -> Eq CEType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CEType -> CEType -> Bool
== :: CEType -> CEType -> Bool
$c/= :: CEType -> CEType -> Bool
/= :: CEType -> CEType -> Bool
Eq, Eq CEType
Eq CEType =>
(CEType -> CEType -> Ordering)
-> (CEType -> CEType -> Bool)
-> (CEType -> CEType -> Bool)
-> (CEType -> CEType -> Bool)
-> (CEType -> CEType -> Bool)
-> (CEType -> CEType -> CEType)
-> (CEType -> CEType -> CEType)
-> Ord CEType
CEType -> CEType -> Bool
CEType -> CEType -> Ordering
CEType -> CEType -> CEType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: CEType -> CEType -> Ordering
compare :: CEType -> CEType -> Ordering
$c< :: CEType -> CEType -> Bool
< :: CEType -> CEType -> Bool
$c<= :: CEType -> CEType -> Bool
<= :: CEType -> CEType -> Bool
$c> :: CEType -> CEType -> Bool
> :: CEType -> CEType -> Bool
$c>= :: CEType -> CEType -> Bool
>= :: CEType -> CEType -> Bool
$cmax :: CEType -> CEType -> CEType
max :: CEType -> CEType -> CEType
$cmin :: CEType -> CEType -> CEType
min :: CEType -> CEType -> CEType
Ord, Int -> CEType -> [Char] -> [Char]
[CEType] -> [Char] -> [Char]
CEType -> [Char]
(Int -> CEType -> [Char] -> [Char])
-> (CEType -> [Char])
-> ([CEType] -> [Char] -> [Char])
-> Show CEType
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> CEType -> [Char] -> [Char]
showsPrec :: Int -> CEType -> [Char] -> [Char]
$cshow :: CEType -> [Char]
show :: CEType -> [Char]
$cshowList :: [CEType] -> [Char] -> [Char]
showList :: [CEType] -> [Char] -> [Char]
Show)
ppCET :: CEType -> String
ppCET :: CEType -> [Char]
ppCET CEType
cet = case CEType
cet of
CETLibrary LibraryName
ln -> LibraryName -> [Char]
showLibraryName LibraryName
ln
CETForeignLibrary UnqualComponentName
n -> [Char]
"foreign library" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ UnqualComponentName -> [Char]
qn UnqualComponentName
n
CETExecutable UnqualComponentName
n -> [Char]
"executable" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ UnqualComponentName -> [Char]
qn UnqualComponentName
n
CETTest UnqualComponentName
n -> [Char]
"test suite" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ UnqualComponentName -> [Char]
qn UnqualComponentName
n
CETBenchmark UnqualComponentName
n -> [Char]
"benchmark" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ UnqualComponentName -> [Char]
qn UnqualComponentName
n
CEType
CETSetup -> [Char]
"custom-setup"
where
qn :: UnqualComponentName -> String
qn :: UnqualComponentName -> [Char]
qn UnqualComponentName
wn = ([Char]
" " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++) ([Char] -> [Char])
-> (UnqualComponentName -> [Char]) -> UnqualComponentName -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char]
quote ([Char] -> [Char])
-> (UnqualComponentName -> [Char]) -> UnqualComponentName -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnqualComponentName -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow (UnqualComponentName -> [Char]) -> UnqualComponentName -> [Char]
forall a b. (a -> b) -> a -> b
$ UnqualComponentName
wn
data WarnLang = LangC | LangCPlusPlus
deriving (WarnLang -> WarnLang -> Bool
(WarnLang -> WarnLang -> Bool)
-> (WarnLang -> WarnLang -> Bool) -> Eq WarnLang
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WarnLang -> WarnLang -> Bool
== :: WarnLang -> WarnLang -> Bool
$c/= :: WarnLang -> WarnLang -> Bool
/= :: WarnLang -> WarnLang -> Bool
Eq, Eq WarnLang
Eq WarnLang =>
(WarnLang -> WarnLang -> Ordering)
-> (WarnLang -> WarnLang -> Bool)
-> (WarnLang -> WarnLang -> Bool)
-> (WarnLang -> WarnLang -> Bool)
-> (WarnLang -> WarnLang -> Bool)
-> (WarnLang -> WarnLang -> WarnLang)
-> (WarnLang -> WarnLang -> WarnLang)
-> Ord WarnLang
WarnLang -> WarnLang -> Bool
WarnLang -> WarnLang -> Ordering
WarnLang -> WarnLang -> WarnLang
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: WarnLang -> WarnLang -> Ordering
compare :: WarnLang -> WarnLang -> Ordering
$c< :: WarnLang -> WarnLang -> Bool
< :: WarnLang -> WarnLang -> Bool
$c<= :: WarnLang -> WarnLang -> Bool
<= :: WarnLang -> WarnLang -> Bool
$c> :: WarnLang -> WarnLang -> Bool
> :: WarnLang -> WarnLang -> Bool
$c>= :: WarnLang -> WarnLang -> Bool
>= :: WarnLang -> WarnLang -> Bool
$cmax :: WarnLang -> WarnLang -> WarnLang
max :: WarnLang -> WarnLang -> WarnLang
$cmin :: WarnLang -> WarnLang -> WarnLang
min :: WarnLang -> WarnLang -> WarnLang
Ord, Int -> WarnLang -> [Char] -> [Char]
[WarnLang] -> [Char] -> [Char]
WarnLang -> [Char]
(Int -> WarnLang -> [Char] -> [Char])
-> (WarnLang -> [Char])
-> ([WarnLang] -> [Char] -> [Char])
-> Show WarnLang
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> WarnLang -> [Char] -> [Char]
showsPrec :: Int -> WarnLang -> [Char] -> [Char]
$cshow :: WarnLang -> [Char]
show :: WarnLang -> [Char]
$cshowList :: [WarnLang] -> [Char] -> [Char]
showList :: [WarnLang] -> [Char] -> [Char]
Show)
ppWarnLang :: WarnLang -> String
ppWarnLang :: WarnLang -> [Char]
ppWarnLang WarnLang
LangC = [Char]
"C"
ppWarnLang WarnLang
LangCPlusPlus = [Char]
"C++"
ppExplanation :: CheckExplanation -> String
ppExplanation :: CheckExplanation -> [Char]
ppExplanation (ParseWarning [Char]
fp PWarning
pp) = [Char] -> PWarning -> [Char]
showPWarning [Char]
fp PWarning
pp
ppExplanation CheckExplanation
NoNameField = [Char]
"No 'name' field."
ppExplanation CheckExplanation
NoVersionField = [Char]
"No 'version' field."
ppExplanation CheckExplanation
NoTarget =
[Char]
"No executables, libraries, tests, or benchmarks found. Nothing to do."
ppExplanation CheckExplanation
UnnamedInternal =
[Char]
"Found one or more unnamed internal libraries. Only the non-internal"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" library can have the same name as the package."
ppExplanation (DuplicateSections [UnqualComponentName]
duplicateNames) =
[Char]
"Duplicate sections: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep ((UnqualComponentName -> [Char])
-> [UnqualComponentName] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map UnqualComponentName -> [Char]
unUnqualComponentName [UnqualComponentName]
duplicateNames)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
". The name of every library, executable, test suite,"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" and benchmark section in the package must be unique."
ppExplanation (IllegalLibraryName PackageName
pname) =
[Char]
"Illegal internal library name "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ PackageName -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow PackageName
pname
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
". Internal libraries cannot have the same name as the package."
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" Maybe you wanted a non-internal library?"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" If so, rewrite the section stanza"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" from 'library: '"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ PackageName -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow PackageName
pname
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"' to 'library'."
ppExplanation (NoModulesExposed LibraryName
lName) =
LibraryName -> [Char]
showLibraryName LibraryName
lName [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" does not expose any modules"
ppExplanation CheckExplanation
SignaturesCabal2 =
[Char]
"To use the 'signatures' field the package needs to specify "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"at least 'cabal-version: 2.0'."
ppExplanation CheckExplanation
AutogenNotExposed =
[Char]
"An 'autogen-module' is neither on 'exposed-modules' nor 'other-modules'."
ppExplanation CheckExplanation
AutogenIncludesNotIncluded =
[Char]
"An include in 'autogen-includes' is neither in 'includes' nor "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"'install-includes'."
ppExplanation (NoMainIs UnqualComponentName
eName) =
[Char]
"No 'main-is' field found for executable " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ UnqualComponentName -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow UnqualComponentName
eName
ppExplanation CheckExplanation
NoHsLhsMain =
[Char]
"The 'main-is' field must specify a '.hs' or '.lhs' file "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"(even if it is generated by a preprocessor), "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"or it may specify a C/C++/obj-C source file."
ppExplanation CheckExplanation
MainCCabal1_18 =
[Char]
"The package uses a C/C++/obj-C source file for the 'main-is' field. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"To use this feature you need to specify 'cabal-version: 1.18' or"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" higher."
ppExplanation (AutogenNoOther CEType
ct) =
[Char]
"On "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ CEType -> [Char]
ppCET CEType
ct
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" an 'autogen-module'"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" is not on 'other-modules'"
ppExplanation CheckExplanation
AutogenIncludesNotIncludedExe =
[Char]
"An include in 'autogen-includes' is not in 'includes'."
ppExplanation (TestsuiteTypeNotKnown TestType
tt) =
[Char] -> [Char]
quote (TestType -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow TestType
tt)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" is not a known type of test suite. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Either remove the 'type' field or use a known type. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"The known test suite types are: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep ((TestType -> [Char]) -> [TestType] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map TestType -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow [TestType]
knownTestTypes)
ppExplanation (TestsuiteNotSupported TestType
tt) =
[Char] -> [Char]
quote (TestType -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow TestType
tt)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" is not a supported test suite version. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Either remove the 'type' field or use a known type. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"The known test suite types are: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep ((TestType -> [Char]) -> [TestType] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map TestType -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow [TestType]
knownTestTypes)
ppExplanation (BenchmarkTypeNotKnown BenchmarkType
tt) =
[Char] -> [Char]
quote (BenchmarkType -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow BenchmarkType
tt)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" is not a known type of benchmark. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Either remove the 'type' field or use a known type. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"The known benchmark types are: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep ((BenchmarkType -> [Char]) -> [BenchmarkType] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map BenchmarkType -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow [BenchmarkType]
knownBenchmarkTypes)
ppExplanation (BenchmarkNotSupported BenchmarkType
tt) =
[Char] -> [Char]
quote (BenchmarkType -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow BenchmarkType
tt)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" is not a supported benchmark version. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Either remove the 'type' field or use a known type. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"The known benchmark types are: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep ((BenchmarkType -> [Char]) -> [BenchmarkType] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map BenchmarkType -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow [BenchmarkType]
knownBenchmarkTypes)
ppExplanation CheckExplanation
NoHsLhsMainBench =
[Char]
"The 'main-is' field must specify a '.hs' or '.lhs' file "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"(even if it is generated by a preprocessor)."
ppExplanation (InvalidNameWin PackageName
pkg) =
[Char]
"The package name '"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ PackageName -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow PackageName
pkg
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"' is "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"invalid on Windows. Many tools need to convert package names to "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"file names, so using this name would cause problems."
ppExplanation CheckExplanation
ZPrefix =
[Char]
"Package names with the prefix 'z-' are reserved by Cabal and "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"cannot be used."
ppExplanation CheckExplanation
NoBuildType =
[Char]
"No 'build-type' specified. If you do not need a custom Setup.hs or "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"./configure script then use 'build-type: Simple'."
ppExplanation CheckExplanation
NoCustomSetup =
[Char]
"Ignoring the 'custom-setup' section because the 'build-type' is "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"not 'Custom'. Use 'build-type: Custom' if you need to use a "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"custom Setup.hs script."
ppExplanation (UnknownCompilers [[Char]]
unknownCompilers) =
[Char]
"Unknown compiler "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep (([Char] -> [Char]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map [Char] -> [Char]
quote [[Char]]
unknownCompilers)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" in 'tested-with' field."
ppExplanation (UnknownLanguages [[Char]]
unknownLanguages) =
[Char]
"Unknown languages: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep [[Char]]
unknownLanguages
ppExplanation (UnknownExtensions [[Char]]
unknownExtensions) =
[Char]
"Unknown extensions: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep [[Char]]
unknownExtensions
ppExplanation (LanguagesAsExtension [[Char]]
languagesUsedAsExtensions) =
[Char]
"Languages listed as extensions: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep [[Char]]
languagesUsedAsExtensions
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
". Languages must be specified in either the 'default-language' "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" or the 'other-languages' field."
ppExplanation (DeprecatedExtensions [(Extension, Maybe Extension)]
ourDeprecatedExtensions) =
[Char]
"Deprecated extensions: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep (((Extension, Maybe Extension) -> [Char])
-> [(Extension, Maybe Extension)] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map ([Char] -> [Char]
quote ([Char] -> [Char])
-> ((Extension, Maybe Extension) -> [Char])
-> (Extension, Maybe Extension)
-> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Extension -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow (Extension -> [Char])
-> ((Extension, Maybe Extension) -> Extension)
-> (Extension, Maybe Extension)
-> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Extension, Maybe Extension) -> Extension
forall a b. (a, b) -> a
fst) [(Extension, Maybe Extension)]
ourDeprecatedExtensions)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
". "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
unwords
[ [Char]
"Instead of '"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Extension -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow Extension
ext
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"' use '"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Extension -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow Extension
replacement
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"'."
| (Extension
ext, Just Extension
replacement) <- [(Extension, Maybe Extension)]
ourDeprecatedExtensions
]
ppExplanation CheckExplanation
MissingFieldCategory = [Char]
"No 'category' field."
ppExplanation CheckExplanation
MissingFieldMaintainer = [Char]
"No 'maintainer' field."
ppExplanation CheckExplanation
MissingFieldSynopsis = [Char]
"No 'synopsis' field."
ppExplanation CheckExplanation
MissingFieldDescription = [Char]
"No 'description' field."
ppExplanation CheckExplanation
MissingFieldSynOrDesc = [Char]
"No 'synopsis' or 'description' field."
ppExplanation CheckExplanation
SynopsisTooLong =
[Char]
"The 'synopsis' field is rather long (max 80 chars is recommended)."
ppExplanation CheckExplanation
ShortDesc =
[Char]
"The 'description' field should be longer than the 'synopsis' field. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"It's useful to provide an informative 'description' to allow "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Haskell programmers who have never heard about your package to "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"understand the purpose of your package. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"The 'description' field content is typically shown by tooling "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"(e.g. 'cabal info', Haddock, Hackage) below the 'synopsis' which "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"serves as a headline. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Please refer to <https://cabal.readthedocs.io/en/stable/"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"cabal-package.html#package-properties> for more details."
ppExplanation (InvalidTestWith [Dependency]
testedWithImpossibleRanges) =
[Char]
"Invalid 'tested-with' version range: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep ((Dependency -> [Char]) -> [Dependency] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map Dependency -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow [Dependency]
testedWithImpossibleRanges)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
". To indicate that you have tested a package with multiple "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"different versions of the same compiler use multiple entries, "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"for example 'tested-with: GHC==6.10.4, GHC==6.12.3' and not "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"'tested-with: GHC==6.10.4 && ==6.12.3'."
ppExplanation (ImpossibleInternalDep [Dependency]
depInternalLibWithImpossibleVersion) =
[Char]
"The package has an impossible version range for a dependency on an "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"internal library: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep ((Dependency -> [Char]) -> [Dependency] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map Dependency -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow [Dependency]
depInternalLibWithImpossibleVersion)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
". This version range does not include the current package, and must "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"be removed as the current package's library will always be used."
ppExplanation (ImpossibleInternalExe [ExeDependency]
depInternalExecWithImpossibleVersion) =
[Char]
"The package has an impossible version range for a dependency on an "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"internal executable: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep ((ExeDependency -> [Char]) -> [ExeDependency] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map ExeDependency -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow [ExeDependency]
depInternalExecWithImpossibleVersion)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
". This version range does not include the current package, and must "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"be removed as the current package's executable will always be used."
ppExplanation (MissingInternalExe [ExeDependency]
depInternalExeWithImpossibleVersion) =
[Char]
"The package depends on a missing internal executable: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep ((ExeDependency -> [Char]) -> [ExeDependency] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map ExeDependency -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow [ExeDependency]
depInternalExeWithImpossibleVersion)
ppExplanation CheckExplanation
NONELicense = [Char]
"The 'license' field is missing or is NONE."
ppExplanation CheckExplanation
NoLicense = [Char]
"The 'license' field is missing."
ppExplanation CheckExplanation
AllRightsReservedLicense =
[Char]
"The 'license' is AllRightsReserved. Is that really what you want?"
ppExplanation (LicenseMessParse License
lic) =
[Char]
"Unfortunately the license "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
quote (License -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow License
lic)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" messes up the parser in earlier Cabal versions so you need to "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"specify 'cabal-version: >= 1.4'. Alternatively if you require "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"compatibility with earlier Cabal versions then use 'OtherLicense'."
ppExplanation (UnrecognisedLicense [Char]
l) =
[Char] -> [Char]
quote ([Char]
"license: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
l)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" is not a recognised license. The "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"known licenses are: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep ((License -> [Char]) -> [License] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map License -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow [License]
knownLicenses)
ppExplanation CheckExplanation
UncommonBSD4 =
[Char]
"Using 'license: BSD4' is almost always a misunderstanding. 'BSD4' "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"refers to the old 4-clause BSD license with the advertising "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"clause. 'BSD3' refers the new 3-clause BSD license."
ppExplanation (UnknownLicenseVersion License
lic [Version]
known) =
[Char]
"'license: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ License -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow License
lic
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"' is not a known "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"version of that license. The known versions are "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep ((Version -> [Char]) -> [Version] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map Version -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow [Version]
known)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
". If this is not a mistake and you think it should be a known "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"version then please file a ticket."
ppExplanation CheckExplanation
NoLicenseFile = [Char]
"A 'license-file' is not specified."
ppExplanation (UnrecognisedSourceRepo [Char]
kind) =
[Char] -> [Char]
quote [Char]
kind
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" is not a recognised kind of source-repository. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"The repo kind is usually 'head' or 'this'"
ppExplanation CheckExplanation
MissingType =
[Char]
"The source-repository 'type' is a required field."
ppExplanation CheckExplanation
MissingLocation =
[Char]
"The source-repository 'location' is a required field."
ppExplanation CheckExplanation
GitProtocol =
[Char]
"Cloning over git:// might lead to an arbitrary code execution "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"vulnerability. Furthermore, popular forges like GitHub do "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"not support it. Use https:// or ssh:// instead."
ppExplanation CheckExplanation
MissingModule =
[Char]
"For a CVS source-repository, the 'module' is a required field."
ppExplanation CheckExplanation
MissingTag =
[Char]
"For the 'this' kind of source-repository, the 'tag' is a required "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"field. It should specify the tag corresponding to this version "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"or release of the package."
ppExplanation CheckExplanation
SubdirRelPath =
[Char]
"The 'subdir' field of a source-repository must be a relative path."
ppExplanation (SubdirGoodRelPath [Char]
err) =
[Char]
"The 'subdir' field of a source-repository is not a good relative path: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
forall a. Show a => a -> [Char]
show [Char]
err
ppExplanation (OptFasm [Char]
fieldName) =
[Char]
"'"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
fieldName
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": -fasm' is unnecessary and will not work on CPU "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"architectures other than x86, x86-64, ppc or sparc."
ppExplanation (OptHpc [Char]
fieldName) =
[Char]
"'"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
fieldName
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": -fhpc' is not necessary. Use the configure flag "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" --enable-coverage instead."
ppExplanation (OptProf [Char]
fieldName) =
[Char]
"'"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
fieldName
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": -prof' is not necessary and will lead to problems "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"when used on a library. Use the configure flag "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"--enable-library-profiling and/or --enable-profiling."
ppExplanation (OptO [Char]
fieldName) =
[Char]
"'"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
fieldName
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": -o' is not needed. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"The output files are named automatically."
ppExplanation (OptHide [Char]
fieldName) =
[Char]
"'"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
fieldName
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": -hide-package' is never needed. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Cabal hides all packages."
ppExplanation (OptMake [Char]
fieldName) =
[Char]
"'"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
fieldName
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": --make' is never needed. Cabal uses this automatically."
ppExplanation (OptONot [Char]
fieldName) =
[Char]
"'"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
fieldName
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": -O0' is not needed. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Use the --disable-optimization configure flag."
ppExplanation (OptOOne [Char]
fieldName) =
[Char]
"'"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
fieldName
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": -O' is not needed. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Cabal automatically adds the '-O' flag. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Setting it yourself interferes with the --disable-optimization flag."
ppExplanation (OptOTwo [Char]
fieldName) =
[Char]
"'"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
fieldName
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": -O2' is rarely needed. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Check that it is giving a real benefit "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"and not just imposing longer compile times on your users."
ppExplanation (OptSplitSections [Char]
fieldName) =
[Char]
"'"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
fieldName
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": -split-sections' is not needed. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Use the --enable-split-sections configure flag."
ppExplanation (OptSplitObjs [Char]
fieldName) =
[Char]
"'"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
fieldName
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": -split-objs' is not needed. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Use the --enable-split-objs configure flag."
ppExplanation (OptWls [Char]
fieldName) =
[Char]
"'"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
fieldName
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": -optl-Wl,-s' is not needed and is not portable to"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" all operating systems. Cabal 1.4 and later automatically strip"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" executables. Cabal also has a flag --disable-executable-stripping"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" which is necessary when building packages for some Linux"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" distributions and using '-optl-Wl,-s' prevents that from working."
ppExplanation (OptExts [Char]
fieldName) =
[Char]
"Instead of '"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
fieldName
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": -fglasgow-exts' it is preferable to use "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"the 'extensions' field."
ppExplanation (OptRts [Char]
fieldName) =
[Char]
"'"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
fieldName
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": -rtsopts' has no effect for libraries. It should "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"only be used for executables."
ppExplanation (OptWithRts [Char]
fieldName) =
[Char]
"'"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
fieldName
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": -with-rtsopts' has no effect for libraries. It "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"should only be used for executables."
ppExplanation (COptONumber [Char]
prefix WarnLang
label) =
[Char]
"'"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
prefix
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": -O[n]' is generally not needed. When building with "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" optimisations Cabal automatically adds '-O2' for "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ WarnLang -> [Char]
ppWarnLang WarnLang
label
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" code. Setting it yourself interferes with the"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" --disable-optimization flag."
ppExplanation (COptCPP [Char]
opt) =
[Char]
"'cpp-options: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
opt [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"' is not a portable C-preprocessor flag."
ppExplanation (OptJSPP [Char]
opt) =
[Char]
"'jspp-options: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
opt [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"' is not a portable JavaScript-preprocessor flag."
ppExplanation (OptAlternatives [Char]
badField [Char]
goodField [([Char], [Char])]
flags) =
[Char]
"Instead of "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
quote ([Char]
badField [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
unwords [[Char]]
badFlags)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" use "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
quote ([Char]
goodField [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
unwords [[Char]]
goodFlags)
where
([[Char]]
badFlags, [[Char]]
goodFlags) = [([Char], [Char])] -> ([[Char]], [[Char]])
forall a b. [(a, b)] -> ([a], [b])
unzip [([Char], [Char])]
flags
ppExplanation (RelativeOutside [Char]
field [Char]
path) =
[Char] -> [Char]
quote ([Char]
field [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
path)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" is a relative path outside of the source tree. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"This will not work when generating a tarball with 'sdist'."
ppExplanation (AbsolutePath [Char]
field [Char]
path) =
[Char] -> [Char]
quote ([Char]
field [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
path)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" specifies an absolute path, but the "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
quote [Char]
field
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" field must use relative paths."
ppExplanation (BadRelativePath [Char]
field [Char]
path [Char]
err) =
[Char] -> [Char]
quote ([Char]
field [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
path)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" is not a good relative path: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
forall a. Show a => a -> [Char]
show [Char]
err
ppExplanation (DistPoint Maybe [Char]
mfield [Char]
path) =
[Char]
incipit
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" points inside the 'dist' "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"directory. This is not reliable because the location of this "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"directory is configurable by the user (or package manager). In "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"addition, the layout of the 'dist' directory is subject to change "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"in future versions of Cabal."
where
incipit :: [Char]
incipit =
[Char] -> ([Char] -> [Char]) -> Maybe [Char] -> [Char]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
([Char]
"'ghc-options' path " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
quote [Char]
path)
(\[Char]
field -> [Char] -> [Char]
quote ([Char]
field [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
path))
Maybe [Char]
mfield
ppExplanation (GlobSyntaxError [Char]
field [Char]
expl) =
[Char]
"In the '" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
field [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"' field: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
expl
ppExplanation (RecursiveGlobInRoot [Char]
field [Char]
glob) =
[Char]
"In the '"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
field
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"': glob '"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
glob
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"' starts at project root directory, this might "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"include `.git/`, ``dist-newstyle/``, or other large directories!"
ppExplanation (InvalidOnWin [[Char]]
paths) =
[Char]
"The "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
quotes [[Char]]
paths
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" invalid on Windows, which "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"would cause portability problems for this package. Windows file "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"names cannot contain any of the characters \":*?<>|\", and there "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"are a few reserved names including \"aux\", \"nul\", \"con\", "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"\"prn\", \"com{1-9}\", \"lpt{1-9}\" and \"clock$\"."
where
quotes :: [[Char]] -> [Char]
quotes [[Char]
failed] = [Char]
"path " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
quote [Char]
failed [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" is"
quotes [[Char]]
failed =
[Char]
"paths "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep (([Char] -> [Char]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map [Char] -> [Char]
quote [[Char]]
failed)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" are"
ppExplanation (FilePathTooLong [Char]
path) =
[Char]
"The following file name is too long to store in a portable POSIX "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"format tar archive. The maximum length is 255 ASCII characters.\n"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"The file in question is:\n "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
path
ppExplanation (FilePathNameTooLong [Char]
path) =
[Char]
"The following file name is too long to store in a portable POSIX "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"format tar archive. The maximum length for the name part (including "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"extension) is 100 ASCII characters. The maximum length for any "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"individual directory component is 155.\n"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"The file in question is:\n "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
path
ppExplanation (FilePathSplitTooLong [Char]
path) =
[Char]
"The following file name is too long to store in a portable POSIX "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"format tar archive. While the total length is less than 255 ASCII "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"characters, there are unfortunately further restrictions. It has to "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"be possible to split the file path on a directory separator into "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"two parts such that the first part fits in 155 characters or less "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"and the second part fits in 100 characters or less. Basically you "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"have to make the file name or directory names shorter, or you could "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"split a long directory name into nested subdirectories with shorter "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"names.\nThe file in question is:\n "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
path
ppExplanation CheckExplanation
FilePathEmpty =
[Char]
"Encountered a file with an empty name, something is very wrong! "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Files with an empty name cannot be stored in a tar archive or in "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"standard file systems."
ppExplanation CheckExplanation
CVTestSuite =
[Char]
"The 'test-suite' section is new in Cabal 1.10. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Unfortunately it messes up the parser in older Cabal versions "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"so you must specify at least 'cabal-version: >= 1.8', but note "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"that only Cabal 1.10 and later can actually run such test suites."
ppExplanation CheckExplanation
CVDefaultLanguage =
[Char]
"To use the 'default-language' field the package needs to specify "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"at least 'cabal-version: >= 1.10'."
ppExplanation CheckExplanation
CVDefaultLanguageComponent =
[Char]
"Packages using 'cabal-version: >= 1.10' and before 'cabal-version: 3.4' "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"must specify the 'default-language' field for each component (e.g. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Haskell98 or Haskell2010). If a component uses different languages "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"in different modules then list the other ones in the "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"'other-languages' field."
ppExplanation CheckExplanation
CVDefaultLanguageComponentSoft =
[Char]
"Without `default-language`, cabal will default to Haskell98, which is "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"probably not what you want. Please add `default-language` to all "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"targets."
ppExplanation CheckExplanation
CVExtraDocFiles =
[Char]
"To use the 'extra-doc-files' field the package needs to specify "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"'cabal-version: 1.18' or higher."
ppExplanation CheckExplanation
CVMultiLib =
[Char]
"To use multiple 'library' sections or a named library section "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"the package needs to specify at least 'cabal-version: 2.0'."
ppExplanation CheckExplanation
CVReexported =
[Char]
"To use the 'reexported-module' field the package needs to specify "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"'cabal-version: 1.22' or higher."
ppExplanation CheckExplanation
CVMixins =
[Char]
"To use the 'mixins' field the package needs to specify "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"at least 'cabal-version: 2.0'."
ppExplanation CheckExplanation
CVExtraFrameworkDirs =
[Char]
"To use the 'extra-framework-dirs' field the package needs to specify"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" 'cabal-version: 1.24' or higher."
ppExplanation CheckExplanation
CVDefaultExtensions =
[Char]
"To use the 'default-extensions' field the package needs to specify "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"at least 'cabal-version: >= 1.10'."
ppExplanation CheckExplanation
CVExtensionsDeprecated =
[Char]
"For packages using 'cabal-version: >= 1.10' the 'extensions' "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"field is deprecated. The new 'default-extensions' field lists "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"extensions that are used in all modules in the component, while "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"the 'other-extensions' field lists extensions that are used in "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"some modules, e.g. via the {-# LANGUAGE #-} pragma."
ppExplanation CheckExplanation
CVSources =
[Char]
"The use of 'asm-sources', 'cmm-sources', 'extra-bundled-libraries' "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" and 'extra-library-flavours' requires the package "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" to specify at least 'cabal-version: 3.0'."
ppExplanation (CVExtraDynamic [[[Char]]]
flavs) =
[Char]
"The use of 'extra-dynamic-library-flavours' requires the package "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" to specify at least 'cabal-version: 3.0'. The flavours are: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep ([[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[[Char]]]
flavs)
ppExplanation CheckExplanation
CVVirtualModules =
[Char]
"The use of 'virtual-modules' requires the package "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" to specify at least 'cabal-version: 2.2'."
ppExplanation CheckExplanation
CVSourceRepository =
[Char]
"The 'source-repository' section is new in Cabal 1.6. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Unfortunately it messes up the parser in earlier Cabal versions "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"so you need to specify 'cabal-version: >= 1.6'."
ppExplanation (CVExtensions CabalSpecVersion
version [Extension]
extCab12) =
[Char]
"Unfortunately the language extensions "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep ((Extension -> [Char]) -> [Extension] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map ([Char] -> [Char]
quote ([Char] -> [Char]) -> (Extension -> [Char]) -> Extension -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Extension -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow) [Extension]
extCab12)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" break the parser in earlier Cabal versions so you need to "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"specify 'cabal-version: >= "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ CabalSpecVersion -> [Char]
showCabalSpecVersion CabalSpecVersion
version
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"'. Alternatively if you require compatibility with earlier "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Cabal versions then you may be able to use an equivalent "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"compiler-specific flag."
ppExplanation CheckExplanation
CVCustomSetup =
[Char]
"Packages using 'cabal-version: 1.24' or higher with 'build-type: Custom' "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"must use a 'custom-setup' section with a 'setup-depends' field "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"that specifies the dependencies of the Setup.hs script itself. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"The 'setup-depends' field uses the same syntax as 'build-depends', "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"so a simple example would be 'setup-depends: base, Cabal'."
ppExplanation CheckExplanation
CVExpliticDepsCustomSetup =
[Char]
"From version 1.24 cabal supports specifying explicit dependencies "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"for Custom setup scripts. Consider using 'cabal-version: 1.24' or "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"higher and adding a 'custom-setup' section with a 'setup-depends' "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"field that specifies the dependencies of the Setup.hs script "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"itself. The 'setup-depends' field uses the same syntax as "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"'build-depends', so a simple example would be 'setup-depends: base, "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Cabal'."
ppExplanation CheckExplanation
CVAutogenPaths =
[Char]
"Packages using 'cabal-version: 2.0' and the autogenerated "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"module Paths_* must include it also on the 'autogen-modules' field "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"besides 'exposed-modules' and 'other-modules'. This specifies that "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"the module does not come with the package and is generated on "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"setup. Modules built with a custom Setup.hs script also go here "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"to ensure that commands like sdist don't fail."
ppExplanation CheckExplanation
CVAutogenPackageInfo =
[Char]
"Packages using 'cabal-version: 2.0' and the autogenerated "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"module PackageInfo_* must include it in 'autogen-modules' as well as"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" 'exposed-modules' and 'other-modules'. This specifies that "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"the module does not come with the package and is generated on "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"setup. Modules built with a custom Setup.hs script also go here "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"to ensure that commands like sdist don't fail."
ppExplanation CheckExplanation
CVAutogenPackageInfoGuard =
[Char]
"To use the autogenerated module PackageInfo_* you need to specify "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"`cabal-version: 3.12` or higher."
ppExplanation (GlobNoMatch [Char]
field [Char]
glob) =
[Char]
"In '"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
field
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"': the pattern '"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
glob
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"' does not"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" match any files."
ppExplanation (GlobExactMatch [Char]
field [Char]
glob [Char]
file) =
[Char]
"In '"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
field
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"': the pattern '"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
glob
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"' does not"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" match the file '"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
file
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"' because the extensions do not"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" exactly match (e.g., foo.en.html does not exactly match *.html)."
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" To enable looser suffix-only matching, set 'cabal-version: 2.4' or"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" higher."
ppExplanation (GlobNoDir [Char]
field [Char]
glob [Char]
dir) =
[Char]
"In '"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
field
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"': the pattern '"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
glob
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"' attempts to"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" match files in the directory '"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
dir
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"', but there is no"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" directory by that name."
ppExplanation (UnknownOS [[Char]]
unknownOSs) =
[Char]
"Unknown operating system name " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep (([Char] -> [Char]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map [Char] -> [Char]
quote [[Char]]
unknownOSs)
ppExplanation (UnknownArch [[Char]]
unknownArches) =
[Char]
"Unknown architecture name " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep (([Char] -> [Char]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map [Char] -> [Char]
quote [[Char]]
unknownArches)
ppExplanation (UnknownCompiler [[Char]]
unknownImpls) =
[Char]
"Unknown compiler name " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep (([Char] -> [Char]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map [Char] -> [Char]
quote [[Char]]
unknownImpls)
ppExplanation CheckExplanation
BaseNoUpperBounds =
[Char]
"The dependency 'build-depends: base' does not specify an upper "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"bound on the version number. Each major release of the 'base' "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"package changes the API in various ways and most packages will "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"need some changes to compile with it. The recommended practice "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"is to specify an upper bound on the version of the 'base' "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"package. This ensures your package will continue to build when a "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"new major version of the 'base' package is released. If you are "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"not sure what upper bound to use then use the next major "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"version. For example if you have tested your package with 'base' "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"version 4.5 and 4.6 then use 'build-depends: base >= 4.5 && < 4.7'."
ppExplanation (MissingUpperBounds CEType
ct [[Char]]
names) =
[Char]
"On "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ CEType -> [Char]
ppCET CEType
ct
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
", "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"these packages miss upper bounds:"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
listSep [[Char]]
names
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Please add them. There is more information at https://pvp.haskell.org/"
ppExplanation (LEUpperBounds CEType
ct [[Char]]
names) =
[Char]
"On "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ CEType -> [Char]
ppCET CEType
ct
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
", "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"these packages have less than or equals (<=) upper bounds:"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
listSep [[Char]]
names
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Please use less than (<) for upper bounds."
ppExplanation (TrailingZeroUpperBounds CEType
ct [[Char]]
names) =
[Char]
"On "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ CEType -> [Char]
ppCET CEType
ct
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
", "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"these packages have upper bounds with trailing zeros:"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
listSep [[Char]]
names
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Please avoid trailing zeros for upper bounds."
ppExplanation (GTLowerBounds CEType
ct [[Char]]
names) =
[Char]
"On "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ CEType -> [Char]
ppCET CEType
ct
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
", "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"these packages have greater than (>) lower bounds:"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
listSep [[Char]]
names
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Please use greater than or equals (>=) for lower bounds."
ppExplanation (SuspiciousFlagName [[Char]]
invalidFlagNames) =
[Char]
"Suspicious flag names: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
unwords [[Char]]
invalidFlagNames
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
". "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"To avoid ambiguity in command line interfaces, a flag shouldn't "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"start with a dash. Also for better compatibility, flag names "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"shouldn't contain non-ascii characters."
ppExplanation (DeclaredUsedFlags Set FlagName
declared Set FlagName
used) =
[Char]
"Declared and used flag sets differ: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Set FlagName -> [Char]
s Set FlagName
declared
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" /= "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Set FlagName -> [Char]
s Set FlagName
used
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
". "
where
s :: Set.Set FlagName -> String
s :: Set FlagName -> [Char]
s = [[Char]] -> [Char]
commaSep ([[Char]] -> [Char])
-> (Set FlagName -> [[Char]]) -> Set FlagName -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FlagName -> [Char]) -> [FlagName] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map FlagName -> [Char]
unFlagName ([FlagName] -> [[Char]])
-> (Set FlagName -> [FlagName]) -> Set FlagName -> [[Char]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set FlagName -> [FlagName]
forall a. Set a -> [a]
Set.toList
ppExplanation (NonASCIICustomField [[Char]]
nonAsciiXFields) =
[Char]
"Non ascii custom fields: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
unwords [[Char]]
nonAsciiXFields
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
". "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"For better compatibility, custom field names "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"shouldn't contain non-ascii characters."
ppExplanation CheckExplanation
RebindableClashPaths =
[Char]
"Packages using RebindableSyntax with OverloadedStrings or"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" OverloadedLists in default-extensions, in conjunction with the"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" autogenerated module Paths_*, are known to cause compile failures"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" with Cabal < 2.2. To use these default-extensions with a Paths_*"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" autogen module, specify at least 'cabal-version: 2.2'."
ppExplanation CheckExplanation
RebindableClashPackageInfo =
[Char]
"Packages using RebindableSyntax with OverloadedStrings or"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" OverloadedLists in default-extensions, in conjunction with the"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" autogenerated module PackageInfo_*, are known to cause compile failures"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" with Cabal < 2.2. To use these default-extensions with a PackageInfo_*"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" autogen module, specify at least 'cabal-version: 2.2'."
ppExplanation (WErrorUnneeded [Char]
fieldName) =
[Char] -> [Char]
addConditionalExp ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$
[Char]
"'"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
fieldName
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": -Werror' makes the package easy to "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"break with future GHC versions because new GHC versions often "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"add new warnings."
ppExplanation (JUnneeded [Char]
fieldName) =
[Char] -> [Char]
addConditionalExp ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$
[Char]
"'"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
fieldName
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": -j[N]' can make sense for a particular user's setup,"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" but it is not appropriate for a distributed package."
ppExplanation (FDeferTypeErrorsUnneeded [Char]
fieldName) =
[Char] -> [Char]
addConditionalExp ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$
[Char]
"'"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
fieldName
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": -fdefer-type-errors' is fine during development "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"but is not appropriate for a distributed package."
ppExplanation (DynamicUnneeded [Char]
fieldName) =
[Char] -> [Char]
addConditionalExp ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$
[Char]
"'"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
fieldName
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": -d*' debug flags are not appropriate "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"for a distributed package."
ppExplanation (ProfilingUnneeded [Char]
fieldName) =
[Char] -> [Char]
addConditionalExp ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$
[Char]
"'"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
fieldName
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": -fprof*' profiling flags are typically not "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"appropriate for a distributed library package. These flags are "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"useful to profile this package, but when profiling other packages "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"that use this one these flags clutter the profile output with "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"excessive detail. If you think other packages really want to see "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"cost centres from this package then use '-fprof-auto-exported' "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"which puts cost centres only on exported functions."
ppExplanation (UpperBoundSetup [Char]
nm) =
[Char]
"The dependency 'setup-depends: '"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
nm
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"' does not specify an "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"upper bound on the version number. Each major release of the "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"'"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
nm
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"' package changes the API in various ways and most "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"packages will need some changes to compile with it. If you are "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"not sure what upper bound to use then use the next major "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"version."
ppExplanation (DuplicateModule [Char]
s [ModuleName]
dupLibsLax) =
[Char]
"Duplicate modules in "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
s
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep ((ModuleName -> [Char]) -> [ModuleName] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map ModuleName -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow [ModuleName]
dupLibsLax)
ppExplanation (PotentialDupModule [Char]
s [ModuleName]
dupLibsStrict) =
[Char]
"Potential duplicate modules (subject to conditionals) in "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
s
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep ((ModuleName -> [Char]) -> [ModuleName] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map ModuleName -> [Char]
forall a. Pretty a => a -> [Char]
prettyShow [ModuleName]
dupLibsStrict)
ppExplanation (BOMStart [Char]
pdfile) =
[Char]
pdfile
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" starts with an Unicode byte order mark (BOM)."
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" This may cause problems with older cabal versions."
ppExplanation (NotPackageName [Char]
pdfile [Char]
expectedCabalname) =
[Char]
"The filename "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
quote [Char]
pdfile
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" does not match package name "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"(expected: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
quote [Char]
expectedCabalname
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
")"
ppExplanation CheckExplanation
NoDesc =
[Char]
"No cabal file found.\n"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Please create a package description file <pkgname>.cabal"
ppExplanation (MultiDesc [[Char]]
multiple) =
[Char]
"Multiple cabal files found while checking.\n"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"Please use only one of: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep [[Char]]
multiple
ppExplanation (UnknownFile [Char]
fieldname SymbolicPathX 'OnlyRelative Pkg 'File
file) =
[Char]
"The '"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
fieldname
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"' field refers to the file "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
quote (SymbolicPathX 'OnlyRelative Pkg 'File -> [Char]
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> [Char]
getSymbolicPath SymbolicPathX 'OnlyRelative Pkg 'File
file)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" which does not exist."
ppExplanation CheckExplanation
MissingSetupFile =
[Char]
"The package is missing a Setup.hs or Setup.lhs script."
ppExplanation CheckExplanation
MissingConfigureScript =
[Char]
"The 'build-type' is 'Configure' but there is no 'configure' script. "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"You probably need to run 'autoreconf -i' to generate it."
ppExplanation (UnknownDirectory [Char]
kind [Char]
dir) =
[Char] -> [Char]
quote ([Char]
kind [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
": " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
dir)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" specifies a directory which does not exist."
ppExplanation CheckExplanation
MissingSourceControl =
[Char]
"When distributing packages, it is encouraged to specify source "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"control information in the .cabal file using one or more "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"'source-repository' sections. See the Cabal user guide for "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"details."
ppExplanation (MissingExpectedDocFiles Bool
extraDocFileSupport [[Char]]
paths) =
[Char]
"Please consider including the "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
quotes [[Char]]
paths
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" in the '"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
targetField
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"' section of the .cabal file "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"if it contains useful information for users of the package."
where
quotes :: [[Char]] -> [Char]
quotes [[Char]
p] = [Char]
"file " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
quote [Char]
p
quotes [[Char]]
ps = [Char]
"files " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep (([Char] -> [Char]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map [Char] -> [Char]
quote [[Char]]
ps)
targetField :: [Char]
targetField =
if Bool
extraDocFileSupport
then [Char]
"extra-doc-files"
else [Char]
"extra-source-files"
ppExplanation (WrongFieldForExpectedDocFiles Bool
extraDocFileSupport [Char]
field [[Char]]
paths) =
[Char]
"Please consider moving the "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
quotes [[Char]]
paths
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" from the '"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
field
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"' section of the .cabal file "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"to the section '"
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
targetField
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"'."
where
quotes :: [[Char]] -> [Char]
quotes [[Char]
p] = [Char]
"file " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [Char]
quote [Char]
p
quotes [[Char]]
ps = [Char]
"files " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
commaSep (([Char] -> [Char]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map [Char] -> [Char]
quote [[Char]]
ps)
targetField :: [Char]
targetField =
if Bool
extraDocFileSupport
then [Char]
"extra-doc-files"
else [Char]
"extra-source-files"
listSep :: [String] -> String
listSep :: [[Char]] -> [Char]
listSep [[Char]]
names =
let separator :: [Char]
separator = [Char]
"\n - "
in [Char]
separator [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char] -> [[Char]] -> [Char]
forall a. [a] -> [[a]] -> [a]
List.intercalate [Char]
separator [[Char]]
names [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"\n"
commaSep :: [String] -> String
commaSep :: [[Char]] -> [Char]
commaSep = [Char] -> [[Char]] -> [Char]
forall a. [a] -> [[a]] -> [a]
List.intercalate [Char]
", "
quote :: String -> String
quote :: [Char] -> [Char]
quote [Char]
s = [Char]
"'" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
s [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"'"
addConditionalExp :: String -> String
addConditionalExp :: [Char] -> [Char]
addConditionalExp [Char]
expl =
[Char]
expl
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" Alternatively, if you want to use this, make it conditional based "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"on a Cabal configuration flag (with 'manual: True' and 'default: "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"False') and enable that flag during development."