{-# LANGUAGE DeriveGeneric #-}
module Distribution.Parsec.Warning (
    PWarning (..),
    PWarnType (..),
    showPWarning,
    ) where

import Distribution.Compat.Prelude
import Distribution.Parsec.Position
import Prelude ()
import System.FilePath              (normalise)

-- | Type of parser warning. We do classify warnings.
--
-- Different application may decide not to show some, or have fatal behaviour on others
data PWarnType
    = PWTOther                 -- ^ Unclassified warning
    | PWTUTF                   -- ^ Invalid UTF encoding
    | PWTBoolCase              -- ^ @true@ or @false@, not @True@ or @False@
    | PWTVersionTag            -- ^ there are version with tags
    | PWTNewSyntax             -- ^ New syntax used, but no @cabal-version: >= 1.2@ specified
    | PWTOldSyntax             -- ^ Old syntax used, and @cabal-version >= 1.2@ specified
    | PWTDeprecatedField
    | PWTInvalidSubsection
    | PWTUnknownField
    | PWTUnknownSection
    | PWTTrailingFields
    | PWTExtraMainIs           -- ^ extra main-is field
    | PWTExtraTestModule       -- ^ extra test-module field
    | PWTExtraBenchmarkModule  -- ^ extra benchmark-module field
    | PWTLexNBSP
    | PWTLexBOM
    | PWTLexTab
    | PWTQuirkyCabalFile       -- ^ legacy cabal file that we know how to patch
    | PWTDoubleDash            -- ^ Double dash token, most likely it's a mistake - it's not a comment
    | PWTMultipleSingularField -- ^ e.g. name or version should be specified only once.
    | PWTBuildTypeDefault      -- ^ Workaround for derive-package having build-type: Default. See <https://github.com/haskell/cabal/issues/5020>.
    deriving (PWarnType -> PWarnType -> Bool
(PWarnType -> PWarnType -> Bool)
-> (PWarnType -> PWarnType -> Bool) -> Eq PWarnType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PWarnType -> PWarnType -> Bool
$c/= :: PWarnType -> PWarnType -> Bool
== :: PWarnType -> PWarnType -> Bool
$c== :: PWarnType -> PWarnType -> Bool
Eq, Eq PWarnType
Eq PWarnType
-> (PWarnType -> PWarnType -> Ordering)
-> (PWarnType -> PWarnType -> Bool)
-> (PWarnType -> PWarnType -> Bool)
-> (PWarnType -> PWarnType -> Bool)
-> (PWarnType -> PWarnType -> Bool)
-> (PWarnType -> PWarnType -> PWarnType)
-> (PWarnType -> PWarnType -> PWarnType)
-> Ord PWarnType
PWarnType -> PWarnType -> Bool
PWarnType -> PWarnType -> Ordering
PWarnType -> PWarnType -> PWarnType
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
min :: PWarnType -> PWarnType -> PWarnType
$cmin :: PWarnType -> PWarnType -> PWarnType
max :: PWarnType -> PWarnType -> PWarnType
$cmax :: PWarnType -> PWarnType -> PWarnType
>= :: PWarnType -> PWarnType -> Bool
$c>= :: PWarnType -> PWarnType -> Bool
> :: PWarnType -> PWarnType -> Bool
$c> :: PWarnType -> PWarnType -> Bool
<= :: PWarnType -> PWarnType -> Bool
$c<= :: PWarnType -> PWarnType -> Bool
< :: PWarnType -> PWarnType -> Bool
$c< :: PWarnType -> PWarnType -> Bool
compare :: PWarnType -> PWarnType -> Ordering
$ccompare :: PWarnType -> PWarnType -> Ordering
$cp1Ord :: Eq PWarnType
Ord, Int -> PWarnType -> ShowS
[PWarnType] -> ShowS
PWarnType -> String
(Int -> PWarnType -> ShowS)
-> (PWarnType -> String)
-> ([PWarnType] -> ShowS)
-> Show PWarnType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PWarnType] -> ShowS
$cshowList :: [PWarnType] -> ShowS
show :: PWarnType -> String
$cshow :: PWarnType -> String
showsPrec :: Int -> PWarnType -> ShowS
$cshowsPrec :: Int -> PWarnType -> ShowS
Show, Int -> PWarnType
PWarnType -> Int
PWarnType -> [PWarnType]
PWarnType -> PWarnType
PWarnType -> PWarnType -> [PWarnType]
PWarnType -> PWarnType -> PWarnType -> [PWarnType]
(PWarnType -> PWarnType)
-> (PWarnType -> PWarnType)
-> (Int -> PWarnType)
-> (PWarnType -> Int)
-> (PWarnType -> [PWarnType])
-> (PWarnType -> PWarnType -> [PWarnType])
-> (PWarnType -> PWarnType -> [PWarnType])
-> (PWarnType -> PWarnType -> PWarnType -> [PWarnType])
-> Enum PWarnType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: PWarnType -> PWarnType -> PWarnType -> [PWarnType]
$cenumFromThenTo :: PWarnType -> PWarnType -> PWarnType -> [PWarnType]
enumFromTo :: PWarnType -> PWarnType -> [PWarnType]
$cenumFromTo :: PWarnType -> PWarnType -> [PWarnType]
enumFromThen :: PWarnType -> PWarnType -> [PWarnType]
$cenumFromThen :: PWarnType -> PWarnType -> [PWarnType]
enumFrom :: PWarnType -> [PWarnType]
$cenumFrom :: PWarnType -> [PWarnType]
fromEnum :: PWarnType -> Int
$cfromEnum :: PWarnType -> Int
toEnum :: Int -> PWarnType
$ctoEnum :: Int -> PWarnType
pred :: PWarnType -> PWarnType
$cpred :: PWarnType -> PWarnType
succ :: PWarnType -> PWarnType
$csucc :: PWarnType -> PWarnType
Enum, PWarnType
PWarnType -> PWarnType -> Bounded PWarnType
forall a. a -> a -> Bounded a
maxBound :: PWarnType
$cmaxBound :: PWarnType
minBound :: PWarnType
$cminBound :: PWarnType
Bounded, (forall x. PWarnType -> Rep PWarnType x)
-> (forall x. Rep PWarnType x -> PWarnType) -> Generic PWarnType
forall x. Rep PWarnType x -> PWarnType
forall x. PWarnType -> Rep PWarnType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PWarnType x -> PWarnType
$cfrom :: forall x. PWarnType -> Rep PWarnType x
Generic)

instance Binary PWarnType
instance NFData PWarnType where rnf :: PWarnType -> ()
rnf = PWarnType -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf

-- | Parser warning.
data PWarning = PWarning !PWarnType !Position String
    deriving (Int -> PWarning -> ShowS
[PWarning] -> ShowS
PWarning -> String
(Int -> PWarning -> ShowS)
-> (PWarning -> String) -> ([PWarning] -> ShowS) -> Show PWarning
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PWarning] -> ShowS
$cshowList :: [PWarning] -> ShowS
show :: PWarning -> String
$cshow :: PWarning -> String
showsPrec :: Int -> PWarning -> ShowS
$cshowsPrec :: Int -> PWarning -> ShowS
Show, (forall x. PWarning -> Rep PWarning x)
-> (forall x. Rep PWarning x -> PWarning) -> Generic PWarning
forall x. Rep PWarning x -> PWarning
forall x. PWarning -> Rep PWarning x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PWarning x -> PWarning
$cfrom :: forall x. PWarning -> Rep PWarning x
Generic)

instance Binary PWarning
instance NFData PWarning where rnf :: PWarning -> ()
rnf = PWarning -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf

showPWarning :: FilePath -> PWarning -> String
showPWarning :: String -> PWarning -> String
showPWarning String
fpath (PWarning PWarnType
_ Position
pos String
msg) =
    ShowS
normalise String
fpath String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
":" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Position -> String
showPos Position
pos String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
": " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
msg