From 728922d2b822eb3c05429f827105553c6763f5e2 Mon Sep 17 00:00:00 2001 From: Ng Zhi An Date: Sun, 6 May 2018 15:24:34 -0700 Subject: [PATCH 1/8] Remove unused code --- src/ShellCheck/Parser.hs | 6 ------ 1 file changed, 6 deletions(-) diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index 8cce9a9..f1f98a8 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -1223,12 +1223,6 @@ doubleQuotedPart = readDoubleLiteral <|> readDoubleQuotedDollar <|> readQuotedBa "This is a unicode quote. Delete and retype it (or ignore/singlequote for literal)." return $ T_Literal id [c] -readDoubleQuotedLiteral = do - doubleQuote - x <- readDoubleLiteral - doubleQuote - return x - readDoubleLiteral = do id <- getNextId s <- many1 readDoubleLiteralPart From f84859ab90fd310a4d4839c86b372c28ec544b9b Mon Sep 17 00:00:00 2001 From: Ng Zhi An Date: Sun, 6 May 2018 16:39:51 -0700 Subject: [PATCH 2/8] When given a %* format string, expect one more argument Fixes #1184 --- src/ShellCheck/Checks/Commands.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/ShellCheck/Checks/Commands.hs b/src/ShellCheck/Checks/Commands.hs index 4080461..7e2c660 100644 --- a/src/ShellCheck/Checks/Commands.hs +++ b/src/ShellCheck/Checks/Commands.hs @@ -513,6 +513,8 @@ prop_checkPrintfVar10= verifyNot checkPrintfVar "printf '%s %s %s' foo bar baz" prop_checkPrintfVar11= verifyNot checkPrintfVar "printf '%(%s%s)T' -1" prop_checkPrintfVar12= verify checkPrintfVar "printf '%s %s\\n' 1 2 3" prop_checkPrintfVar13= verifyNot checkPrintfVar "printf '%s %s\\n' 1 2 3 4" +prop_checkPrintfVar14= verify checkPrintfVar "printf '%*s\\n' 1" +prop_checkPrintfVar15= verifyNot checkPrintfVar "printf '%*s\\n' 1 2" checkPrintfVar = CommandCheck (Exactly "printf") (f . arguments) where f (doubledash:rest) | getLiteralString doubledash == Just "--" = f rest f (dashv:var:rest) | getLiteralString dashv == Just "-v" = f rest @@ -523,6 +525,7 @@ checkPrintfVar = CommandCheck (Exactly "printf") (f . arguments) where case string of '%':'%':rest -> countFormats rest '%':'(':rest -> 1 + countFormats (dropWhile (/= ')') rest) + '%':'*':rest -> 2 + countFormats rest -- width is specified as an argument '%':rest -> 1 + countFormats rest _:rest -> countFormats rest [] -> 0 From 719e1854e5c2c6af7d0722e77fa876f7858e198b Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Fri, 11 May 2018 21:39:54 -0700 Subject: [PATCH 3/8] Clarify 'export' suggestion in SC2034 (unused vars). --- src/ShellCheck/Analytics.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index ca835b3..7a3ca0c 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -1817,7 +1817,7 @@ checkUnusedAssignments params t = execWriter (mapM_ warnFor unused) warnFor (name, token) = warn (getId token) 2034 $ - name ++ " appears unused. Verify it or export it." + name ++ " appears unused. Verify use (or export if used externally)." stripSuffix = takeWhile isVariableChar defaultMap = Map.fromList $ zip internalVariables $ repeat () From bca2ad4e182a212087a17a526d2bddc6bbfb951a Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sat, 12 May 2018 17:34:23 -0700 Subject: [PATCH 4/8] Don't think declare -x -F var is used (fixes #1209). --- src/ShellCheck/Analytics.hs | 1 + src/ShellCheck/AnalyzerLib.hs | 4 +++- 2 files changed, 4 insertions(+), 1 deletion(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index 7a3ca0c..d73ff8e 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -1800,6 +1800,7 @@ prop_checkUnused35= verifyNotTree checkUnusedAssignments "a=foo; b=2; echo ${a:b prop_checkUnused36= verifyNotTree checkUnusedAssignments "if [[ -v foo ]]; then true; fi" prop_checkUnused37= verifyNotTree checkUnusedAssignments "fd=2; exec {fd}>&-" prop_checkUnused38= verifyTree checkUnusedAssignments "(( a=42 ))" +prop_checkUnused39= verifyNotTree checkUnusedAssignments "declare -x -f foo" checkUnusedAssignments params t = execWriter (mapM_ warnFor unused) where flow = variableFlow params diff --git a/src/ShellCheck/AnalyzerLib.hs b/src/ShellCheck/AnalyzerLib.hs index f3470b9..fc5e30b 100644 --- a/src/ShellCheck/AnalyzerLib.hs +++ b/src/ShellCheck/AnalyzerLib.hs @@ -498,7 +498,9 @@ getReferencedVariableCommand base@(T_SimpleCommand _ _ (T_NormalWord _ (T_Litera "export" -> if "f" `elem` flags then [] else concatMap getReference rest - "declare" -> if any (`elem` flags) ["x", "p"] + "declare" -> if + any (`elem` flags) ["x", "p"] && + (not $ any (`elem` flags) ["f", "F"]) then concatMap getReference rest else [] "readonly" -> From aa3b3fdc56a41fd8b7d8e01056efbfdc7a644ba6 Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sat, 12 May 2018 17:47:21 -0700 Subject: [PATCH 5/8] Make .ghci look in ./src --- .ghci | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.ghci b/.ghci index ed7b31f..f20fa67 100644 --- a/.ghci +++ b/.ghci @@ -1 +1 @@ -:set -idist/build/autogen +:set -idist/build/autogen -isrc From cf608dc2f65b53f416de8e6e45a366d0fd32b204 Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sat, 12 May 2018 18:30:35 -0700 Subject: [PATCH 6/8] Parse FD move operations like 2>&1- correctly. Fixes #1180. --- CHANGELOG.md | 1 + src/ShellCheck/Analytics.hs | 1 + src/ShellCheck/Parser.hs | 10 +++++++++- 3 files changed, 11 insertions(+), 1 deletion(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index aa82016..97edd24 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -16,6 +16,7 @@ - Associative arrays are now respected in arithmetic contexts - SC1087 about `$var[@]` now correctly triggers on any index - Bad expansions in here documents are no longer ignored +- FD move operations like {fd}>1- now parse correctly ### Changed - SC1073: 'else if' is now parsed correctly and not like 'elif' diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index d73ff8e..e55d12b 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -1401,6 +1401,7 @@ prop_checkSpuriousExec4 = verifyNot checkSpuriousExec "if a; then exec b; fi" prop_checkSpuriousExec5 = verifyNot checkSpuriousExec "exec > file; cmd" prop_checkSpuriousExec6 = verify checkSpuriousExec "exec foo > file; cmd" prop_checkSpuriousExec7 = verifyNot checkSpuriousExec "exec file; echo failed; exit 3" +prop_checkSpuriousExec8 = verifyNot checkSpuriousExec "exec {origout}>&1- >tmp.log 2>&1; bar" checkSpuriousExec _ = doLists where doLists (T_Script _ _ cmds) = doList cmds diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index 8cce9a9..1152cf9 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -1716,8 +1716,15 @@ readIoFileOp = choice [g_DGREAT, g_LESSGREAT, g_GREATAND, g_LESSAND, g_CLOBBER, readIoDuplicate = try $ do id <- getNextId op <- g_GREATAND <|> g_LESSAND - target <- readIoVariable <|> many1 digit <|> string "-" + target <- readIoVariable <|> digitsAndOrDash return $ T_IoDuplicate id op target + where + -- either digits with optional dash, or a required dash + digitsAndOrDash = do + str <- many digit + dash <- (if null str then id else option "") $ string "-" + return $ str ++ dash + prop_readIoFile = isOk readIoFile ">> \"$(date +%YYmmDD)\"" readIoFile = called "redirection" $ do @@ -1744,6 +1751,7 @@ prop_readIoRedirect3 = isOk readIoRedirect "4>&-" prop_readIoRedirect4 = isOk readIoRedirect "&> lol" prop_readIoRedirect5 = isOk readIoRedirect "{foo}>&2" prop_readIoRedirect6 = isOk readIoRedirect "{foo}<&-" +prop_readIoRedirect7 = isOk readIoRedirect "{foo}>&1-" readIoRedirect = do id <- getNextId n <- readIoSource From b3362f1dc3493638be0512dcd3c1105082150877 Mon Sep 17 00:00:00 2001 From: Ng Zhi An Date: Sun, 13 May 2018 15:17:32 -0700 Subject: [PATCH 7/8] Assignments are okay in SC2094 (fixes #1192) --- src/ShellCheck/Analytics.hs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index e55d12b..357f353 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -573,6 +573,7 @@ prop_checkRedirectToSame4 = verifyNot checkRedirectToSame "foo /dev/null > /dev/ prop_checkRedirectToSame5 = verifyNot checkRedirectToSame "foo > bar 2> bar" prop_checkRedirectToSame6 = verifyNot checkRedirectToSame "echo foo > foo" prop_checkRedirectToSame7 = verifyNot checkRedirectToSame "sed 's/foo/bar/g' file | sponge file" +prop_checkRedirectToSame8 = verifyNot checkRedirectToSame "while read -r line; do _=\"$fname\"; done <\"$fname\"" checkRedirectToSame params s@(T_Pipeline _ _ list) = mapM_ (\l -> (mapM_ (\x -> doAnalysis (checkOccurrences x) l) (getAllRedirs list))) list where @@ -583,7 +584,8 @@ checkRedirectToSame params s@(T_Pipeline _ _ list) = && x == y && not (isOutput t && isOutput u) && not (special t) - && not (any isHarmlessCommand [t,u])) $ do + && not (any isHarmlessCommand [t,u]) + && not (any containsAssignment [u])) $ do addComment $ note newId addComment $ note exceptId checkOccurrences _ _ = return () @@ -610,6 +612,9 @@ checkRedirectToSame params s@(T_Pipeline _ _ list) = cmd <- getClosestCommand (parentMap params) arg name <- getCommandBasename cmd return $ name `elem` ["echo", "printf", "sponge"] + containsAssignment arg = fromMaybe False $ do + cmd <- getClosestCommand (parentMap params) arg + return $ isAssignment cmd checkRedirectToSame _ _ = return () From 0c88fbc76d7255b349bbdf00c051aead886ecd86 Mon Sep 17 00:00:00 2001 From: Ng Zhi An Date: Sun, 13 May 2018 15:18:55 -0700 Subject: [PATCH 8/8] Suppress SC2016 for git filter-branch (fixes #196) --- src/ShellCheck/Analytics.hs | 11 ++++++++++- 1 file changed, 10 insertions(+), 1 deletion(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index e55d12b..2256638 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -788,6 +788,8 @@ prop_checkSingleQuotedVariables11= verifyNot checkSingleQuotedVariables "sed '${ prop_checkSingleQuotedVariables12= verifyNot checkSingleQuotedVariables "eval 'echo $1'" prop_checkSingleQuotedVariables13= verifyNot checkSingleQuotedVariables "busybox awk '{print $1}'" prop_checkSingleQuotedVariables14= verifyNot checkSingleQuotedVariables "[ -v 'bar[$foo]' ]" +prop_checkSingleQuotedVariables15= verifyNot checkSingleQuotedVariables "git filter-branch 'test $GIT_COMMIT'" +prop_checkSingleQuotedVariables16= verify checkSingleQuotedVariables "git '$a'" checkSingleQuotedVariables params t@(T_SingleQuoted id s) = when (s `matches` re) $ if "sed" == commandName @@ -800,7 +802,7 @@ checkSingleQuotedVariables params t@(T_SingleQuoted id s) = commandName = fromMaybe "" $ do cmd <- getClosestCommand parents t name <- getCommandBasename cmd - return $ if name == "find" then getFindCommand cmd else name + return $ if name == "find" then getFindCommand cmd else if name == "git" then getGitCommand cmd else name isProbablyOk = any isOkAssignment (take 3 $ getPath parents t) @@ -818,6 +820,7 @@ checkSingleQuotedVariables params t@(T_SingleQuoted id s) = ,"docker" -- like above ,"dpkg-query" ,"jq" -- could also check that user provides --arg + ,"git filter-branch" ] || "awk" `isSuffixOf` commandName || "perl" `isPrefixOf` commandName @@ -841,6 +844,12 @@ checkSingleQuotedVariables params t@(T_SingleQuoted id s) = _ -> "find" getFindCommand (T_Redirecting _ _ cmd) = getFindCommand cmd getFindCommand _ = "find" + getGitCommand (T_SimpleCommand _ _ words) = + case map getLiteralString words of + Just "git":Just "filter-branch":_ -> "git filter-branch" + _ -> "git" + getGitCommand (T_Redirecting _ _ cmd) = getGitCommand cmd + getGitCommand _ = "git" checkSingleQuotedVariables _ _ = return ()