module HaskellCI.ParsecError (
renderParseError,
) where
import Prelude ()
import Prelude.Compat
import Distribution.Parsec (PError (..), PWarning (..), Position (..), showPos, zeroPos)
import Distribution.Simple.Utils (fromUTF8BS)
import System.FilePath (normalise)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BS8
renderParseError
:: FilePath
-> BS.ByteString
-> [PError]
-> [PWarning]
-> String
renderParseError filepath contents errors warnings
| null errors && null warnings = ""
| null errors = unlines $
("Warnings encountered when parsing file " <> filepath <> ":")
: renderedWarnings
| otherwise = unlines $
[ "Errors encountered when parsing file " <> filepath <> ":"
]
++ renderedErrors
++ renderedWarnings
where
filepath' = normalise filepath
rows :: [(String, Int, Bool)]
rows = zipWith f (BS8.lines contents) [1..] where
f bs i = let s = fromUTF8BS bs in (s, i, isEmptyOrComment s)
rowsZipper = listToZipper rows
isEmptyOrComment :: String -> Bool
isEmptyOrComment s = case dropWhile (== ' ') s of
"" -> True
('-':'-':_) -> True
_ -> False
renderedErrors = concatMap renderError errors
renderedWarnings = concatMap renderWarning warnings
renderError :: PError -> [String]
renderError (PError pos@(Position row col) msg)
| pos == zeroPos = msgs
| otherwise = msgs ++ formatInput row col
where
msgs = [ "", filepath' ++ ":" ++ showPos pos ++ ": error:", trimLF msg, "" ]
renderWarning :: PWarning -> [String]
renderWarning (PWarning _ pos@(Position row col) msg)
| pos == zeroPos = msgs
| otherwise = msgs ++ formatInput row col
where
msgs = [ "", filepath' ++ ":" ++ showPos pos ++ ": warning:", trimLF msg, "" ]
trimLF :: String -> String
trimLF = dropWhile (== '\n') . reverse . dropWhile (== '\n') . reverse
formatInput :: Int -> Int -> [String]
formatInput row col = case advance (row - 1) rowsZipper of
Zipper xs ys -> before ++ after where
before = case span (\(_, _, b) -> b) xs of
(_, []) -> []
(zs, z : _) -> map formatInputLine $ z : reverse zs
after = case ys of
[] -> []
(z : _zs) ->
[ formatInputLine z
, " | " ++ replicate (col - 1) ' ' ++ "^"
]
formatInputLine :: (String, Int, Bool) -> String
formatInputLine (str, row, _) = leftPadShow row ++ " | " ++ str
leftPadShow :: Int -> String
leftPadShow n = let s = show n in replicate (5 - length s) ' ' ++ s
data Zipper a = Zipper [a] [a]
listToZipper :: [a] -> Zipper a
listToZipper = Zipper []
advance :: Int -> Zipper a -> Zipper a
advance n z@(Zipper xs ys)
| n <= 0 = z
| otherwise = case ys of
[] -> z
(y:ys') -> advance (n - 1) $ Zipper (y:xs) ys'