{-# LANGUAGE DeriveGeneric #-}
module Distribution.Parsec.Error (
    PError (..),
    showPError,
    ) where

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

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

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

showPError :: FilePath -> PError -> String
showPError :: String -> PError -> String
showPError String
fpath (PError 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