Allow '# shellcheck disable=SC1234' to ignore by code.

This commit is contained in:
Vidar Holen 2014-01-16 23:08:56 -08:00
parent 4dca88aade
commit 43ed5e748d
4 changed files with 124 additions and 15 deletions

View File

@ -117,8 +117,10 @@ data Token =
| T_UntilExpression Id [Token] [Token] | T_UntilExpression Id [Token] [Token]
| T_While Id | T_While Id
| T_WhileExpression Id [Token] [Token] | T_WhileExpression Id [Token] [Token]
| T_Annotation Id [Annotation] Token
deriving (Show) deriving (Show)
data Annotation = DisableComment Integer deriving (Show, Eq)
data ConditionType = DoubleBracket | SingleBracket deriving (Show, Eq) data ConditionType = DoubleBracket | SingleBracket deriving (Show, Eq)
-- I apologize for nothing! -- I apologize for nothing!
@ -239,6 +241,7 @@ analyze f g i t =
return $ TA_Trinary id a b c return $ TA_Trinary id a b c
delve (TA_Expansion id t) = d1 t $ TA_Expansion id delve (TA_Expansion id t) = d1 t $ TA_Expansion id
delve (TA_Base id b t) = d1 t $ TA_Base id b delve (TA_Base id b t) = d1 t $ TA_Base id b
delve (T_Annotation id anns t) = d1 t $ T_Annotation id anns
delve t = return t delve t = return t
getId t = case t of getId t = case t of
@ -331,6 +334,7 @@ getId t = case t of
T_DollarSingleQuoted id _ -> id T_DollarSingleQuoted id _ -> id
T_DollarDoubleQuoted id _ -> id T_DollarDoubleQuoted id _ -> id
T_DollarBracket id _ -> id T_DollarBracket id _ -> id
T_Annotation id _ _ -> id
blank :: Monad m => Token -> m () blank :: Monad m => Token -> m ()
blank = const $ return () blank = const $ return ()

View File

@ -154,6 +154,21 @@ runBasicTreeAnalysis checks token =
parentTree = getParentTree token parentTree = getParentTree token
runTree f t = runBasicAnalysis (flip f $ parentTree) t runTree f t = runBasicAnalysis (flip f $ parentTree) t
filterByAnnotation token metadataMap =
Map.mapWithKey removeVals metadataMap
where
removeVals id (Metadata pos notes) =
Metadata pos $ filter (not . shouldIgnore id . numFor) notes
numFor (Note _ code _) = code
shouldIgnore id num =
any (shouldIgnoreFor num) $ getPath parents (T_Bang id)
shouldIgnoreFor num (T_Annotation _ anns _) =
any hasNum anns
where
hasNum (DisableComment ts) = num == ts
shouldIgnoreFor _ _ = False
parents = getParentTree token
addNoteFor id note = modify ((id, note):) addNoteFor id note = modify ((id, note):)
warn id code note = addNoteFor id $ Note WarningC code $ note warn id code note = addNoteFor id $ Note WarningC code $ note
err id code note = addNoteFor id $ Note ErrorC code $ note err id code note = addNoteFor id $ Note ErrorC code $ note
@ -218,6 +233,7 @@ isEmpty token =
makeSimple (T_NormalWord _ [f]) = f makeSimple (T_NormalWord _ [f]) = f
makeSimple (T_Redirecting _ _ f) = f makeSimple (T_Redirecting _ _ f) = f
makeSimple (T_Annotation _ _ f) = f
makeSimple t = t makeSimple t = t
simplify = doTransform makeSimple simplify = doTransform makeSimple
@ -234,6 +250,7 @@ deadSimple (T_Literal _ x) = [x]
deadSimple (T_SimpleCommand _ vars words) = concatMap (deadSimple) words deadSimple (T_SimpleCommand _ vars words) = concatMap (deadSimple) words
deadSimple (T_Redirecting _ _ foo) = deadSimple foo deadSimple (T_Redirecting _ _ foo) = deadSimple foo
deadSimple (T_DollarSingleQuoted _ s) = [s] deadSimple (T_DollarSingleQuoted _ s) = [s]
deadSimple (T_Annotation _ _ s) = deadSimple s
deadSimple _ = [] deadSimple _ = []
(!!!) list i = (!!!) list i =
@ -1054,11 +1071,13 @@ getCommandName (T_Redirecting _ _ w) =
getCommandName w getCommandName w
getCommandName (T_SimpleCommand _ _ (w:_)) = getCommandName (T_SimpleCommand _ _ (w:_)) =
getLiteralString w getLiteralString w
getCommandName (T_Annotation _ _ t) = getCommandName t
getCommandName _ = Nothing getCommandName _ = Nothing
getCommandBasename = liftM basename . getCommandName getCommandBasename = liftM basename . getCommandName
basename = reverse . (takeWhile (/= '/')) . reverse basename = reverse . (takeWhile (/= '/')) . reverse
isAssignment (T_Annotation _ _ w) = isAssignment w
isAssignment (T_Redirecting _ _ w) = isAssignment w isAssignment (T_Redirecting _ _ w) = isAssignment w
isAssignment (T_SimpleCommand _ (w:_) []) = True isAssignment (T_SimpleCommand _ (w:_) []) = True
isAssignment _ = False isAssignment _ = False

View File

@ -104,8 +104,12 @@ data Note = Note Severity Code String deriving (Show, Eq)
data ParseNote = ParseNote SourcePos Severity Code String deriving (Show, Eq) data ParseNote = ParseNote SourcePos Severity Code String deriving (Show, Eq)
data Metadata = Metadata SourcePos [Note] deriving (Show) data Metadata = Metadata SourcePos [Note] deriving (Show)
data Severity = ErrorC | WarningC | InfoC | StyleC deriving (Show, Eq, Ord) data Severity = ErrorC | WarningC | InfoC | StyleC deriving (Show, Eq, Ord)
data Context = ContextName SourcePos String | ContextAnnotation [Annotation]
type Code = Integer type Code = Integer
codeForNote (Note _ code _) = code
codeForParseNote (ParseNote _ _ code _) = code
initialState = (Id $ -1, Map.empty, []) initialState = (Id $ -1, Map.empty, [])
getInitialMeta pos = Metadata pos [] getInitialMeta pos = Metadata pos []
@ -139,9 +143,19 @@ getParseNotes = do
return notes return notes
addParseNote n = do addParseNote n = do
irrelevant <- shouldIgnoreCode (codeForParseNote n)
when (not irrelevant) $ do
(a, b, notes) <- getState (a, b, notes) <- getState
putState (a, b, n:notes) putState (a, b, n:notes)
shouldIgnoreCode code = do
context <- getCurrentContexts
return $ any disabling context
where
disabling (ContextAnnotation list) =
any disabling' list
disabling _ = False
disabling' (DisableComment n) = code == n
-- Store potential parse problems outside of parsec -- Store potential parse problems outside of parsec
parseProblem level code msg = do parseProblem level code msg = do
@ -170,6 +184,8 @@ pushContext c = do
setCurrentContexts (c:v) setCurrentContexts (c:v)
parseProblemAt pos level code msg = do parseProblemAt pos level code msg = do
irrelevant <- shouldIgnoreCode code
when (not irrelevant) $
Ms.modify (\(list, current) -> ((ParseNote pos level code msg):list, current)) Ms.modify (\(list, current) -> ((ParseNote pos level code msg):list, current))
-- Store non-parse problems inside -- Store non-parse problems inside
@ -226,9 +242,8 @@ acceptButWarn parser level code note = do
parseProblemAt pos level code note parseProblemAt pos level code note
) )
called s p = do withContext entry p = do
pos <- getPosition pushContext entry
pushContext (pos, s)
do do
v <- p v <- p
popContext popContext
@ -237,6 +252,13 @@ called s p = do
popContext popContext
fail $ "" fail $ ""
called s p = do
pos <- getPosition
withContext (ContextName pos s) p
withAnnotations anns p =
withContext (ContextAnnotation anns) p
readConditionContents single = do readConditionContents single = do
readCondContents `attempting` (lookAhead $ do readCondContents `attempting` (lookAhead $ do
pos <- getPosition pos <- getPosition
@ -615,7 +637,41 @@ condSpacingMsg soft msg = do
space <- spacing space <- spacing
when (null space) $ (if soft then parseNoteAt else parseProblemAt) pos ErrorC 1035 msg when (null space) $ (if soft then parseNoteAt else parseProblemAt) pos ErrorC 1035 msg
readAnnotationPrefix = do
char '#'
many linewhitespace
string "shellcheck"
prop_readAnnotation1 = isOk readAnnotation "# shellcheck disable=1234,5678\n"
prop_readAnnotation2 = isOk readAnnotation "# shellcheck disable=SC1234 disable=SC5678\n"
readAnnotation = called "shellcheck annotation" $ do
try readAnnotationPrefix
many1 linewhitespace
values <- many1 (readDisable)
linefeed
many linewhitespace
return $ concat values
where
readDisable = forKey "disable" $ do
readCode `sepBy` char ','
where
readCode = do
optional $ string "SC"
int <- many1 digit
return $ DisableComment (read int)
forKey s p = do
try $ string s
char '='
value <- p
many linewhitespace
return value
readAnnotations = do
annotations <- many (readAnnotation `thenSkip` allspacing)
return $ concat annotations
readComment = do readComment = do
unexpecting "shellcheck annotation" readAnnotationPrefix
char '#' char '#'
many $ noneOf "\r\n" many $ noneOf "\r\n"
@ -1229,12 +1285,23 @@ readPipeline = do
readPipeSequence readPipeSequence
prop_readAndOr = isOk readAndOr "grep -i lol foo || exit 1" prop_readAndOr = isOk readAndOr "grep -i lol foo || exit 1"
readAndOr = chainr1 readPipeline $ do prop_readAndOr1 = isOk readAndOr "# shellcheck disable=1\nfoo"
prop_readAndOr2 = isOk readAndOr "# shellcheck disable=1\n# lol\n# shellcheck disable=3\nfoo"
readAndOr = do
aid <- getNextId
annotations <- readAnnotations
andOr <- withAnnotations annotations $ do
chainr1 readPipeline $ do
op <- g_AND_IF <|> g_OR_IF op <- g_AND_IF <|> g_OR_IF
readLineBreak readLineBreak
return $ case op of T_AND_IF id -> T_AndIf id return $ case op of T_AND_IF id -> T_AndIf id
T_OR_IF id -> T_OrIf id T_OR_IF id -> T_OrIf id
return $ if null annotations
then andOr
else T_Annotation aid annotations andOr
readTerm = do readTerm = do
allspacing allspacing
m <- readAndOr m <- readAndOr
@ -1840,10 +1907,12 @@ parseShell filename contents = do
(Left err, (p, context)) -> ParseResult Nothing (nub $ sortNotes $ p ++ (notesForContext context) ++ ([makeErrorFor err])) (Left err, (p, context)) -> ParseResult Nothing (nub $ sortNotes $ p ++ (notesForContext context) ++ ([makeErrorFor err]))
where where
notesForContext list = zipWith ($) [first, second] list isName (ContextName _ _) = True
first (pos, str) = ParseNote pos ErrorC 1073 $ isName _ = False
notesForContext list = zipWith ($) [first, second] $ filter isName list
first (ContextName pos str) = ParseNote pos ErrorC 1073 $
"Couldn't parse this " ++ str ++ "." "Couldn't parse this " ++ str ++ "."
second (pos, str) = ParseNote pos InfoC 1009 $ second (ContextName pos str) = ParseNote pos InfoC 1009 $
"The mentioned parser error was in this " ++ str ++ "." "The mentioned parser error was in this " ++ str ++ "."
lt x = trace (show x) x lt x = trace (show x) x

View File

@ -23,13 +23,30 @@ import Data.Maybe
import Text.Parsec.Pos import Text.Parsec.Pos
import Data.List import Data.List
prop_findsParseIssue =
let comments = shellCheck "echo \"$12\"" in
(length comments) == 1 && (scCode $ head comments) == 1037
prop_commentDisablesParseIssue1 =
null $ shellCheck "#shellcheck disable=SC1037\necho \"$12\""
prop_commentDisablesParseIssue2 =
null $ shellCheck "#shellcheck disable=SC1037\n#lol\necho \"$12\""
prop_findsAnalysisIssue =
let comments = shellCheck "echo $1" in
(length comments) == 1 && (scCode $ head comments) == 2086
prop_commentDisablesAnalysisIssue1 =
null $ shellCheck "#shellcheck disable=SC2086\necho $1"
prop_commentDisablesAnalysisIssue2 =
null $ shellCheck "#shellcheck disable=SC2086\n#lol\necho $1"
shellCheck :: String -> [ShellCheckComment] shellCheck :: String -> [ShellCheckComment]
shellCheck script = shellCheck script =
let (ParseResult result notes) = parseShell "-" script in let (ParseResult result notes) = parseShell "-" script in
let allNotes = notes ++ (concat $ maybeToList $ do let allNotes = notes ++ (concat $ maybeToList $ do
(tree, map) <- result (tree, map) <- result
let newMap = runAllAnalytics tree map let newMap = runAllAnalytics tree map
return $ notesFromMap newMap return $ notesFromMap $ filterByAnnotation tree newMap
) )
in in
map formatNote $ nub $ sortNotes allNotes map formatNote $ nub $ sortNotes allNotes