diff --git a/ShellCheck/Analytics.hs b/ShellCheck/Analytics.hs index d2bfd0e..bbaeb0b 100644 --- a/ShellCheck/Analytics.hs +++ b/ShellCheck/Analytics.hs @@ -366,7 +366,7 @@ verifyNotTree :: (Parameters -> Token -> [Note]) -> String -> Bool verifyNotTree f s = checkTree f s == Just False checkNode f = checkTree (runNodeAnalysis f) -checkTree f s = case parseShell "-" s of +checkTree f s = case parseShell defaultAnalysisOptions "-" s of (ParseResult (Just (t, m)) _) -> Just . not . null $ runList defaultAnalysisOptions t [f] _ -> Nothing diff --git a/ShellCheck/Parser.hs b/ShellCheck/Parser.hs index ce20784..4bd8441 100644 --- a/ShellCheck/Parser.hs +++ b/ShellCheck/Parser.hs @@ -20,6 +20,7 @@ module ShellCheck.Parser (Note(..), Severity(..), parseShell, ParseResult(..), P import ShellCheck.AST import ShellCheck.Data +import ShellCheck.Options import Text.Parsec import Debug.Trace import Control.Monad @@ -2157,13 +2158,13 @@ getStringFromParsec errors = Message s -> if null s then Nothing else return $ s ++ "." unexpected s = "Unexpected " ++ (if null s then "eof" else s) ++ "." -parseShell filename contents = +parseShell options filename contents = case rp (parseWithNotes readScript) filename contents of (Right (script, map, notes), (parsenotes, _)) -> - ParseResult (Just (script, map)) (nub $ sortNotes $ notes ++ parsenotes) + ParseResult (Just (script, map)) (nub . sortNotes . excludeNotes $ notes ++ parsenotes) (Left err, (p, context)) -> ParseResult Nothing - (nub $ sortNotes $ p ++ notesForContext context ++ [makeErrorFor err]) + (nub . sortNotes . excludeNotes $ p ++ notesForContext context ++ [makeErrorFor err]) where isName (ContextName _ _) = True isName _ = False @@ -2172,6 +2173,7 @@ parseShell filename contents = "Couldn't parse this " ++ str ++ "." second (ContextName pos str) = ParseNote pos InfoC 1009 $ "The mentioned parser error was in this " ++ str ++ "." + excludeNotes = filter (\c -> codeForParseNote c `notElem` optionExcludes options) lt x = trace (show x) x ltt t = trace (show t) diff --git a/ShellCheck/Simple.hs b/ShellCheck/Simple.hs index 4eef476..71cde43 100644 --- a/ShellCheck/Simple.hs +++ b/ShellCheck/Simple.hs @@ -28,7 +28,7 @@ import Text.Parsec.Pos shellCheck :: AnalysisOptions -> String -> [ShellCheckComment] shellCheck options script = - let (ParseResult result notes) = parseShell "-" script in + let (ParseResult result notes) = parseShell options "-" script in let allNotes = notes ++ concat (maybeToList $ do (tree, posMap) <- result let list = runAnalytics options tree @@ -72,6 +72,9 @@ prop_commentDisablesAnalysisIssue2 = prop_optionDisablesIssue1 = null $ shellCheck (defaultAnalysisOptions { optionExcludes = [2086, 2148] }) "echo $1" +prop_optionDisablesIssue2 = + null $ shellCheck (defaultAnalysisOptions { optionExcludes = [2148, 1037] }) "echo \"$10\"" + return [] runTests = $quickCheckAll