Implement loading of automatic annotation files
This commit is contained in:
parent
7d0f4da27f
commit
461f34a100
3 changed files with 63 additions and 26 deletions
1
example/automatic-rules
Normal file
1
example/automatic-rules
Normal file
|
|
@ -0,0 +1 @@
|
||||||
|
Intentional (Rule "autosar_cpp14_a18_9_1") "Test auto"
|
||||||
|
|
@ -16,8 +16,9 @@ import Control.Monad.IO.Class
|
||||||
import Control.Monad.Trans.Reader
|
import Control.Monad.Trans.Reader
|
||||||
import Control.Exception (evaluate)
|
import Control.Exception (evaluate)
|
||||||
import Data.Function (on)
|
import Data.Function (on)
|
||||||
import Data.List (delete, intercalate, foldl', sortBy)
|
import Data.List (delete, intercalate, foldl', sortBy, nub)
|
||||||
import Data.Char (isSpace)
|
import Data.Char (isSpace)
|
||||||
|
import Data.Either (rights)
|
||||||
import Data.Ord
|
import Data.Ord
|
||||||
import Data.Monoid
|
import Data.Monoid
|
||||||
import Data.Maybe (fromMaybe, catMaybes)
|
import Data.Maybe (fromMaybe, catMaybes)
|
||||||
|
|
@ -29,7 +30,7 @@ import Annotator.Rule
|
||||||
import Annotator.Annotation
|
import Annotator.Annotation
|
||||||
|
|
||||||
version :: Vsn.Version
|
version :: Vsn.Version
|
||||||
version = Vsn.makeVersion [0,0,2,1]
|
version = Vsn.makeVersion [0,0,3,0]
|
||||||
|
|
||||||
type App a = ReaderT Options IO a
|
type App a = ReaderT Options IO a
|
||||||
|
|
||||||
|
|
@ -52,6 +53,7 @@ data Options = Options
|
||||||
, contextLines :: Int
|
, contextLines :: Int
|
||||||
, onlyNewest :: Bool
|
, onlyNewest :: Bool
|
||||||
, annotationFiles :: [FilePath]
|
, annotationFiles :: [FilePath]
|
||||||
|
, autoAnnotations :: [Annotation]
|
||||||
}
|
}
|
||||||
deriving (Show, Eq)
|
deriving (Show, Eq)
|
||||||
|
|
||||||
|
|
@ -64,6 +66,7 @@ defaultOptions = Options
|
||||||
, contextLines = 0
|
, contextLines = 0
|
||||||
, onlyNewest = True
|
, onlyNewest = True
|
||||||
, annotationFiles = []
|
, annotationFiles = []
|
||||||
|
, autoAnnotations = []
|
||||||
}
|
}
|
||||||
|
|
||||||
options :: [OptDescr (Options -> Options)]
|
options :: [OptDescr (Options -> Options)]
|
||||||
|
|
@ -89,9 +92,9 @@ options =
|
||||||
, Option ['C'] ["context"]
|
, Option ['C'] ["context"]
|
||||||
(OptArg ((\f opts -> opts { contextLines = fromMaybe 0 $ readMaybe f }) . fromMaybe "0") "NUM")
|
(OptArg ((\f opts -> opts { contextLines = fromMaybe 0 $ readMaybe f }) . fromMaybe "0") "NUM")
|
||||||
"specify how much context should be shown around a violation"
|
"specify how much context should be shown around a violation"
|
||||||
-- , Option ['A'] ["annotations"]
|
, Option ['A'] ["annotations"]
|
||||||
-- (ReqArg (\f opts -> opts { annotationFiles = (nub $ annotationFiles opts ++ [f]) }) "FILE")
|
(ReqArg (\f opts -> opts { annotationFiles = (nub $ annotationFiles opts ++ [f]) }) "FILE")
|
||||||
-- "load automatic annotation rules"
|
"load automatic annotation rules"
|
||||||
]
|
]
|
||||||
|
|
||||||
readMaybe :: (Read a) => String -> Maybe a
|
readMaybe :: (Read a) => String -> Maybe a
|
||||||
|
|
@ -136,7 +139,11 @@ defaultMain = do
|
||||||
putStr $ usageInfo header options
|
putStr $ usageInfo header options
|
||||||
exitWith ExitSuccess
|
exitWith ExitSuccess
|
||||||
|
|
||||||
runReaderT (genericMain fn) opts
|
automaticAnnotations <- rights . concat <$> mapM fromFile (annotationFiles opts)
|
||||||
|
|
||||||
|
let opts' = opts { autoAnnotations = automaticAnnotations }
|
||||||
|
|
||||||
|
runReaderT (genericMain fn) opts'
|
||||||
|
|
||||||
where
|
where
|
||||||
header = unlines $
|
header = unlines $
|
||||||
|
|
@ -340,6 +347,11 @@ handleViolation content v@Violation{..} = do
|
||||||
context = getContext (contextLines opts) before after
|
context = getContext (contextLines opts) before after
|
||||||
indent = takeWhile isSpace (snd . head $ after)
|
indent = takeWhile isSpace (snd . head $ after)
|
||||||
|
|
||||||
|
case lookupAnnotation rule (autoAnnotations opts) of
|
||||||
|
Just a -> do
|
||||||
|
verbose Low $ "automatically annotated violation of rule " <> show rule
|
||||||
|
pure $ Just (AnnotatedViolation v a indent)
|
||||||
|
_ -> do
|
||||||
verbose Chatty $ "indentation: " <> show indent
|
verbose Chatty $ "indentation: " <> show indent
|
||||||
|
|
||||||
-- print some context
|
-- print some context
|
||||||
|
|
@ -362,6 +374,17 @@ handleViolation content v@Violation{..} = do
|
||||||
Annotate annotation -> pure $ Just (AnnotatedViolation v annotation indent)
|
Annotate annotation -> pure $ Just (AnnotatedViolation v annotation indent)
|
||||||
Skip -> pure Nothing
|
Skip -> pure Nothing
|
||||||
Help -> handleViolation content v
|
Help -> handleViolation content v
|
||||||
|
where
|
||||||
|
lookupAnnotation :: Rule -> [Annotation] -> Maybe Annotation
|
||||||
|
lookupAnnotation _ [] = Nothing
|
||||||
|
lookupAnnotation r (a:as)
|
||||||
|
| r == annotationRule a = Just a
|
||||||
|
| otherwise = lookupAnnotation r as
|
||||||
|
|
||||||
|
annotationRule :: Annotation -> Rule
|
||||||
|
annotationRule (Intentional r _) = r
|
||||||
|
annotationRule (FalsePositive r _) = r
|
||||||
|
annotationRule (ToDo r) = r
|
||||||
|
|
||||||
-- | Get some context around some line
|
-- | Get some context around some line
|
||||||
--
|
--
|
||||||
|
|
|
||||||
|
|
@ -1,4 +1,5 @@
|
||||||
module Annotator.Annotation (Annotation(..), showAnnotation) where
|
{-# LANGUAGE LambdaCase #-}
|
||||||
|
module Annotator.Annotation (Annotation(..), showAnnotation, fromFile) where
|
||||||
|
|
||||||
import Annotator.Rule
|
import Annotator.Rule
|
||||||
import Data.Monoid
|
import Data.Monoid
|
||||||
|
|
@ -12,3 +13,15 @@ showAnnotation :: Annotation -> String -> String
|
||||||
showAnnotation (Intentional (Rule rule) reason) _ = mconcat ["// ", "coverity[", rule, "_violation", "] ", reason]
|
showAnnotation (Intentional (Rule rule) reason) _ = mconcat ["// ", "coverity[", rule, "_violation", "] ", reason]
|
||||||
showAnnotation (FalsePositive (Rule rule) reason) _ = mconcat ["// ", "coverity[", rule, "_violation", " : FALSE", "] ", reason]
|
showAnnotation (FalsePositive (Rule rule) reason) _ = mconcat ["// ", "coverity[", rule, "_violation", " : FALSE", "] ", reason]
|
||||||
showAnnotation (ToDo (Rule rule)) description = "// FIXME violation " <> rule <> ": " <> description
|
showAnnotation (ToDo (Rule rule)) description = "// FIXME violation " <> rule <> ": " <> description
|
||||||
|
|
||||||
|
fromFile :: FilePath -> IO [Either String Annotation]
|
||||||
|
fromFile fn = fmap safeRead . removeBoring . lines <$> readFile fn
|
||||||
|
where
|
||||||
|
removeBoring :: [String] -> [String]
|
||||||
|
removeBoring = filter (const True)
|
||||||
|
|
||||||
|
safeRead :: String -> Either String Annotation
|
||||||
|
safeRead s = case reads s of
|
||||||
|
[] -> Left "empty line"
|
||||||
|
[(a,"")] -> Right a
|
||||||
|
_ -> Left "invalid line"
|
||||||
|
|
|
||||||
Loading…
Add table
Add a link
Reference in a new issue