{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module Krank.Checkers.Ignore
( IgnoreCommand (..),
filterViolations,
)
where
import qualified Data.ByteString.Char8 as ByteString
import Data.ByteString.Char8 (ByteString)
import Data.HashMap.Strict as HashM
import qualified Data.List as DataL
import Krank.Types
import PyF (fmt)
import qualified Text.Regex.PCRE.Heavy as RE
data IgnoreCommand = IgnoreLine deriving (Show, Eq)
ignoreRe :: RE.Regex
ignoreRe = [RE.re|krank:ignore-(line)|]
extractIssuesOnALine :: ByteString -> [(Int, IgnoreCommand)]
extractIssuesOnALine lineContent = Prelude.map f (RE.scan ignoreRe lineContent)
where
f (match, [command]) = (colNo, ignoreCommand)
where
colNo = 1 + ByteString.length (fst $ ByteString.breakSubstring match lineContent)
ignoreCommand
| command == "line" = IgnoreLine
| otherwise = error [fmt|Impossible case, update the guard with: {ByteString.unpack command}|]
f res = error ("Error: impossible match" <> show res)
extractIgnores ::
FilePath ->
ByteString ->
[Localized IgnoreCommand]
extractIgnores filePath toCheck = concat (zipWith extract [1 ..] (ByteString.lines toCheck))
where
extract lineNo lineContent = Prelude.map f (extractIssuesOnALine lineContent)
where
f (colNo, gitIssue) = Localized (SourcePos filePath lineNo colNo) gitIssue
filterViolations ::
[Violation] ->
FilePath ->
ByteString ->
[Violation]
filterViolations violations filePath content =
DataL.filter isNotIgnored violations
where
ignoreCommands = extractIgnores filePath content
f hashMap ignoreCommand = HashM.insert (lineNumber . getLocation $ ignoreCommand) (unLocalized ignoreCommand) hashMap
ignoreIndex = foldl f HashM.empty ignoreCommands
isIgnored violation = HashM.lookup (lineNumber . location $ violation) ignoreIndex == Just IgnoreLine
isNotIgnored = not . isIgnored