{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}

-- |
-- Module      :  Distribution.PackageDescription.Check.Warning
-- Copyright   :  Francesco Ariis 2022
-- License     :  BSD3
--
-- Maintainer  :  cabal-devel@haskell.org
-- Portability :  portable
--
-- Warning types, messages, severity and associated functions.
module Distribution.PackageDescription.Check.Warning
  ( -- * Types and constructors
    PackageCheck (..)
  , CheckExplanation (..)
  , CheckExplanationID
  , CheckExplanationIDString
  , CEType (..)
  , WarnLang (..)

    -- * Operations
  , ppPackageCheck
  , ppCheckExplanationId
  , isHackageDistError
  , extractCheckExplantion
  , 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
  ( LicenseFile
  , PackageDir
  , SymbolicPath
  , getSymbolicPath
  )
import Language.Haskell.Extension (Extension)

import qualified Data.Either as Either
import qualified Data.List as List
import qualified Data.Set as Set

-- ------------------------------------------------------------
-- Check types and explanations
-- ------------------------------------------------------------

-- | Results of some kind of failed package check.
--
-- There are a range of severities, from merely dubious to totally insane.
-- All of them come with a human readable explanation. In future we may augment
-- them with more machine readable explanations, for example to help an IDE
-- suggest automatic corrections.
data PackageCheck
  = -- | This package description is no good. There's no way it's going to
    -- build sensibly. This should give an error at configure time.
    PackageBuildImpossible {PackageCheck -> CheckExplanation
explanation :: CheckExplanation}
  | -- | A problem that is likely to affect building the package, or an
    -- issue that we'd like every package author to be aware of, even if
    -- the package is never distributed.
    PackageBuildWarning {explanation :: CheckExplanation}
  | -- | An issue that might not be a problem for the package author but
    -- might be annoying or detrimental when the package is distributed to
    -- users. We should encourage distributed packages to be free from these
    -- issues, but occasionally there are justifiable reasons so we cannot
    -- ban them entirely.
    PackageDistSuspicious {explanation :: CheckExplanation}
  | -- | Like PackageDistSuspicious but will only display warnings
    -- rather than causing abnormal exit when you run 'cabal check'.
    PackageDistSuspiciousWarn {explanation :: CheckExplanation}
  | -- | An issue that is OK in the author's environment but is almost
    -- certain to be a portability problem for other environments. We can
    -- quite legitimately refuse to publicly distribute packages with these
    -- problems.
    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)

-- | Pretty printing 'PackageCheck'.
ppPackageCheck :: PackageCheck -> String
ppPackageCheck :: PackageCheck -> String
ppPackageCheck PackageCheck
e =
  let ex :: CheckExplanation
ex = PackageCheck -> CheckExplanation
explanation PackageCheck
e
   in String
"["
        String -> String -> String
forall a. [a] -> [a] -> [a]
++ (CheckExplanationID -> String
ppCheckExplanationId (CheckExplanationID -> String)
-> (CheckExplanation -> CheckExplanationID)
-> CheckExplanation
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CheckExplanation -> CheckExplanationID
checkExplanationId) CheckExplanation
ex
        String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"] "
        String -> String -> String
forall a. [a] -> [a] -> [a]
++ CheckExplanation -> String
ppExplanation CheckExplanation
ex

-- | Broken 'Show' instance (not bijective with Read), alas external packages
-- depend on it.
instance Show PackageCheck where
  show :: PackageCheck -> String
show PackageCheck
notice = PackageCheck -> String
ppPackageCheck PackageCheck
notice

-- | Would Hackage refuse a package because of this error?
isHackageDistError :: PackageCheck -> Bool
isHackageDistError :: PackageCheck -> Bool
isHackageDistError = \case
  (PackageBuildImpossible{}) -> Bool
True
  (PackageBuildWarning{}) -> Bool
True
  (PackageDistInexcusable{}) -> Bool
True
  (PackageDistSuspicious{}) -> Bool
False
  (PackageDistSuspiciousWarn{}) -> Bool
False

-- | Filter Package Check by CheckExplanationID.
filterPackageChecksById
  :: [PackageCheck]
  -- ^ Original checks.
  -> [CheckExplanationID]
  -- ^ IDs to omit.
  -> [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
extractCheckExplantion
        (PackageCheck -> Bool) -> PackageCheck -> Bool
forall a b. (a -> b) -> a -> b
$ PackageCheck
c

-- | Filter Package Check by Check explanation /string/.
filterPackageChecksByIdString
  :: [PackageCheck]
  -- ^ Original checks.
  -> [CheckExplanationIDString]
  -- ^ IDs to omit, in @String@ format.
  -> ([PackageCheck], [CheckExplanationIDString])
-- Filtered checks plus unrecognised id strings.
filterPackageChecksByIdString :: [PackageCheck] -> [String] -> ([PackageCheck], [String])
filterPackageChecksByIdString [PackageCheck]
cs [String]
ss =
  let ([String]
es, [CheckExplanationID]
is) = [Either String CheckExplanationID]
-> ([String], [CheckExplanationID])
forall a b. [Either a b] -> ([a], [b])
Either.partitionEithers ([Either String CheckExplanationID]
 -> ([String], [CheckExplanationID]))
-> [Either String CheckExplanationID]
-> ([String], [CheckExplanationID])
forall a b. (a -> b) -> a -> b
$ (String -> Either String CheckExplanationID)
-> [String] -> [Either String CheckExplanationID]
forall a b. (a -> b) -> [a] -> [b]
map String -> Either String CheckExplanationID
readExplanationID [String]
ss
   in ([PackageCheck] -> [CheckExplanationID] -> [PackageCheck]
filterPackageChecksById [PackageCheck]
cs [CheckExplanationID]
is, [String]
es)

-- | Explanations of 'PackageCheck`'s errors/warnings.
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
  | MissingModule
  | MissingTag
  | SubdirRelPath
  | SubdirGoodRelPath String
  | OptFasm String
  | OptHpc String
  | OptProf String
  | OptO String
  | OptHide String
  | OptMake String
  | OptONot String
  | OptOOne String
  | OptOTwo String
  | OptSplitSections String
  | OptSplitObjs String
  | OptWls String
  | OptExts String
  | OptRts String
  | OptWithRts String
  | COptONumber String WarnLang
  | COptCPP String
  | OptAlternatives String String [(String, String)]
  | RelativeOutside String FilePath
  | AbsolutePath String FilePath
  | BadRelativePath String FilePath String
  | DistPoint (Maybe String) FilePath
  | GlobSyntaxError String String
  | RecursiveGlobInRoot String FilePath
  | InvalidOnWin [FilePath]
  | FilePathTooLong FilePath
  | FilePathNameTooLong FilePath
  | FilePathSplitTooLong FilePath
  | FilePathEmpty
  | CVTestSuite
  | CVDefaultLanguage
  | CVDefaultLanguageComponent
  | CVExtraDocFiles
  | CVMultiLib
  | CVReexported
  | CVMixins
  | CVExtraFrameworkDirs
  | CVDefaultExtensions
  | CVExtensionsDeprecated
  | CVSources
  | CVExtraDynamic [[String]]
  | CVVirtualModules
  | CVSourceRepository
  | CVExtensions CabalSpecVersion [Extension]
  | CVCustomSetup
  | CVExpliticDepsCustomSetup
  | CVAutogenPaths
  | CVAutogenPackageInfo
  | CVAutogenPackageInfoGuard
  | GlobNoMatch String String
  | GlobExactMatch String String FilePath
  | GlobNoDir String String FilePath
  | UnknownOS [String]
  | UnknownArch [String]
  | UnknownCompiler [String]
  | BaseNoUpperBounds
  | MissingUpperBounds CEType [String]
  | SuspiciousFlagName [String]
  | DeclaredUsedFlags (Set.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 (SymbolicPath PackageDir LicenseFile)
  | 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 -> String -> String
[CheckExplanation] -> String -> String
CheckExplanation -> String
(Int -> CheckExplanation -> String -> String)
-> (CheckExplanation -> String)
-> ([CheckExplanation] -> String -> String)
-> Show CheckExplanation
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> CheckExplanation -> String -> String
showsPrec :: Int -> CheckExplanation -> String -> String
$cshow :: CheckExplanation -> String
show :: CheckExplanation -> String
$cshowList :: [CheckExplanation] -> String -> String
showList :: [CheckExplanation] -> String -> String
Show)

-- TODO Some checks have a constructor in list form
--      (e.g. `SomeWarn [n]`), CheckM m () correctly catches warnings in
--      different stanzas in different checks (so it is not one soup).
--
--      Ideally [SomeWar [a], SomeWar [b]] would be translated into
--      SomeWar [a,b] in the few cases where it is appropriate for UX
--      and left separated otherwise.
--      To achieve this the Writer part of CheckM could be modified
--      to be a ad hoc monoid.

-- Convenience.
extractCheckExplantion :: PackageCheck -> CheckExplanation
extractCheckExplantion :: PackageCheck -> CheckExplanation
extractCheckExplantion (PackageBuildImpossible CheckExplanation
e) = CheckExplanation
e
extractCheckExplantion (PackageBuildWarning CheckExplanation
e) = CheckExplanation
e
extractCheckExplantion (PackageDistSuspicious CheckExplanation
e) = CheckExplanation
e
extractCheckExplantion (PackageDistSuspiciousWarn CheckExplanation
e) = CheckExplanation
e
extractCheckExplantion (PackageDistInexcusable CheckExplanation
e) = CheckExplanation
e

-- | Identifier for the speficic 'CheckExplanation'. This ensures `--ignore`
-- can output a warning on unrecognised values.
-- ☞ N.B.: should be kept in sync with 'CheckExplanation'.
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
  | CIMissingModule
  | CIMissingTag
  | CISubdirRelPath
  | CISubdirGoodRelPath
  | CIOptFasm
  | CIOptHpc
  | CIOptProf
  | CIOptO
  | CIOptHide
  | CIOptMake
  | CIOptONot
  | CIOptOOne
  | CIOptOTwo
  | CIOptSplitSections
  | CIOptSplitObjs
  | CIOptWls
  | CIOptExts
  | CIOptRts
  | CIOptWithRts
  | CICOptONumber
  | CICOptCPP
  | CIOptAlternatives
  | CIRelativeOutside
  | CIAbsolutePath
  | CIBadRelativePath
  | CIDistPoint
  | CIGlobSyntaxError
  | CIRecursiveGlobInRoot
  | CIInvalidOnWin
  | CIFilePathTooLong
  | CIFilePathNameTooLong
  | CIFilePathSplitTooLong
  | CIFilePathEmpty
  | CICVTestSuite
  | CICVDefaultLanguage
  | CICVDefaultLanguageComponent
  | CICVExtraDocFiles
  | CICVMultiLib
  | CICVReexported
  | CICVMixins
  | CICVExtraFrameworkDirs
  | CICVDefaultExtensions
  | CICVExtensionsDeprecated
  | CICVSources
  | CICVExtraDynamic
  | CICVVirtualModules
  | CICVSourceRepository
  | CICVExtensions
  | CICVCustomSetup
  | CICVExpliticDepsCustomSetup
  | CICVAutogenPaths
  | CICVAutogenPackageInfo
  | CICVAutogenPackageInfoGuard
  | CIGlobNoMatch
  | CIGlobExactMatch
  | CIGlobNoDir
  | CIUnknownOS
  | CIUnknownArch
  | CIUnknownCompiler
  | CIBaseNoUpperBounds
  | CIMissingUpperBounds
  | 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 -> String -> String
[CheckExplanationID] -> String -> String
CheckExplanationID -> String
(Int -> CheckExplanationID -> String -> String)
-> (CheckExplanationID -> String)
-> ([CheckExplanationID] -> String -> String)
-> Show CheckExplanationID
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> CheckExplanationID -> String -> String
showsPrec :: Int -> CheckExplanationID -> String -> String
$cshow :: CheckExplanationID -> String
show :: CheckExplanationID -> String
$cshowList :: [CheckExplanationID] -> String -> String
showList :: [CheckExplanationID] -> String -> String
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 (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 (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 (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 (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

-- A one-word identifier for each CheckExplanation
--
-- ☞ N.B: if you modify anything here, remeber to change the documentation
-- in @doc/cabal-commands.rst@!
ppCheckExplanationId :: CheckExplanationID -> CheckExplanationIDString
ppCheckExplanationId :: CheckExplanationID -> String
ppCheckExplanationId CheckExplanationID
CIParseWarning = String
"parser-warning"
ppCheckExplanationId CheckExplanationID
CINoNameField = String
"no-name-field"
ppCheckExplanationId CheckExplanationID
CINoVersionField = String
"no-version-field"
ppCheckExplanationId CheckExplanationID
CINoTarget = String
"no-target"
ppCheckExplanationId CheckExplanationID
CIUnnamedInternal = String
"unnamed-internal-library"
ppCheckExplanationId CheckExplanationID
CIDuplicateSections = String
"duplicate-sections"
ppCheckExplanationId CheckExplanationID
CIIllegalLibraryName = String
"illegal-library-name"
ppCheckExplanationId CheckExplanationID
CINoModulesExposed = String
"no-modules-exposed"
ppCheckExplanationId CheckExplanationID
CISignaturesCabal2 = String
"signatures"
ppCheckExplanationId CheckExplanationID
CIAutogenNotExposed = String
"autogen-not-exposed"
ppCheckExplanationId CheckExplanationID
CIAutogenIncludesNotIncluded = String
"autogen-not-included"
ppCheckExplanationId CheckExplanationID
CINoMainIs = String
"no-main-is"
ppCheckExplanationId CheckExplanationID
CINoHsLhsMain = String
"unknown-extension-main"
ppCheckExplanationId CheckExplanationID
CIMainCCabal1_18 = String
"c-like-main"
ppCheckExplanationId CheckExplanationID
CIAutogenNoOther = String
"autogen-other-modules"
ppCheckExplanationId CheckExplanationID
CIAutogenIncludesNotIncludedExe = String
"autogen-exe"
ppCheckExplanationId CheckExplanationID
CITestsuiteTypeNotKnown = String
"unknown-testsuite-type"
ppCheckExplanationId CheckExplanationID
CITestsuiteNotSupported = String
"unsupported-testsuite"
ppCheckExplanationId CheckExplanationID
CIBenchmarkTypeNotKnown = String
"unknown-bench"
ppCheckExplanationId CheckExplanationID
CIBenchmarkNotSupported = String
"unsupported-bench"
ppCheckExplanationId CheckExplanationID
CINoHsLhsMainBench = String
"bench-unknown-extension"
ppCheckExplanationId CheckExplanationID
CIInvalidNameWin = String
"invalid-name-win"
ppCheckExplanationId CheckExplanationID
CIZPrefix = String
"reserved-z-prefix"
ppCheckExplanationId CheckExplanationID
CINoBuildType = String
"no-build-type"
ppCheckExplanationId CheckExplanationID
CINoCustomSetup = String
"undeclared-custom-setup"
ppCheckExplanationId CheckExplanationID
CIUnknownCompilers = String
"unknown-compiler-tested"
ppCheckExplanationId CheckExplanationID
CIUnknownLanguages = String
"unknown-languages"
ppCheckExplanationId CheckExplanationID
CIUnknownExtensions = String
"unknown-extension"
ppCheckExplanationId CheckExplanationID
CILanguagesAsExtension = String
"languages-as-extensions"
ppCheckExplanationId CheckExplanationID
CIDeprecatedExtensions = String
"deprecated-extensions"
ppCheckExplanationId CheckExplanationID
CIMissingFieldCategory = String
"no-category"
ppCheckExplanationId CheckExplanationID
CIMissingFieldMaintainer = String
"no-maintainer"
ppCheckExplanationId CheckExplanationID
CIMissingFieldSynopsis = String
"no-synopsis"
ppCheckExplanationId CheckExplanationID
CIMissingFieldDescription = String
"no-description"
ppCheckExplanationId CheckExplanationID
CIMissingFieldSynOrDesc = String
"no-syn-desc"
ppCheckExplanationId CheckExplanationID
CISynopsisTooLong = String
"long-synopsis"
ppCheckExplanationId CheckExplanationID
CIShortDesc = String
"short-description"
ppCheckExplanationId CheckExplanationID
CIInvalidTestWith = String
"invalid-range-tested"
ppCheckExplanationId CheckExplanationID
CIImpossibleInternalDep = String
"impossible-dep"
ppCheckExplanationId CheckExplanationID
CIImpossibleInternalExe = String
"impossible-dep-exe"
ppCheckExplanationId CheckExplanationID
CIMissingInternalExe = String
"no-internal-exe"
ppCheckExplanationId CheckExplanationID
CINONELicense = String
"license-none"
ppCheckExplanationId CheckExplanationID
CINoLicense = String
"no-license"
ppCheckExplanationId CheckExplanationID
CIAllRightsReservedLicense = String
"all-rights-reserved"
ppCheckExplanationId CheckExplanationID
CILicenseMessParse = String
"license-parse"
ppCheckExplanationId CheckExplanationID
CIUnrecognisedLicense = String
"unknown-license"
ppCheckExplanationId CheckExplanationID
CIUncommonBSD4 = String
"bsd4-license"
ppCheckExplanationId CheckExplanationID
CIUnknownLicenseVersion = String
"unknown-license-version"
ppCheckExplanationId CheckExplanationID
CINoLicenseFile = String
"no-license-file"
ppCheckExplanationId CheckExplanationID
CIUnrecognisedSourceRepo = String
"unrecognised-repo-type"
ppCheckExplanationId CheckExplanationID
CIMissingType = String
"repo-no-type"
ppCheckExplanationId CheckExplanationID
CIMissingLocation = String
"repo-no-location"
ppCheckExplanationId CheckExplanationID
CIMissingModule = String
"repo-no-module"
ppCheckExplanationId CheckExplanationID
CIMissingTag = String
"repo-no-tag"
ppCheckExplanationId CheckExplanationID
CISubdirRelPath = String
"repo-relative-dir"
ppCheckExplanationId CheckExplanationID
CISubdirGoodRelPath = String
"repo-malformed-subdir"
ppCheckExplanationId CheckExplanationID
CIOptFasm = String
"option-fasm"
ppCheckExplanationId CheckExplanationID
CIOptHpc = String
"option-fhpc"
ppCheckExplanationId CheckExplanationID
CIOptProf = String
"option-prof"
ppCheckExplanationId CheckExplanationID
CIOptO = String
"option-o"
ppCheckExplanationId CheckExplanationID
CIOptHide = String
"option-hide-package"
ppCheckExplanationId CheckExplanationID
CIOptMake = String
"option-make"
ppCheckExplanationId CheckExplanationID
CIOptONot = String
"option-optimize"
ppCheckExplanationId CheckExplanationID
CIOptOOne = String
"option-o1"
ppCheckExplanationId CheckExplanationID
CIOptOTwo = String
"option-o2"
ppCheckExplanationId CheckExplanationID
CIOptSplitSections = String
"option-split-section"
ppCheckExplanationId CheckExplanationID
CIOptSplitObjs = String
"option-split-objs"
ppCheckExplanationId CheckExplanationID
CIOptWls = String
"option-optl-wl"
ppCheckExplanationId CheckExplanationID
CIOptExts = String
"use-extension"
ppCheckExplanationId CheckExplanationID
CIOptRts = String
"option-rtsopts"
ppCheckExplanationId CheckExplanationID
CIOptWithRts = String
"option-with-rtsopts"
ppCheckExplanationId CheckExplanationID
CICOptONumber = String
"option-opt-c"
ppCheckExplanationId CheckExplanationID
CICOptCPP = String
"cpp-options"
ppCheckExplanationId CheckExplanationID
CIOptAlternatives = String
"misplaced-c-opt"
ppCheckExplanationId CheckExplanationID
CIRelativeOutside = String
"relative-path-outside"
ppCheckExplanationId CheckExplanationID
CIAbsolutePath = String
"absolute-path"
ppCheckExplanationId CheckExplanationID
CIBadRelativePath = String
"malformed-relative-path"
ppCheckExplanationId CheckExplanationID
CIDistPoint = String
"unreliable-dist-path"
ppCheckExplanationId CheckExplanationID
CIGlobSyntaxError = String
"glob-syntax-error"
ppCheckExplanationId CheckExplanationID
CIRecursiveGlobInRoot = String
"recursive-glob"
ppCheckExplanationId CheckExplanationID
CIInvalidOnWin = String
"invalid-path-win"
ppCheckExplanationId CheckExplanationID
CIFilePathTooLong = String
"long-path"
ppCheckExplanationId CheckExplanationID
CIFilePathNameTooLong = String
"long-name"
ppCheckExplanationId CheckExplanationID
CIFilePathSplitTooLong = String
"name-not-portable"
ppCheckExplanationId CheckExplanationID
CIFilePathEmpty = String
"empty-path"
ppCheckExplanationId CheckExplanationID
CICVTestSuite = String
"test-cabal-ver"
ppCheckExplanationId CheckExplanationID
CICVDefaultLanguage = String
"default-language"
ppCheckExplanationId CheckExplanationID
CICVDefaultLanguageComponent = String
"no-default-language"
ppCheckExplanationId CheckExplanationID
CICVExtraDocFiles = String
"extra-doc-files"
ppCheckExplanationId CheckExplanationID
CICVMultiLib = String
"multilib"
ppCheckExplanationId CheckExplanationID
CICVReexported = String
"reexported-modules"
ppCheckExplanationId CheckExplanationID
CICVMixins = String
"mixins"
ppCheckExplanationId CheckExplanationID
CICVExtraFrameworkDirs = String
"extra-framework-dirs"
ppCheckExplanationId CheckExplanationID
CICVDefaultExtensions = String
"default-extensions"
ppCheckExplanationId CheckExplanationID
CICVExtensionsDeprecated = String
"extensions-field"
ppCheckExplanationId CheckExplanationID
CICVSources = String
"unsupported-sources"
ppCheckExplanationId CheckExplanationID
CICVExtraDynamic = String
"extra-dynamic"
ppCheckExplanationId CheckExplanationID
CICVVirtualModules = String
"virtual-modules"
ppCheckExplanationId CheckExplanationID
CICVSourceRepository = String
"source-repository"
ppCheckExplanationId CheckExplanationID
CICVExtensions = String
"incompatible-extension"
ppCheckExplanationId CheckExplanationID
CICVCustomSetup = String
"no-setup-depends"
ppCheckExplanationId CheckExplanationID
CICVExpliticDepsCustomSetup = String
"dependencies-setup"
ppCheckExplanationId CheckExplanationID
CICVAutogenPaths = String
"no-autogen-paths"
ppCheckExplanationId CheckExplanationID
CICVAutogenPackageInfo = String
"no-autogen-pinfo"
ppCheckExplanationId CheckExplanationID
CICVAutogenPackageInfoGuard = String
"autogen-guard"
ppCheckExplanationId CheckExplanationID
CIGlobNoMatch = String
"no-glob-match"
ppCheckExplanationId CheckExplanationID
CIGlobExactMatch = String
"glob-no-extension"
ppCheckExplanationId CheckExplanationID
CIGlobNoDir = String
"glob-missing-dir"
ppCheckExplanationId CheckExplanationID
CIUnknownOS = String
"unknown-os"
ppCheckExplanationId CheckExplanationID
CIUnknownArch = String
"unknown-arch"
ppCheckExplanationId CheckExplanationID
CIUnknownCompiler = String
"unknown-compiler"
ppCheckExplanationId CheckExplanationID
CIBaseNoUpperBounds = String
"missing-bounds-important"
ppCheckExplanationId CheckExplanationID
CIMissingUpperBounds = String
"missing-upper-bounds"
ppCheckExplanationId CheckExplanationID
CISuspiciousFlagName = String
"suspicious-flag"
ppCheckExplanationId CheckExplanationID
CIDeclaredUsedFlags = String
"unused-flag"
ppCheckExplanationId CheckExplanationID
CINonASCIICustomField = String
"non-ascii"
ppCheckExplanationId CheckExplanationID
CIRebindableClashPaths = String
"rebindable-clash-paths"
ppCheckExplanationId CheckExplanationID
CIRebindableClashPackageInfo = String
"rebindable-clash-info"
ppCheckExplanationId CheckExplanationID
CIWErrorUnneeded = String
"werror"
ppCheckExplanationId CheckExplanationID
CIJUnneeded = String
"unneeded-j"
ppCheckExplanationId CheckExplanationID
CIFDeferTypeErrorsUnneeded = String
"fdefer-type-errors"
ppCheckExplanationId CheckExplanationID
CIDynamicUnneeded = String
"debug-flag"
ppCheckExplanationId CheckExplanationID
CIProfilingUnneeded = String
"fprof-flag"
ppCheckExplanationId CheckExplanationID
CIUpperBoundSetup = String
"missing-bounds-setup"
ppCheckExplanationId CheckExplanationID
CIDuplicateModule = String
"duplicate-modules"
ppCheckExplanationId CheckExplanationID
CIPotentialDupModule = String
"maybe-duplicate-modules"
ppCheckExplanationId CheckExplanationID
CIBOMStart = String
"bom"
ppCheckExplanationId CheckExplanationID
CINotPackageName = String
"name-no-match"
ppCheckExplanationId CheckExplanationID
CINoDesc = String
"no-cabal-file"
ppCheckExplanationId CheckExplanationID
CIMultiDesc = String
"multiple-cabal-file"
ppCheckExplanationId CheckExplanationID
CIUnknownFile = String
"unknown-file"
ppCheckExplanationId CheckExplanationID
CIMissingSetupFile = String
"missing-setup"
ppCheckExplanationId CheckExplanationID
CIMissingConfigureScript = String
"missing-conf-script"
ppCheckExplanationId CheckExplanationID
CIUnknownDirectory = String
"unknown-directory"
ppCheckExplanationId CheckExplanationID
CIMissingSourceControl = String
"no-repository"
ppCheckExplanationId CheckExplanationID
CIMissingExpectedDocFiles = String
"no-docs"
ppCheckExplanationId CheckExplanationID
CIWrongFieldForExpectedDocFiles = String
"doc-place"

-- String: the unrecognised 'CheckExplanationIDString' itself.
readExplanationID
  :: CheckExplanationIDString
  -> Either String CheckExplanationID
readExplanationID :: String -> Either String CheckExplanationID
readExplanationID String
s = Either String CheckExplanationID
-> (CheckExplanationID -> Either String CheckExplanationID)
-> Maybe CheckExplanationID
-> Either String CheckExplanationID
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Either String CheckExplanationID
forall a b. a -> Either a b
Left String
s) CheckExplanationID -> Either String CheckExplanationID
forall a b. b -> Either a b
Right (String
-> [(String, CheckExplanationID)] -> Maybe CheckExplanationID
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
s [(String, CheckExplanationID)]
idsDict)
  where
    idsDict :: [(CheckExplanationIDString, CheckExplanationID)]
    idsDict :: [(String, CheckExplanationID)]
idsDict = (CheckExplanationID -> (String, CheckExplanationID))
-> [CheckExplanationID] -> [(String, CheckExplanationID)]
forall a b. (a -> b) -> [a] -> [b]
map (\CheckExplanationID
i -> (CheckExplanationID -> String
ppCheckExplanationId CheckExplanationID
i, CheckExplanationID
i)) [CheckExplanationID
forall a. Bounded a => a
minBound .. CheckExplanationID
forall a. Bounded a => a
maxBound]

-- | Which stanza does `CheckExplanation` refer to?
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 -> String -> String
[CEType] -> String -> String
CEType -> String
(Int -> CEType -> String -> String)
-> (CEType -> String)
-> ([CEType] -> String -> String)
-> Show CEType
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> CEType -> String -> String
showsPrec :: Int -> CEType -> String -> String
$cshow :: CEType -> String
show :: CEType -> String
$cshowList :: [CEType] -> String -> String
showList :: [CEType] -> String -> String
Show)

-- | Pretty printing `CEType`.
ppCET :: CEType -> String
ppCET :: CEType -> String
ppCET CEType
cet = case CEType
cet of
  CETLibrary LibraryName
ln -> LibraryName -> String
showLibraryName LibraryName
ln
  CETForeignLibrary UnqualComponentName
n -> String
"foreign library" String -> String -> String
forall a. [a] -> [a] -> [a]
++ UnqualComponentName -> String
qn UnqualComponentName
n
  CETExecutable UnqualComponentName
n -> String
"executable" String -> String -> String
forall a. [a] -> [a] -> [a]
++ UnqualComponentName -> String
qn UnqualComponentName
n
  CETTest UnqualComponentName
n -> String
"test suite" String -> String -> String
forall a. [a] -> [a] -> [a]
++ UnqualComponentName -> String
qn UnqualComponentName
n
  CETBenchmark UnqualComponentName
n -> String
"benchmark" String -> String -> String
forall a. [a] -> [a] -> [a]
++ UnqualComponentName -> String
qn UnqualComponentName
n
  CEType
CETSetup -> String
"custom-setup"
  where
    qn :: UnqualComponentName -> String
    qn :: UnqualComponentName -> String
qn UnqualComponentName
wn = (String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++) (String -> String)
-> (UnqualComponentName -> String) -> UnqualComponentName -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
quote (String -> String)
-> (UnqualComponentName -> String) -> UnqualComponentName -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnqualComponentName -> String
forall a. Pretty a => a -> String
prettyShow (UnqualComponentName -> String) -> UnqualComponentName -> String
forall a b. (a -> b) -> a -> b
$ UnqualComponentName
wn

-- | Which language are we referring to in our warning message?
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 -> String -> String
[WarnLang] -> String -> String
WarnLang -> String
(Int -> WarnLang -> String -> String)
-> (WarnLang -> String)
-> ([WarnLang] -> String -> String)
-> Show WarnLang
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> WarnLang -> String -> String
showsPrec :: Int -> WarnLang -> String -> String
$cshow :: WarnLang -> String
show :: WarnLang -> String
$cshowList :: [WarnLang] -> String -> String
showList :: [WarnLang] -> String -> String
Show)

-- | Pretty printing `WarnLang`.
ppWarnLang :: WarnLang -> String
ppWarnLang :: WarnLang -> String
ppWarnLang WarnLang
LangC = String
"C"
ppWarnLang WarnLang
LangCPlusPlus = String
"C++"

-- | Pretty printing `CheckExplanation`.
ppExplanation :: CheckExplanation -> String
ppExplanation :: CheckExplanation -> String
ppExplanation (ParseWarning String
fp PWarning
pp) = String -> PWarning -> String
showPWarning String
fp PWarning
pp
ppExplanation CheckExplanation
NoNameField = String
"No 'name' field."
ppExplanation CheckExplanation
NoVersionField = String
"No 'version' field."
ppExplanation CheckExplanation
NoTarget =
  String
"No executables, libraries, tests, or benchmarks found. Nothing to do."
ppExplanation CheckExplanation
UnnamedInternal =
  String
"Found one or more unnamed internal libraries. Only the non-internal"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" library can have the same name as the package."
ppExplanation (DuplicateSections [UnqualComponentName]
duplicateNames) =
  String
"Duplicate sections: "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep ((UnqualComponentName -> String)
-> [UnqualComponentName] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map UnqualComponentName -> String
unUnqualComponentName [UnqualComponentName]
duplicateNames)
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
". The name of every library, executable, test suite,"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" and benchmark section in the package must be unique."
ppExplanation (IllegalLibraryName PackageName
pname) =
  String
"Illegal internal library name "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ PackageName -> String
forall a. Pretty a => a -> String
prettyShow PackageName
pname
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
". Internal libraries cannot have the same name as the package."
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" Maybe you wanted a non-internal library?"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" If so, rewrite the section stanza"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" from 'library: '"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ PackageName -> String
forall a. Pretty a => a -> String
prettyShow PackageName
pname
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' to 'library'."
ppExplanation (NoModulesExposed LibraryName
lName) =
  LibraryName -> String
showLibraryName LibraryName
lName String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" does not expose any modules"
ppExplanation CheckExplanation
SignaturesCabal2 =
  String
"To use the 'signatures' field the package needs to specify "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"at least 'cabal-version: 2.0'."
ppExplanation CheckExplanation
AutogenNotExposed =
  String
"An 'autogen-module' is neither on 'exposed-modules' nor 'other-modules'."
ppExplanation CheckExplanation
AutogenIncludesNotIncluded =
  String
"An include in 'autogen-includes' is neither in 'includes' nor "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'install-includes'."
ppExplanation (NoMainIs UnqualComponentName
eName) =
  String
"No 'main-is' field found for executable " String -> String -> String
forall a. [a] -> [a] -> [a]
++ UnqualComponentName -> String
forall a. Pretty a => a -> String
prettyShow UnqualComponentName
eName
ppExplanation CheckExplanation
NoHsLhsMain =
  String
"The 'main-is' field must specify a '.hs' or '.lhs' file "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"(even if it is generated by a preprocessor), "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"or it may specify a C/C++/obj-C source file."
ppExplanation CheckExplanation
MainCCabal1_18 =
  String
"The package uses a C/C++/obj-C source file for the 'main-is' field. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"To use this feature you need to specify 'cabal-version: 1.18' or"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" higher."
ppExplanation (AutogenNoOther CEType
ct) =
  String
"On "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ CEType -> String
ppCET CEType
ct
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" an 'autogen-module'"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is not on 'other-modules'"
ppExplanation CheckExplanation
AutogenIncludesNotIncludedExe =
  String
"An include in 'autogen-includes' is not in 'includes'."
ppExplanation (TestsuiteTypeNotKnown TestType
tt) =
  String -> String
quote (TestType -> String
forall a. Pretty a => a -> String
prettyShow TestType
tt)
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is not a known type of test suite. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Either remove the 'type' field or use a known type. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"The known test suite types are: "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep ((TestType -> String) -> [TestType] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map TestType -> String
forall a. Pretty a => a -> String
prettyShow [TestType]
knownTestTypes)
ppExplanation (TestsuiteNotSupported TestType
tt) =
  String -> String
quote (TestType -> String
forall a. Pretty a => a -> String
prettyShow TestType
tt)
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is not a supported test suite version. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Either remove the 'type' field or use a known type. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"The known test suite types are: "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep ((TestType -> String) -> [TestType] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map TestType -> String
forall a. Pretty a => a -> String
prettyShow [TestType]
knownTestTypes)
ppExplanation (BenchmarkTypeNotKnown BenchmarkType
tt) =
  String -> String
quote (BenchmarkType -> String
forall a. Pretty a => a -> String
prettyShow BenchmarkType
tt)
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is not a known type of benchmark. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Either remove the 'type' field or use a known type. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"The known benchmark types are: "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep ((BenchmarkType -> String) -> [BenchmarkType] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map BenchmarkType -> String
forall a. Pretty a => a -> String
prettyShow [BenchmarkType]
knownBenchmarkTypes)
ppExplanation (BenchmarkNotSupported BenchmarkType
tt) =
  String -> String
quote (BenchmarkType -> String
forall a. Pretty a => a -> String
prettyShow BenchmarkType
tt)
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is not a supported benchmark version. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Either remove the 'type' field or use a known type. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"The known benchmark types are: "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep ((BenchmarkType -> String) -> [BenchmarkType] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map BenchmarkType -> String
forall a. Pretty a => a -> String
prettyShow [BenchmarkType]
knownBenchmarkTypes)
ppExplanation CheckExplanation
NoHsLhsMainBench =
  String
"The 'main-is' field must specify a '.hs' or '.lhs' file "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"(even if it is generated by a preprocessor)."
ppExplanation (InvalidNameWin PackageName
pkg) =
  String
"The package name '"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ PackageName -> String
forall a. Pretty a => a -> String
prettyShow PackageName
pkg
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' is "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"invalid on Windows. Many tools need to convert package names to "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"file names, so using this name would cause problems."
ppExplanation CheckExplanation
ZPrefix =
  String
"Package names with the prefix 'z-' are reserved by Cabal and "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"cannot be used."
ppExplanation CheckExplanation
NoBuildType =
  String
"No 'build-type' specified. If you do not need a custom Setup.hs or "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"./configure script then use 'build-type: Simple'."
ppExplanation CheckExplanation
NoCustomSetup =
  String
"Ignoring the 'custom-setup' section because the 'build-type' is "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"not 'Custom'. Use 'build-type: Custom' if you need to use a "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"custom Setup.hs script."
ppExplanation (UnknownCompilers [String]
unknownCompilers) =
  String
"Unknown compiler "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
quote [String]
unknownCompilers)
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" in 'tested-with' field."
ppExplanation (UnknownLanguages [String]
unknownLanguages) =
  String
"Unknown languages: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep [String]
unknownLanguages
ppExplanation (UnknownExtensions [String]
unknownExtensions) =
  String
"Unknown extensions: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep [String]
unknownExtensions
ppExplanation (LanguagesAsExtension [String]
languagesUsedAsExtensions) =
  String
"Languages listed as extensions: "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep [String]
languagesUsedAsExtensions
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
". Languages must be specified in either the 'default-language' "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" or the 'other-languages' field."
ppExplanation (DeprecatedExtensions [(Extension, Maybe Extension)]
ourDeprecatedExtensions) =
  String
"Deprecated extensions: "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep (((Extension, Maybe Extension) -> String)
-> [(Extension, Maybe Extension)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String -> String
quote (String -> String)
-> ((Extension, Maybe Extension) -> String)
-> (Extension, Maybe Extension)
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Extension -> String
forall a. Pretty a => a -> String
prettyShow (Extension -> String)
-> ((Extension, Maybe Extension) -> Extension)
-> (Extension, Maybe Extension)
-> String
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)
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
". "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
unwords
      [ String
"Instead of '"
        String -> String -> String
forall a. [a] -> [a] -> [a]
++ Extension -> String
forall a. Pretty a => a -> String
prettyShow Extension
ext
        String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' use '"
        String -> String -> String
forall a. [a] -> [a] -> [a]
++ Extension -> String
forall a. Pretty a => a -> String
prettyShow Extension
replacement
        String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'."
      | (Extension
ext, Just Extension
replacement) <- [(Extension, Maybe Extension)]
ourDeprecatedExtensions
      ]
ppExplanation CheckExplanation
MissingFieldCategory = String
"No 'category' field."
ppExplanation CheckExplanation
MissingFieldMaintainer = String
"No 'maintainer' field."
ppExplanation CheckExplanation
MissingFieldSynopsis = String
"No 'synopsis' field."
ppExplanation CheckExplanation
MissingFieldDescription = String
"No 'description' field."
ppExplanation CheckExplanation
MissingFieldSynOrDesc = String
"No 'synopsis' or 'description' field."
ppExplanation CheckExplanation
SynopsisTooLong =
  String
"The 'synopsis' field is rather long (max 80 chars is recommended)."
ppExplanation CheckExplanation
ShortDesc =
  String
"The 'description' field should be longer than the 'synopsis' field. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"It's useful to provide an informative 'description' to allow "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Haskell programmers who have never heard about your package to "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"understand the purpose of your package. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"The 'description' field content is typically shown by tooling "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"(e.g. 'cabal info', Haddock, Hackage) below the 'synopsis' which "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"serves as a headline. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Please refer to <https://cabal.readthedocs.io/en/stable/"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"cabal-package.html#package-properties> for more details."
ppExplanation (InvalidTestWith [Dependency]
testedWithImpossibleRanges) =
  String
"Invalid 'tested-with' version range: "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep ((Dependency -> String) -> [Dependency] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Dependency -> String
forall a. Pretty a => a -> String
prettyShow [Dependency]
testedWithImpossibleRanges)
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
". To indicate that you have tested a package with multiple "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"different versions of the same compiler use multiple entries, "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"for example 'tested-with: GHC==6.10.4, GHC==6.12.3' and not "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'tested-with: GHC==6.10.4 && ==6.12.3'."
ppExplanation (ImpossibleInternalDep [Dependency]
depInternalLibWithImpossibleVersion) =
  String
"The package has an impossible version range for a dependency on an "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"internal library: "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep ((Dependency -> String) -> [Dependency] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Dependency -> String
forall a. Pretty a => a -> String
prettyShow [Dependency]
depInternalLibWithImpossibleVersion)
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
". This version range does not include the current package, and must "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"be removed as the current package's library will always be used."
ppExplanation (ImpossibleInternalExe [ExeDependency]
depInternalExecWithImpossibleVersion) =
  String
"The package has an impossible version range for a dependency on an "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"internal executable: "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep ((ExeDependency -> String) -> [ExeDependency] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map ExeDependency -> String
forall a. Pretty a => a -> String
prettyShow [ExeDependency]
depInternalExecWithImpossibleVersion)
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
". This version range does not include the current package, and must "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"be removed as the current package's executable will always be used."
ppExplanation (MissingInternalExe [ExeDependency]
depInternalExeWithImpossibleVersion) =
  String
"The package depends on a missing internal executable: "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep ((ExeDependency -> String) -> [ExeDependency] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map ExeDependency -> String
forall a. Pretty a => a -> String
prettyShow [ExeDependency]
depInternalExeWithImpossibleVersion)
ppExplanation CheckExplanation
NONELicense = String
"The 'license' field is missing or is NONE."
ppExplanation CheckExplanation
NoLicense = String
"The 'license' field is missing."
ppExplanation CheckExplanation
AllRightsReservedLicense =
  String
"The 'license' is AllRightsReserved. Is that really what you want?"
ppExplanation (LicenseMessParse License
lic) =
  String
"Unfortunately the license "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
quote (License -> String
forall a. Pretty a => a -> String
prettyShow License
lic)
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" messes up the parser in earlier Cabal versions so you need to "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"specify 'cabal-version: >= 1.4'. Alternatively if you require "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"compatibility with earlier Cabal versions then use 'OtherLicense'."
ppExplanation (UnrecognisedLicense String
l) =
  String -> String
quote (String
"license: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
l)
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is not a recognised license. The "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"known licenses are: "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep ((License -> String) -> [License] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map License -> String
forall a. Pretty a => a -> String
prettyShow [License]
knownLicenses)
ppExplanation CheckExplanation
UncommonBSD4 =
  String
"Using 'license: BSD4' is almost always a misunderstanding. 'BSD4' "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"refers to the old 4-clause BSD license with the advertising "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"clause. 'BSD3' refers the new 3-clause BSD license."
ppExplanation (UnknownLicenseVersion License
lic [Version]
known) =
  String
"'license: "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ License -> String
forall a. Pretty a => a -> String
prettyShow License
lic
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' is not a known "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"version of that license. The known versions are "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep ((Version -> String) -> [Version] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Version -> String
forall a. Pretty a => a -> String
prettyShow [Version]
known)
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
". If this is not a mistake and you think it should be a known "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"version then please file a ticket."
ppExplanation CheckExplanation
NoLicenseFile = String
"A 'license-file' is not specified."
ppExplanation (UnrecognisedSourceRepo String
kind) =
  String -> String
quote String
kind
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is not a recognised kind of source-repository. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"The repo kind is usually 'head' or 'this'"
ppExplanation CheckExplanation
MissingType =
  String
"The source-repository 'type' is a required field."
ppExplanation CheckExplanation
MissingLocation =
  String
"The source-repository 'location' is a required field."
ppExplanation CheckExplanation
MissingModule =
  String
"For a CVS source-repository, the 'module' is a required field."
ppExplanation CheckExplanation
MissingTag =
  String
"For the 'this' kind of source-repository, the 'tag' is a required "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"field. It should specify the tag corresponding to this version "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"or release of the package."
ppExplanation CheckExplanation
SubdirRelPath =
  String
"The 'subdir' field of a source-repository must be a relative path."
ppExplanation (SubdirGoodRelPath String
err) =
  String
"The 'subdir' field of a source-repository is not a good relative path: "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
err
ppExplanation (OptFasm String
fieldName) =
  String
"'"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fieldName
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": -fasm' is unnecessary and will not work on CPU "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"architectures other than x86, x86-64, ppc or sparc."
ppExplanation (OptHpc String
fieldName) =
  String
"'"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fieldName
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": -fhpc' is not necessary. Use the configure flag "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" --enable-coverage instead."
ppExplanation (OptProf String
fieldName) =
  String
"'"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fieldName
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": -prof' is not necessary and will lead to problems "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"when used on a library. Use the configure flag "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"--enable-library-profiling and/or --enable-profiling."
ppExplanation (OptO String
fieldName) =
  String
"'"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fieldName
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": -o' is not needed. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"The output files are named automatically."
ppExplanation (OptHide String
fieldName) =
  String
"'"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fieldName
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": -hide-package' is never needed. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Cabal hides all packages."
ppExplanation (OptMake String
fieldName) =
  String
"'"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fieldName
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": --make' is never needed. Cabal uses this automatically."
ppExplanation (OptONot String
fieldName) =
  String
"'"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fieldName
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": -O0' is not needed. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Use the --disable-optimization configure flag."
ppExplanation (OptOOne String
fieldName) =
  String
"'"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fieldName
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": -O' is not needed. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Cabal automatically adds the '-O' flag. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Setting it yourself interferes with the --disable-optimization flag."
ppExplanation (OptOTwo String
fieldName) =
  String
"'"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fieldName
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": -O2' is rarely needed. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Check that it is giving a real benefit "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"and not just imposing longer compile times on your users."
ppExplanation (OptSplitSections String
fieldName) =
  String
"'"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fieldName
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": -split-sections' is not needed. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Use the --enable-split-sections configure flag."
ppExplanation (OptSplitObjs String
fieldName) =
  String
"'"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fieldName
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": -split-objs' is not needed. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Use the --enable-split-objs configure flag."
ppExplanation (OptWls String
fieldName) =
  String
"'"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fieldName
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": -optl-Wl,-s' is not needed and is not portable to"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" all operating systems. Cabal 1.4 and later automatically strip"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" executables. Cabal also has a flag --disable-executable-stripping"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" which is necessary when building packages for some Linux"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" distributions and using '-optl-Wl,-s' prevents that from working."
ppExplanation (OptExts String
fieldName) =
  String
"Instead of '"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fieldName
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": -fglasgow-exts' it is preferable to use "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"the 'extensions' field."
ppExplanation (OptRts String
fieldName) =
  String
"'"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fieldName
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": -rtsopts' has no effect for libraries. It should "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"only be used for executables."
ppExplanation (OptWithRts String
fieldName) =
  String
"'"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fieldName
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": -with-rtsopts' has no effect for libraries. It "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"should only be used for executables."
ppExplanation (COptONumber String
prefix WarnLang
label) =
  String
"'"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
prefix
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": -O[n]' is generally not needed. When building with "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" optimisations Cabal automatically adds '-O2' for "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ WarnLang -> String
ppWarnLang WarnLang
label
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" code. Setting it yourself interferes with the"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" --disable-optimization flag."
ppExplanation (COptCPP String
opt) =
  String
"'cpp-options: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
opt String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' is not a portable C-preprocessor flag."
ppExplanation (OptAlternatives String
badField String
goodField [(String, String)]
flags) =
  String
"Instead of "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
quote (String
badField String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
unwords [String]
badFlags)
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" use "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
quote (String
goodField String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
unwords [String]
goodFlags)
  where
    ([String]
badFlags, [String]
goodFlags) = [(String, String)] -> ([String], [String])
forall a b. [(a, b)] -> ([a], [b])
unzip [(String, String)]
flags
ppExplanation (RelativeOutside String
field String
path) =
  String -> String
quote (String
field String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
path)
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is a relative path outside of the source tree. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"This will not work when generating a tarball with 'sdist'."
ppExplanation (AbsolutePath String
field String
path) =
  String -> String
quote (String
field String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
path)
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" specifies an absolute path, but the "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
quote String
field
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" field must use relative paths."
ppExplanation (BadRelativePath String
field String
path String
err) =
  String -> String
quote (String
field String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
path)
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is not a good relative path: "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
err
ppExplanation (DistPoint Maybe String
mfield String
path) =
  String
incipit
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" points inside the 'dist' "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"directory. This is not reliable because the location of this "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"directory is configurable by the user (or package manager). In "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"addition, the layout of the 'dist' directory is subject to change "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"in future versions of Cabal."
  where
    -- mfiled Nothing -> the path is inside `ghc-options`
    incipit :: String
incipit =
      String -> (String -> String) -> Maybe String -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
        (String
"'ghc-options' path " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
quote String
path)
        (\String
field -> String -> String
quote (String
field String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
path))
        Maybe String
mfield
ppExplanation (GlobSyntaxError String
field String
expl) =
  String
"In the '" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
field String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' field: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
expl
ppExplanation (RecursiveGlobInRoot String
field String
glob) =
  String
"In the '"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
field
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"': glob '"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
glob
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' starts at project root directory, this might "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"include `.git/`, ``dist-newstyle/``, or other large directories!"
ppExplanation (InvalidOnWin [String]
paths) =
  String
"The "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
quotes [String]
paths
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" invalid on Windows, which "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"would cause portability problems for this package. Windows file "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"names cannot contain any of the characters \":*?<>|\" and there "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"a few reserved names including \"aux\", \"nul\", \"con\", "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\"prn\", \"com1-9\", \"lpt1-9\" and \"clock$\"."
  where
    quotes :: [String] -> String
quotes [String
failed] = String
"path " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
quote String
failed String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is"
    quotes [String]
failed =
      String
"paths "
        String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
quote [String]
failed)
        String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" are"
ppExplanation (FilePathTooLong String
path) =
  String
"The following file name is too long to store in a portable POSIX "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"format tar archive. The maximum length is 255 ASCII characters.\n"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"The file in question is:\n  "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
path
ppExplanation (FilePathNameTooLong String
path) =
  String
"The following file name is too long to store in a portable POSIX "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"format tar archive. The maximum length for the name part (including "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"extension) is 100 ASCII characters. The maximum length for any "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"individual directory component is 155.\n"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"The file in question is:\n  "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
path
ppExplanation (FilePathSplitTooLong String
path) =
  String
"The following file name is too long to store in a portable POSIX "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"format tar archive. While the total length is less than 255 ASCII "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"characters, there are unfortunately further restrictions. It has to "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"be possible to split the file path on a directory separator into "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"two parts such that the first part fits in 155 characters or less "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"and the second part fits in 100 characters or less. Basically you "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"have to make the file name or directory names shorter, or you could "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"split a long directory name into nested subdirectories with shorter "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"names.\nThe file in question is:\n  "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
path
ppExplanation CheckExplanation
FilePathEmpty =
  String
"Encountered a file with an empty name, something is very wrong! "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Files with an empty name cannot be stored in a tar archive or in "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"standard file systems."
ppExplanation CheckExplanation
CVTestSuite =
  String
"The 'test-suite' section is new in Cabal 1.10. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Unfortunately it messes up the parser in older Cabal versions "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"so you must specify at least 'cabal-version: >= 1.8', but note "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"that only Cabal 1.10 and later can actually run such test suites."
ppExplanation CheckExplanation
CVDefaultLanguage =
  String
"To use the 'default-language' field the package needs to specify "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"at least 'cabal-version: >= 1.10'."
ppExplanation CheckExplanation
CVDefaultLanguageComponent =
  String
"Packages using 'cabal-version: >= 1.10' and before 'cabal-version: 3.4' "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"must specify the 'default-language' field for each component (e.g. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Haskell98 or Haskell2010). If a component uses different languages "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"in different modules then list the other ones in the "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'other-languages' field."
ppExplanation CheckExplanation
CVExtraDocFiles =
  String
"To use the 'extra-doc-files' field the package needs to specify "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'cabal-version: 1.18' or higher."
ppExplanation CheckExplanation
CVMultiLib =
  String
"To use multiple 'library' sections or a named library section "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"the package needs to specify at least 'cabal-version: 2.0'."
ppExplanation CheckExplanation
CVReexported =
  String
"To use the 'reexported-module' field the package needs to specify "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'cabal-version: 1.22' or higher."
ppExplanation CheckExplanation
CVMixins =
  String
"To use the 'mixins' field the package needs to specify "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"at least 'cabal-version: 2.0'."
ppExplanation CheckExplanation
CVExtraFrameworkDirs =
  String
"To use the 'extra-framework-dirs' field the package needs to specify"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" 'cabal-version: 1.24' or higher."
ppExplanation CheckExplanation
CVDefaultExtensions =
  String
"To use the 'default-extensions' field the package needs to specify "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"at least 'cabal-version: >= 1.10'."
ppExplanation CheckExplanation
CVExtensionsDeprecated =
  String
"For packages using 'cabal-version: >= 1.10' the 'extensions' "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"field is deprecated. The new 'default-extensions' field lists "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"extensions that are used in all modules in the component, while "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"the 'other-extensions' field lists extensions that are used in "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"some modules, e.g. via the {-# LANGUAGE #-} pragma."
ppExplanation CheckExplanation
CVSources =
  String
"The use of 'asm-sources', 'cmm-sources', 'extra-bundled-libraries' "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" and 'extra-library-flavours' requires the package "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" to specify at least 'cabal-version: 3.0'."
ppExplanation (CVExtraDynamic [[String]]
flavs) =
  String
"The use of 'extra-dynamic-library-flavours' requires the package "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" to specify at least 'cabal-version: 3.0'. The flavours are: "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep ([[String]] -> [String]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[String]]
flavs)
ppExplanation CheckExplanation
CVVirtualModules =
  String
"The use of 'virtual-modules' requires the package "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" to specify at least 'cabal-version: 2.2'."
ppExplanation CheckExplanation
CVSourceRepository =
  String
"The 'source-repository' section is new in Cabal 1.6. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Unfortunately it messes up the parser in earlier Cabal versions "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"so you need to specify 'cabal-version: >= 1.6'."
ppExplanation (CVExtensions CabalSpecVersion
version [Extension]
extCab12) =
  String
"Unfortunately the language extensions "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep ((Extension -> String) -> [Extension] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String -> String
quote (String -> String) -> (Extension -> String) -> Extension -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Extension -> String
forall a. Pretty a => a -> String
prettyShow) [Extension]
extCab12)
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" break the parser in earlier Cabal versions so you need to "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"specify 'cabal-version: >= "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ CabalSpecVersion -> String
showCabalSpecVersion CabalSpecVersion
version
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'. Alternatively if you require compatibility with earlier "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Cabal versions then you may be able to use an equivalent "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"compiler-specific flag."
ppExplanation CheckExplanation
CVCustomSetup =
  String
"Packages using 'cabal-version: 1.24' or higher with 'build-type: Custom' "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"must use a 'custom-setup' section with a 'setup-depends' field "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"that specifies the dependencies of the Setup.hs script itself. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"The 'setup-depends' field uses the same syntax as 'build-depends', "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"so a simple example would be 'setup-depends: base, Cabal'."
ppExplanation CheckExplanation
CVExpliticDepsCustomSetup =
  String
"From version 1.24 cabal supports specifying explicit dependencies "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"for Custom setup scripts. Consider using 'cabal-version: 1.24' or "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"higher and adding a 'custom-setup' section with a 'setup-depends' "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"field that specifies the dependencies of the Setup.hs script "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"itself. The 'setup-depends' field uses the same syntax as "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'build-depends', so a simple example would be 'setup-depends: base, "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Cabal'."
ppExplanation CheckExplanation
CVAutogenPaths =
  String
"Packages using 'cabal-version: 2.0' and the autogenerated "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"module Paths_* must include it also on the 'autogen-modules' field "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"besides 'exposed-modules' and 'other-modules'. This specifies that "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"the module does not come with the package and is generated on "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"setup. Modules built with a custom Setup.hs script also go here "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"to ensure that commands like sdist don't fail."
ppExplanation CheckExplanation
CVAutogenPackageInfo =
  String
"Packages using 'cabal-version: 2.0' and the autogenerated "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"module PackageInfo_* must include it in 'autogen-modules' as well as"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" 'exposed-modules' and 'other-modules'. This specifies that "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"the module does not come with the package and is generated on "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"setup. Modules built with a custom Setup.hs script also go here "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"to ensure that commands like sdist don't fail."
ppExplanation CheckExplanation
CVAutogenPackageInfoGuard =
  String
"To use the autogenerated module PackageInfo_* you need to specify "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"`cabal-version: 3.12` or higher."
ppExplanation (GlobNoMatch String
field String
glob) =
  String
"In '"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
field
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"': the pattern '"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
glob
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' does not"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" match any files."
ppExplanation (GlobExactMatch String
field String
glob String
file) =
  String
"In '"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
field
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"': the pattern '"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
glob
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' does not"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" match the file '"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
file
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' because the extensions do not"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" exactly match (e.g., foo.en.html does not exactly match *.html)."
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" To enable looser suffix-only matching, set 'cabal-version: 2.4' or"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" higher."
ppExplanation (GlobNoDir String
field String
glob String
dir) =
  String
"In '"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
field
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"': the pattern '"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
glob
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' attempts to"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" match files in the directory '"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
dir
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"', but there is no"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" directory by that name."
ppExplanation (UnknownOS [String]
unknownOSs) =
  String
"Unknown operating system name " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
quote [String]
unknownOSs)
ppExplanation (UnknownArch [String]
unknownArches) =
  String
"Unknown architecture name " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
quote [String]
unknownArches)
ppExplanation (UnknownCompiler [String]
unknownImpls) =
  String
"Unknown compiler name " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
quote [String]
unknownImpls)
ppExplanation CheckExplanation
BaseNoUpperBounds =
  String
"The dependency 'build-depends: base' does not specify an upper "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"bound on the version number. Each major release of the 'base' "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"package changes the API in various ways and most packages will "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"need some changes to compile with it. The recommended practice "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"is to specify an upper bound on the version of the 'base' "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"package. This ensures your package will continue to build when a "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"new major version of the 'base' package is released. If you are "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"not sure what upper bound to use then use the next  major "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"version. For example if you have tested your package with 'base' "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"version 4.5 and 4.6 then use 'build-depends: base >= 4.5 && < 4.7'."
ppExplanation (MissingUpperBounds CEType
ct [String]
names) =
  let separator :: String
separator = String
"\n  - "
   in String
"On "
        String -> String -> String
forall a. [a] -> [a] -> [a]
++ CEType -> String
ppCET CEType
ct
        String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
", "
        String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"these packages miss upper bounds:"
        String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
separator
        String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
List.intercalate String
separator [String]
names
        String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n"
        String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Please add them. There is more information at https://pvp.haskell.org/"
ppExplanation (SuspiciousFlagName [String]
invalidFlagNames) =
  String
"Suspicious flag names: "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
unwords [String]
invalidFlagNames
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
". "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"To avoid ambiguity in command line interfaces, a flag shouldn't "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"start with a dash. Also for better compatibility, flag names "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"shouldn't contain non-ascii characters."
ppExplanation (DeclaredUsedFlags Set FlagName
declared Set FlagName
used) =
  String
"Declared and used flag sets differ: "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ Set FlagName -> String
s Set FlagName
declared
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" /= "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ Set FlagName -> String
s Set FlagName
used
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
". "
  where
    s :: Set.Set FlagName -> String
    s :: Set FlagName -> String
s = [String] -> String
commaSep ([String] -> String)
-> (Set FlagName -> [String]) -> Set FlagName -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FlagName -> String) -> [FlagName] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map FlagName -> String
unFlagName ([FlagName] -> [String])
-> (Set FlagName -> [FlagName]) -> Set FlagName -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set FlagName -> [FlagName]
forall a. Set a -> [a]
Set.toList
ppExplanation (NonASCIICustomField [String]
nonAsciiXFields) =
  String
"Non ascii custom fields: "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
unwords [String]
nonAsciiXFields
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
". "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"For better compatibility, custom field names "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"shouldn't contain non-ascii characters."
ppExplanation CheckExplanation
RebindableClashPaths =
  String
"Packages using RebindableSyntax with OverloadedStrings or"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" OverloadedLists in default-extensions, in conjunction with the"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" autogenerated module Paths_*, are known to cause compile failures"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" with Cabal < 2.2. To use these default-extensions with a Paths_*"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" autogen module, specify at least 'cabal-version: 2.2'."
ppExplanation CheckExplanation
RebindableClashPackageInfo =
  String
"Packages using RebindableSyntax with OverloadedStrings or"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" OverloadedLists in default-extensions, in conjunction with the"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" autogenerated module PackageInfo_*, are known to cause compile failures"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" with Cabal < 2.2. To use these default-extensions with a PackageInfo_*"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" autogen module, specify at least 'cabal-version: 2.2'."
ppExplanation (WErrorUnneeded String
fieldName) =
  String -> String
addConditionalExp (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$
    String
"'"
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fieldName
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": -Werror' makes the package easy to "
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"break with future GHC versions because new GHC versions often "
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"add new warnings."
ppExplanation (JUnneeded String
fieldName) =
  String -> String
addConditionalExp (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$
    String
"'"
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fieldName
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": -j[N]' can make sense for a particular user's setup,"
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" but it is not appropriate for a distributed package."
ppExplanation (FDeferTypeErrorsUnneeded String
fieldName) =
  String -> String
addConditionalExp (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$
    String
"'"
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fieldName
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": -fdefer-type-errors' is fine during development "
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"but is not appropriate for a distributed package."
ppExplanation (DynamicUnneeded String
fieldName) =
  String -> String
addConditionalExp (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$
    String
"'"
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fieldName
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": -d*' debug flags are not appropriate "
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"for a distributed package."
ppExplanation (ProfilingUnneeded String
fieldName) =
  String -> String
addConditionalExp (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$
    String
"'"
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fieldName
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": -fprof*' profiling flags are typically not "
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"appropriate for a distributed library package. These flags are "
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"useful to profile this package, but when profiling other packages "
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"that use this one these flags clutter the profile output with "
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"excessive detail. If you think other packages really want to see "
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"cost centres from this package then use '-fprof-auto-exported' "
      String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"which puts cost centres only on exported functions."
ppExplanation (UpperBoundSetup String
nm) =
  String
"The dependency 'setup-depends: '"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
nm
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' does not specify an "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"upper bound on the version number. Each major release of the "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
nm
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' package changes the API in various ways and most "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"packages will need some changes to compile with it. If you are "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"not sure what upper bound to use then use the next major "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"version."
ppExplanation (DuplicateModule String
s [ModuleName]
dupLibsLax) =
  String
"Duplicate modules in "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep ((ModuleName -> String) -> [ModuleName] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map ModuleName -> String
forall a. Pretty a => a -> String
prettyShow [ModuleName]
dupLibsLax)
ppExplanation (PotentialDupModule String
s [ModuleName]
dupLibsStrict) =
  String
"Potential duplicate modules (subject to conditionals) in "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep ((ModuleName -> String) -> [ModuleName] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map ModuleName -> String
forall a. Pretty a => a -> String
prettyShow [ModuleName]
dupLibsStrict)
ppExplanation (BOMStart String
pdfile) =
  String
pdfile
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" starts with an Unicode byte order mark (BOM)."
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" This may cause problems with older cabal versions."
ppExplanation (NotPackageName String
pdfile String
expectedCabalname) =
  String
"The filename "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
quote String
pdfile
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" does not match package name "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"(expected: "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
quote String
expectedCabalname
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")"
ppExplanation CheckExplanation
NoDesc =
  String
"No cabal file found.\n"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Please create a package description file <pkgname>.cabal"
ppExplanation (MultiDesc [String]
multiple) =
  String
"Multiple cabal files found while checking.\n"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Please use only one of: "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep [String]
multiple
ppExplanation (UnknownFile String
fieldname SymbolicPath PackageDir LicenseFile
file) =
  String
"The '"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fieldname
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' field refers to the file "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
quote (SymbolicPath PackageDir LicenseFile -> String
forall from to. SymbolicPath from to -> String
getSymbolicPath SymbolicPath PackageDir LicenseFile
file)
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" which does not exist."
ppExplanation CheckExplanation
MissingSetupFile =
  String
"The package is missing a Setup.hs or Setup.lhs script."
ppExplanation CheckExplanation
MissingConfigureScript =
  String
"The 'build-type' is 'Configure' but there is no 'configure' script. "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"You probably need to run 'autoreconf -i' to generate it."
ppExplanation (UnknownDirectory String
kind String
dir) =
  String -> String
quote (String
kind String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
dir)
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" specifies a directory which does not exist."
ppExplanation CheckExplanation
MissingSourceControl =
  String
"When distributing packages, it is encouraged to specify source "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"control information in the .cabal file using one or more "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'source-repository' sections. See the Cabal user guide for "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"details."
ppExplanation (MissingExpectedDocFiles Bool
extraDocFileSupport [String]
paths) =
  String
"Please consider including the "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
quotes [String]
paths
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" in the '"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
targetField
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' section of the .cabal file "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"if it contains useful information for users of the package."
  where
    quotes :: [String] -> String
quotes [String
p] = String
"file " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
quote String
p
    quotes [String]
ps = String
"files " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
quote [String]
ps)
    targetField :: String
targetField =
      if Bool
extraDocFileSupport
        then String
"extra-doc-files"
        else String
"extra-source-files"
ppExplanation (WrongFieldForExpectedDocFiles Bool
extraDocFileSupport String
field [String]
paths) =
  String
"Please consider moving the "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
quotes [String]
paths
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" from the '"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
field
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' section of the .cabal file "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"to the section '"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
targetField
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'."
  where
    quotes :: [String] -> String
quotes [String
p] = String
"file " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
quote String
p
    quotes [String]
ps = String
"files " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
commaSep ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
quote [String]
ps)
    targetField :: String
targetField =
      if Bool
extraDocFileSupport
        then String
"extra-doc-files"
        else String
"extra-source-files"

-- * Formatting utilities

commaSep :: [String] -> String
commaSep :: [String] -> String
commaSep = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
List.intercalate String
", "

quote :: String -> String
quote :: String -> String
quote String
s = String
"'" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'"

addConditionalExp :: String -> String
addConditionalExp :: String -> String
addConditionalExp String
expl =
  String
expl
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" Alternatively, if you want to use this, make it conditional based "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"on a Cabal configuration flag (with 'manual: True' and 'default: "
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"False') and enable that flag during development."