From 07ffcb626ebfdabe7ae283cf073a59e04994dd8b Mon Sep 17 00:00:00 2001 From: Hugo Peixoto Date: Mon, 27 May 2019 10:58:16 +0100 Subject: [PATCH 01/35] SC2016: Don't trigger when using empty backticks When using '``' or '```', it should not suggest using double quotes. --- src/ShellCheck/Analytics.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index 36b941e..4babe73 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -917,6 +917,8 @@ prop_checkSingleQuotedVariables14= verifyNot checkSingleQuotedVariables "[ -v 'b prop_checkSingleQuotedVariables15= verifyNot checkSingleQuotedVariables "git filter-branch 'test $GIT_COMMIT'" prop_checkSingleQuotedVariables16= verify checkSingleQuotedVariables "git '$a'" prop_checkSingleQuotedVariables17= verifyNot checkSingleQuotedVariables "rename 's/(.)a/$1/g' *" +prop_checkSingleQuotedVariables18= verifyNot checkSingleQuotedVariables "echo '``'" +prop_checkSingleQuotedVariables19= verifyNot checkSingleQuotedVariables "echo '```'" checkSingleQuotedVariables params t@(T_SingleQuoted id s) = when (s `matches` re) $ @@ -962,7 +964,7 @@ checkSingleQuotedVariables params t@(T_SingleQuoted id s) = TC_Unary _ _ "-v" _ -> True _ -> False - re = mkRegex "\\$[{(0-9a-zA-Z_]|`.*`" + re = mkRegex "\\$[{(0-9a-zA-Z_]|`[^`]+`" sedContra = mkRegex "\\$[{dpsaic]($|[^a-zA-Z])" getFindCommand (T_SimpleCommand _ _ words) = From 3e7c2bfec04ed6a0479a5f0e35d129c8089f3e7e Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sun, 2 Jun 2019 09:24:53 -0700 Subject: [PATCH 02/35] Warn about [ $a != x ] || [ $a != y ] --- CHANGELOG.md | 1 + src/ShellCheck/Analytics.hs | 29 +++++++++++++++++++++++++++-- 2 files changed, 28 insertions(+), 2 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index 262849f..93f83c8 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -8,6 +8,7 @@ - Source paths: Use `-P dir1:dir2` or a `source-path=dir1` directive to specify search paths for sourced files. - json1 format like --format=json but treats tabs as single characters +- SC2252: Warn about `[ $a != x ] || [ $a != y ]`, similar to SC2055 - SC2251: Inform about ineffectual ! in front of commands - SC2250: Warn about variable references without braces (optional) - SC2249: Warn about `case` with missing default case (optional) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index 36b941e..3ee454c 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -1348,14 +1348,39 @@ prop_checkOrNeq2 = verify checkOrNeq "(( a!=lol || a!=foo ))" prop_checkOrNeq3 = verify checkOrNeq "[ \"$a\" != lol || \"$a\" != foo ]" prop_checkOrNeq4 = verifyNot checkOrNeq "[ a != $cow || b != $foo ]" prop_checkOrNeq5 = verifyNot checkOrNeq "[[ $a != /home || $a != */public_html/* ]]" +prop_checkOrNeq6 = verify checkOrNeq "[ $a != a ] || [ $a != b ]" +prop_checkOrNeq7 = verify checkOrNeq "[ $a != a ] || [ $a != b ] || true" +prop_checkOrNeq8 = verifyNot checkOrNeq "[[ $a != x || $a != x ]]" -- This only catches the most idiomatic cases. Fixme? + +-- For test-level "or": [ x != y -o x != z ] checkOrNeq _ (TC_Or id typ op (TC_Binary _ _ op1 lhs1 rhs1 ) (TC_Binary _ _ op2 lhs2 rhs2)) - | lhs1 == lhs2 && (op1 == op2 && (op1 == "-ne" || op1 == "!=")) && not (any isGlob [rhs1,rhs2]) = + | (op1 == op2 && (op1 == "-ne" || op1 == "!=")) && lhs1 == lhs2 && rhs1 /= rhs2 && not (any isGlob [rhs1,rhs2]) = warn id 2055 $ "You probably wanted " ++ (if typ == SingleBracket then "-a" else "&&") ++ " here." +-- For arithmetic context "or" checkOrNeq _ (TA_Binary id "||" (TA_Binary _ "!=" word1 _) (TA_Binary _ "!=" word2 _)) | word1 == word2 = - warn id 2056 "You probably wanted && here." + warn id 2056 "You probably wanted && here, otherwise it's always true." + +-- For command level "or": [ x != y ] || [ x != z ] +checkOrNeq _ (T_OrIf id lhs rhs) = potentially $ do + (lhs1, op1, rhs1) <- getExpr lhs + (lhs2, op2, rhs2) <- getExpr rhs + guard $ op1 == op2 && op1 `elem` ["-ne", "!="] + guard $ lhs1 == lhs2 && rhs1 /= rhs2 + guard . not $ any isGlob [rhs1, rhs2] + return $ warn id 2252 "You probably wanted && here, otherwise it's always true." + where + getExpr x = + case x of + T_OrIf _ lhs _ -> getExpr lhs -- Fetches x and y in `T_OrIf x (T_OrIf y z)` + T_Pipeline _ _ [x] -> getExpr x + T_Redirecting _ _ c -> getExpr c + T_Condition _ _ c -> getExpr c + TC_Binary _ _ op lhs rhs -> return (lhs, op, rhs) + _ -> fail "" + checkOrNeq _ _ = return () From f4be53eb199fab001bd7460026e971103f7b8f94 Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sun, 2 Jun 2019 10:28:20 -0700 Subject: [PATCH 03/35] Warn about [ -v var ] for POSIX sh --- src/ShellCheck/Checks/ShellSupport.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/ShellCheck/Checks/ShellSupport.hs b/src/ShellCheck/Checks/ShellSupport.hs index 5ca44a1..4a86891 100644 --- a/src/ShellCheck/Checks/ShellSupport.hs +++ b/src/ShellCheck/Checks/ShellSupport.hs @@ -174,6 +174,7 @@ prop_checkBashisms90 = verifyNot checkBashisms "#!/bin/sh\nset -o \"$opt\"" prop_checkBashisms91 = verify checkBashisms "#!/bin/sh\nwait -n" prop_checkBashisms92 = verify checkBashisms "#!/bin/sh\necho $((16#FF))" prop_checkBashisms93 = verify checkBashisms "#!/bin/sh\necho $(( 10#$(date +%m) ))" +prop_checkBashisms94 = verify checkBashisms "#!/bin/sh\n[ -v var ]" checkBashisms = ForShell [Sh, Dash] $ \t -> do params <- ask kludge params t @@ -208,6 +209,8 @@ checkBashisms = ForShell [Sh, Dash] $ \t -> do warnMsg id "== in place of = is" bashism (TC_Binary id SingleBracket "=~" _ _) = warnMsg id "=~ regex matching is" + bashism (TC_Unary id SingleBracket "-v" _) = + warnMsg id "unary -v (in place of [ -n \"${var+x}\" ]) is" bashism (TC_Unary id _ "-a" _) = warnMsg id "unary -a in place of -e is" bashism (TA_Unary id op _) From 1297ef46d702daab795449e76f7c7f8e4b08f61d Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sun, 2 Jun 2019 10:28:37 -0700 Subject: [PATCH 04/35] Add JSON1 as a separate format, wrap result in an object --- ShellCheck.cabal | 1 + shellcheck.hs | 5 +++-- src/ShellCheck/Formatter/JSON.hs | 17 +++++------------ 3 files changed, 9 insertions(+), 14 deletions(-) diff --git a/ShellCheck.cabal b/ShellCheck.cabal index 099052e..d54f0b8 100644 --- a/ShellCheck.cabal +++ b/ShellCheck.cabal @@ -80,6 +80,7 @@ library ShellCheck.Formatter.CheckStyle ShellCheck.Formatter.GCC ShellCheck.Formatter.JSON + ShellCheck.Formatter.JSON1 ShellCheck.Formatter.TTY ShellCheck.Formatter.Quiet ShellCheck.Interface diff --git a/shellcheck.hs b/shellcheck.hs index 02ed88a..351e1c2 100644 --- a/shellcheck.hs +++ b/shellcheck.hs @@ -27,6 +27,7 @@ import qualified ShellCheck.Formatter.CheckStyle import ShellCheck.Formatter.Format import qualified ShellCheck.Formatter.GCC import qualified ShellCheck.Formatter.JSON +import qualified ShellCheck.Formatter.JSON1 import qualified ShellCheck.Formatter.TTY import qualified ShellCheck.Formatter.Quiet @@ -141,8 +142,8 @@ formats :: FormatterOptions -> Map.Map String (IO Formatter) formats options = Map.fromList [ ("checkstyle", ShellCheck.Formatter.CheckStyle.format), ("gcc", ShellCheck.Formatter.GCC.format), - ("json", ShellCheck.Formatter.JSON.format False), -- JSON with 8-char tabs - ("json1", ShellCheck.Formatter.JSON.format True), -- JSON with 1-char tabs + ("json", ShellCheck.Formatter.JSON.format), + ("json1", ShellCheck.Formatter.JSON1.format), ("tty", ShellCheck.Formatter.TTY.format options), ("quiet", ShellCheck.Formatter.Quiet.format options) ] diff --git a/src/ShellCheck/Formatter/JSON.hs b/src/ShellCheck/Formatter/JSON.hs index c3f3219..7c26421 100644 --- a/src/ShellCheck/Formatter/JSON.hs +++ b/src/ShellCheck/Formatter/JSON.hs @@ -30,12 +30,12 @@ import GHC.Exts import System.IO import qualified Data.ByteString.Lazy.Char8 as BL -format :: Bool -> IO Formatter -format removeTabs = do +format :: IO Formatter +format = do ref <- newIORef [] return Formatter { header = return (), - onResult = collectResult removeTabs ref, + onResult = collectResult ref, onFailure = outputError, footer = finish ref } @@ -98,19 +98,12 @@ instance ToJSON Fix where outputError file msg = hPutStrLn stderr $ file ++ ": " ++ msg -collectResult removeTabs ref cr sys = mapM_ f groups +collectResult ref cr sys = mapM_ f groups where comments = crComments cr groups = groupWith sourceFile comments f :: [PositionedComment] -> IO () - f group = do - let filename = sourceFile (head group) - result <- siReadFile sys filename - let contents = either (const "") id result - let comments' = if removeTabs - then makeNonVirtual comments contents - else comments - modifyIORef ref (\x -> comments' ++ x) + f group = modifyIORef ref (\x -> comments ++ x) finish ref = do list <- readIORef ref From 9f0ef5983afddabc2bf5c5f62b11471e651224fc Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sun, 2 Jun 2019 10:25:22 -0700 Subject: [PATCH 05/35] Optionally check for unassigned uppercase variables --- CHANGELOG.md | 1 + shellcheck.1.md | 3 +++ src/ShellCheck/Analytics.hs | 17 +++++++++++++++-- 3 files changed, 19 insertions(+), 2 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index 93f83c8..0e812ac 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -8,6 +8,7 @@ - Source paths: Use `-P dir1:dir2` or a `source-path=dir1` directive to specify search paths for sourced files. - json1 format like --format=json but treats tabs as single characters +- SC2154: Also warn about unassigned uppercase variables (optional) - SC2252: Warn about `[ $a != x ] || [ $a != y ]`, similar to SC2055 - SC2251: Inform about ineffectual ! in front of commands - SC2250: Warn about variable references without braces (optional) diff --git a/shellcheck.1.md b/shellcheck.1.md index 3b3498a..18abb58 100644 --- a/shellcheck.1.md +++ b/shellcheck.1.md @@ -251,6 +251,9 @@ Here is an example `.shellcheckrc`: # Turn on warnings for unquoted variables with safe values enable=quote-safe-variables + # Turn on warnings for unassigned uppercase variables + enable=check-unassigned-uppercase + # Allow using `which` since it gives full paths and is common enough disable=SC2230 diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index 3ee454c..cd1281c 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -231,6 +231,13 @@ optionalTreeChecks = [ cdPositive = "var=hello; echo $var", cdNegative = "var=hello; echo ${var}" }, nodeChecksToTreeCheck [checkVariableBraces]) + + ,(newCheckDescription { + cdName = "check-unassigned-uppercase", + cdDescription = "Warn when uppercase variables are unassigned", + cdPositive = "echo $VAR", + cdNegative = "VAR=hello; echo $VAR" + }, checkUnassignedReferences' True) ] optionalCheckMap :: Map.Map String (Parameters -> Token -> [TokenComment]) @@ -2131,7 +2138,10 @@ prop_checkUnassignedReferences34= verifyNotTree checkUnassignedReferences "decla prop_checkUnassignedReferences35= verifyNotTree checkUnassignedReferences "echo ${arr[foo-bar]:?fail}" prop_checkUnassignedReferences36= verifyNotTree checkUnassignedReferences "read -a foo -r <<<\"foo bar\"; echo \"$foo\"" prop_checkUnassignedReferences37= verifyNotTree checkUnassignedReferences "var=howdy; printf -v 'array[0]' %s \"$var\"; printf %s \"${array[0]}\";" -checkUnassignedReferences params t = warnings +prop_checkUnassignedReferences38= verifyTree (checkUnassignedReferences' True) "echo $VAR" + +checkUnassignedReferences = checkUnassignedReferences' False +checkUnassignedReferences' includeGlobals params t = warnings where (readMap, writeMap) = execState (mapM tally $ variableFlow params) (Map.empty, Map.empty) defaultAssigned = Map.fromList $ map (\a -> (a, ())) $ filter (not . null) internalVariables @@ -2176,8 +2186,11 @@ checkUnassignedReferences params t = warnings return $ " (did you mean '" ++ match ++ "'?)" warningFor var place = do + guard $ isVariableName var guard . not $ isInArray var place || isGuarded place - (if isLocal var then warningForLocals else warningForGlobals) var place + (if includeGlobals || isLocal var + then warningForLocals + else warningForGlobals) var place warnings = execWriter . sequence $ mapMaybe (uncurry warningFor) unassigned From 61d2112e71e7f02f44a44fd82de54b9b4b455990 Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sun, 2 Jun 2019 13:00:38 -0700 Subject: [PATCH 06/35] Add missing JSON1.hs --- src/ShellCheck/Formatter/JSON1.hs | 127 ++++++++++++++++++++++++++++++ 1 file changed, 127 insertions(+) create mode 100644 src/ShellCheck/Formatter/JSON1.hs diff --git a/src/ShellCheck/Formatter/JSON1.hs b/src/ShellCheck/Formatter/JSON1.hs new file mode 100644 index 0000000..7335d8c --- /dev/null +++ b/src/ShellCheck/Formatter/JSON1.hs @@ -0,0 +1,127 @@ +{-# LANGUAGE OverloadedStrings #-} +{- + Copyright 2012-2019 Vidar Holen + + This file is part of ShellCheck. + https://www.shellcheck.net + + ShellCheck is free software: you can redistribute it and/or modify + it under the terms of the GNU General Public License as published by + the Free Software Foundation, either version 3 of the License, or + (at your option) any later version. + + ShellCheck is distributed in the hope that it will be useful, + but WITHOUT ANY WARRANTY; without even the implied warranty of + MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + GNU General Public License for more details. + + You should have received a copy of the GNU General Public License + along with this program. If not, see . +-} +module ShellCheck.Formatter.JSON1 (format) where + +import ShellCheck.Interface +import ShellCheck.Formatter.Format + +import Data.Aeson +import Data.IORef +import Data.Monoid +import GHC.Exts +import System.IO +import qualified Data.ByteString.Lazy.Char8 as BL + +format :: IO Formatter +format = do + ref <- newIORef [] + return Formatter { + header = return (), + onResult = collectResult ref, + onFailure = outputError, + footer = finish ref + } + +data Json1Output = Json1Output { + comments :: [PositionedComment] + } + +instance ToJSON Json1Output where + toJSON result = object [ + "comments" .= comments result + ] + toEncoding result = pairs ( + "comments" .= comments result + ) + +instance ToJSON Replacement where + toJSON replacement = + let start = repStartPos replacement + end = repEndPos replacement + str = repString replacement in + object [ + "precedence" .= repPrecedence replacement, + "insertionPoint" .= + case repInsertionPoint replacement of + InsertBefore -> "beforeStart" :: String + InsertAfter -> "afterEnd", + "line" .= posLine start, + "column" .= posColumn start, + "endLine" .= posLine end, + "endColumn" .= posColumn end, + "replacement" .= str + ] + +instance ToJSON PositionedComment where + toJSON comment = + let start = pcStartPos comment + end = pcEndPos comment + c = pcComment comment in + object [ + "file" .= posFile start, + "line" .= posLine start, + "endLine" .= posLine end, + "column" .= posColumn start, + "endColumn" .= posColumn end, + "level" .= severityText comment, + "code" .= cCode c, + "message" .= cMessage c, + "fix" .= pcFix comment + ] + + toEncoding comment = + let start = pcStartPos comment + end = pcEndPos comment + c = pcComment comment in + pairs ( + "file" .= posFile start + <> "line" .= posLine start + <> "endLine" .= posLine end + <> "column" .= posColumn start + <> "endColumn" .= posColumn end + <> "level" .= severityText comment + <> "code" .= cCode c + <> "message" .= cMessage c + <> "fix" .= pcFix comment + ) + +instance ToJSON Fix where + toJSON fix = object [ + "replacements" .= fixReplacements fix + ] + +outputError file msg = hPutStrLn stderr $ file ++ ": " ++ msg + +collectResult ref cr sys = mapM_ f groups + where + comments = crComments cr + groups = groupWith sourceFile comments + f :: [PositionedComment] -> IO () + f group = do + let filename = sourceFile (head group) + result <- siReadFile sys filename + let contents = either (const "") id result + let comments' = makeNonVirtual comments contents + modifyIORef ref (\x -> comments' ++ x) + +finish ref = do + list <- readIORef ref + BL.putStrLn $ encode $ Json1Output { comments = list } From c6dcb4127a61c4ca831907b889bb2242777b1118 Mon Sep 17 00:00:00 2001 From: Oleg Andreyev Date: Sun, 9 Jun 2019 17:00:51 +0300 Subject: [PATCH 07/35] #1607 fixing brew command --- README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index 6b789cd..3baca68 100644 --- a/README.md +++ b/README.md @@ -258,7 +258,7 @@ ShellCheck is built and packaged using Cabal. Install the package `cabal-install On MacOS (OS X), you can do a fast install of Cabal using brew, which takes a couple of minutes instead of more than 30 minutes if you try to compile it from source. brew install cask - brew cask install haskell-platform + brew cask install haskell-for-mac cabal install cabal-install On MacPorts, the package is instead called `hs-cabal-install`, while native Windows users should install the latest version of the Haskell platform from From 200aabb63c61d530c8ae8283832e92f745568ec4 Mon Sep 17 00:00:00 2001 From: Daniel Hahler Date: Tue, 18 Jun 2019 23:18:26 +0200 Subject: [PATCH 08/35] Add .dockerignore This explicitly defines included/copied files, to reduce the context being sent to the Docker daemon initially. --- .dockerignore | 6 ++++++ 1 file changed, 6 insertions(+) create mode 100644 .dockerignore diff --git a/.dockerignore b/.dockerignore new file mode 100644 index 0000000..39d8893 --- /dev/null +++ b/.dockerignore @@ -0,0 +1,6 @@ +* +!LICENSE +!Setup.hs +!ShellCheck.cabal +!shellcheck.hs +!src From 7e77bfae491ba577aa2b859b39ea9a64cada686d Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Tue, 11 Jun 2019 18:39:09 -0700 Subject: [PATCH 09/35] Improve message for SC2055 --- 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 1b28c6f..c2bcc78 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -1365,7 +1365,7 @@ prop_checkOrNeq8 = verifyNot checkOrNeq "[[ $a != x || $a != x ]]" -- For test-level "or": [ x != y -o x != z ] checkOrNeq _ (TC_Or id typ op (TC_Binary _ _ op1 lhs1 rhs1 ) (TC_Binary _ _ op2 lhs2 rhs2)) | (op1 == op2 && (op1 == "-ne" || op1 == "!=")) && lhs1 == lhs2 && rhs1 /= rhs2 && not (any isGlob [rhs1,rhs2]) = - warn id 2055 $ "You probably wanted " ++ (if typ == SingleBracket then "-a" else "&&") ++ " here." + warn id 2055 $ "You probably wanted " ++ (if typ == SingleBracket then "-a" else "&&") ++ " here, otherwise it's always true." -- For arithmetic context "or" checkOrNeq _ (TA_Binary id "||" (TA_Binary _ "!=" word1 _) (TA_Binary _ "!=" word2 _)) From 5242e384a11ce6855a4be8b23944634ee60fccfd Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sun, 23 Jun 2019 13:47:35 -0700 Subject: [PATCH 10/35] Fix error spans for shebang warnings (fixes #1620) --- src/ShellCheck/AST.hs | 2 +- src/ShellCheck/Analytics.hs | 4 ++-- src/ShellCheck/AnalyzerLib.hs | 4 ++-- src/ShellCheck/Parser.hs | 24 ++++++++++++++---------- 4 files changed, 19 insertions(+), 15 deletions(-) diff --git a/src/ShellCheck/AST.hs b/src/ShellCheck/AST.hs index eb236ca..d8faec6 100644 --- a/src/ShellCheck/AST.hs +++ b/src/ShellCheck/AST.hs @@ -121,7 +121,7 @@ data Token = | T_Rbrace Id | T_Redirecting Id [Token] Token | T_Rparen Id - | T_Script Id String [Token] + | T_Script Id Token [Token] -- Shebang T_Literal, followed by script. | T_Select Id | T_SelectIn Id String [Token] [Token] | T_Semi Id diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index c2bcc78..e1523fd 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -534,7 +534,7 @@ indexOfSublists sub = f 0 prop_checkShebangParameters1 = verifyTree checkShebangParameters "#!/usr/bin/env bash -x\necho cow" prop_checkShebangParameters2 = verifyNotTree checkShebangParameters "#! /bin/sh -l " checkShebangParameters p (T_Annotation _ _ t) = checkShebangParameters p t -checkShebangParameters _ (T_Script id sb _) = +checkShebangParameters _ (T_Script _ (T_Literal id sb) _) = [makeComment ErrorC id 2096 "On most OS, shebangs can only specify a single parameter." | length (words sb) > 2] prop_checkShebang1 = verifyNotTree checkShebang "#!/usr/bin/env bash -x\necho cow" @@ -554,7 +554,7 @@ checkShebang params (T_Annotation _ list t) = where isOverride (ShellOverride _) = True isOverride _ = False -checkShebang params (T_Script id sb _) = execWriter $ do +checkShebang params (T_Script _ (T_Literal id sb) _) = execWriter $ do unless (shellTypeSpecified params) $ do when (sb == "") $ err id 2148 "Tips depend on target shell and yours is unknown. Add a shebang." diff --git a/src/ShellCheck/AnalyzerLib.hs b/src/ShellCheck/AnalyzerLib.hs index d99ea98..388f871 100644 --- a/src/ShellCheck/AnalyzerLib.hs +++ b/src/ShellCheck/AnalyzerLib.hs @@ -206,7 +206,7 @@ containsSetE root = isNothing $ doAnalysis (guard . not . isSetE) root where isSetE t = case t of - T_Script _ str _ -> str `matches` re + T_Script _ (T_Literal _ str) _ -> str `matches` re T_SimpleCommand {} -> t `isUnqualifiedCommand` "set" && ("errexit" `elem` oversimplify t || @@ -252,7 +252,7 @@ determineShell fallbackShell t = fromMaybe Bash $ do getCandidates (T_Annotation _ annotations s) = map forAnnotation annotations ++ [Just $ fromShebang s] - fromShebang (T_Script _ s t) = executableFromShebang s + fromShebang (T_Script _ (T_Literal _ s) _) = executableFromShebang s -- Given a string like "/bin/bash" or "/usr/bin/env dash", -- return the shell basename like "bash" or "dash" diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index c09d64c..cd4bc8f 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -2790,10 +2790,11 @@ readAssignmentWordExt lenient = try $ do string "=" >> return Assign ] - readEmptyLiteral = do - start <- startSpan - id <- endSpan start - return $ T_Literal id "" + +readEmptyLiteral = do + start <- startSpan + id <- endSpan start + return $ T_Literal id "" readArrayIndex = do start <- startSpan @@ -2941,12 +2942,14 @@ prop_readShebang5 = isWarning readShebang "\n#!/bin/sh" prop_readShebang6 = isWarning readShebang " # Copyright \n!#/bin/bash" prop_readShebang7 = isNotOk readShebang "# Copyright \nfoo\n#!/bin/bash" readShebang = do + start <- startSpan anyShebang <|> try readMissingBang <|> withHeader many linewhitespace str <- many $ noneOf "\r\n" + id <- endSpan start optional carriageReturn optional linefeed - return str + return $ T_Literal id str where anyShebang = choice $ map try [ readCorrect, @@ -3077,7 +3080,8 @@ readScriptFile sourced = do readUtf8Bom parseProblem ErrorC 1082 "This file has a UTF-8 BOM. Remove it with: LC_CTYPE=C sed '1s/^...//' < yourscript ." - sb <- option "" readShebang + shebang <- readShebang <|> readEmptyLiteral + let (T_Literal _ shebangString) = shebang allspacing annotationStart <- startSpan fileAnnotations <- readAnnotations @@ -3094,19 +3098,19 @@ readScriptFile sourced = do let ignoreShebang = shellAnnotationSpecified || shellFlagSpecified unless ignoreShebang $ - verifyShebang pos (getShell sb) - if ignoreShebang || isValidShell (getShell sb) /= Just False + verifyShebang pos (getShell shebangString) + if ignoreShebang || isValidShell (getShell shebangString) /= Just False then do commands <- withAnnotations annotations readCompoundListOrEmpty id <- endSpan start verifyEof let script = T_Annotation annotationId annotations $ - T_Script id sb commands + T_Script id shebang commands reparseIndices script else do many anyChar id <- endSpan start - return $ T_Script id sb [] + return $ T_Script id shebang [] where basename s = reverse . takeWhile (/= '/') . reverse $ s From e099625e7d09f26146d0197d6ff466dc8cd89b39 Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sun, 23 Jun 2019 14:26:18 -0700 Subject: [PATCH 11/35] Remove unused ioref --- src/ShellCheck/Formatter/Quiet.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/ShellCheck/Formatter/Quiet.hs b/src/ShellCheck/Formatter/Quiet.hs index 9ad8b97..b7e0ee9 100644 --- a/src/ShellCheck/Formatter/Quiet.hs +++ b/src/ShellCheck/Formatter/Quiet.hs @@ -27,8 +27,7 @@ import Data.IORef import System.Exit format :: FormatterOptions -> IO Formatter -format options = do - topErrorRef <- newIORef [] +format options = return Formatter { header = return (), footer = return (), From b8b4a11348bb77514c77679c2a58a721fc89f31e Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sun, 23 Jun 2019 19:18:45 -0700 Subject: [PATCH 12/35] Update JSON1 docs in man page --- shellcheck.1.md | 28 +++++++++++++++------------- 1 file changed, 15 insertions(+), 13 deletions(-) diff --git a/shellcheck.1.md b/shellcheck.1.md index 18abb58..c9963bd 100644 --- a/shellcheck.1.md +++ b/shellcheck.1.md @@ -158,22 +158,24 @@ not warn at all, as `ksh` supports decimals in arithmetic contexts. applications. ShellCheck's json is compact and contains only the bare minimum. Tabs are counted as 1 character. - [ - { - "file": "filename", - "line": lineNumber, - "column": columnNumber, - "level": "severitylevel", - "code": errorCode, - "message": "warning message" - }, - ... - ] + { + comments: [ + { + "file": "filename", + "line": lineNumber, + "column": columnNumber, + "level": "severitylevel", + "code": errorCode, + "message": "warning message" + }, + ... + ] + } **json** -: This is a legacy version of the **json1** format, with a tab stop - of 8 instead of 1. +: This is a legacy version of the **json1** format. It's a raw array of + comments, and all offsets have a tab stop of 8. **quiet** From b1aeee564c6852147081dda08b1030e864b1711f Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sun, 23 Jun 2019 19:05:12 -0700 Subject: [PATCH 13/35] Add a Diff output format --- CHANGELOG.md | 1 + ShellCheck.cabal | 4 + shellcheck.1.md | 17 +++ shellcheck.hs | 2 + src/ShellCheck/Formatter/Diff.hs | 222 +++++++++++++++++++++++++++++ src/ShellCheck/Formatter/Format.hs | 17 ++- src/ShellCheck/Formatter/TTY.hs | 8 +- test/shellcheck.hs | 2 + 8 files changed, 265 insertions(+), 8 deletions(-) create mode 100644 src/ShellCheck/Formatter/Diff.hs diff --git a/CHANGELOG.md b/CHANGELOG.md index 0e812ac..e074894 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -1,6 +1,7 @@ ## Since previous release ### Added - Preliminary support for fix suggestions +- New `-f diff` unified diff format for auto-fixes - Files containing Bats tests can now be checked - Directory wide directives can now be placed in a `.shellcheckrc` - Optional checks: Use `--list-optional` to show a list of tests, diff --git a/ShellCheck.cabal b/ShellCheck.cabal index d54f0b8..781a082 100644 --- a/ShellCheck.cabal +++ b/ShellCheck.cabal @@ -57,6 +57,7 @@ library bytestring, containers >= 0.5, deepseq >= 1.4.0.0, + Diff >= 0.2.0, directory >= 1.2.3.0, mtl >= 2.2.1, filepath, @@ -78,6 +79,7 @@ library ShellCheck.Fixer ShellCheck.Formatter.Format ShellCheck.Formatter.CheckStyle + ShellCheck.Formatter.Diff ShellCheck.Formatter.GCC ShellCheck.Formatter.JSON ShellCheck.Formatter.JSON1 @@ -100,6 +102,7 @@ executable shellcheck bytestring, containers, deepseq >= 1.4.0.0, + Diff >= 0.2.0, directory >= 1.2.3.0, mtl >= 2.2.1, filepath, @@ -118,6 +121,7 @@ test-suite test-shellcheck bytestring, containers, deepseq >= 1.4.0.0, + Diff >= 0.2.0, directory >= 1.2.3.0, mtl >= 2.2.1, filepath, diff --git a/shellcheck.1.md b/shellcheck.1.md index c9963bd..77fa79a 100644 --- a/shellcheck.1.md +++ b/shellcheck.1.md @@ -152,6 +152,23 @@ not warn at all, as `ksh` supports decimals in arithmetic contexts. ... +**diff** + +: Auto-fixes in unified diff format. Can be piped to `git apply` or `patch -p1` + to automatically apply fixes. + + --- a/test.sh + +++ b/test.sh + @@ -2,6 +2,6 @@ + ## Example of a broken script. + for f in $(ls *.m3u) + do + - grep -qi hq.*mp3 $f \ + + grep -qi hq.*mp3 "$f" \ + && echo -e 'Playlist $f contains a HQ file in mp3 format' + done + + **json1** : Json is a popular serialization format that is more suitable for web diff --git a/shellcheck.hs b/shellcheck.hs index 351e1c2..4ba8b70 100644 --- a/shellcheck.hs +++ b/shellcheck.hs @@ -25,6 +25,7 @@ import ShellCheck.Regex import qualified ShellCheck.Formatter.CheckStyle import ShellCheck.Formatter.Format +import qualified ShellCheck.Formatter.Diff import qualified ShellCheck.Formatter.GCC import qualified ShellCheck.Formatter.JSON import qualified ShellCheck.Formatter.JSON1 @@ -141,6 +142,7 @@ parseArguments argv = formats :: FormatterOptions -> Map.Map String (IO Formatter) formats options = Map.fromList [ ("checkstyle", ShellCheck.Formatter.CheckStyle.format), + ("diff", ShellCheck.Formatter.Diff.format options), ("gcc", ShellCheck.Formatter.GCC.format), ("json", ShellCheck.Formatter.JSON.format), ("json1", ShellCheck.Formatter.JSON1.format), diff --git a/src/ShellCheck/Formatter/Diff.hs b/src/ShellCheck/Formatter/Diff.hs new file mode 100644 index 0000000..f89a756 --- /dev/null +++ b/src/ShellCheck/Formatter/Diff.hs @@ -0,0 +1,222 @@ +{- + Copyright 2019 Vidar 'koala_man' Holen + + This file is part of ShellCheck. + https://www.shellcheck.net + + ShellCheck is free software: you can redistribute it and/or modify + it under the terms of the GNU General Public License as published by + the Free Software Foundation, either version 3 of the License, or + (at your option) any later version. + + ShellCheck is distributed in the hope that it will be useful, + but WITHOUT ANY WARRANTY; without even the implied warranty of + MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + GNU General Public License for more details. + + You should have received a copy of the GNU General Public License + along with this program. If not, see . +-} +{-# LANGUAGE TemplateHaskell #-} +module ShellCheck.Formatter.Diff (format, ShellCheck.Formatter.Diff.runTests) where + +import ShellCheck.Interface +import ShellCheck.Fixer +import ShellCheck.Formatter.Format + +import Control.Monad +import Data.Algorithm.Diff +import Data.Array +import Data.IORef +import Data.List +import Data.Maybe +import qualified Data.Map as M +import GHC.Exts (sortWith) +import System.IO +import System.FilePath + +import Test.QuickCheck + +import Debug.Trace +ltt x = trace (show x) x + +format :: FormatterOptions -> IO Formatter +format options = do + didOutput <- newIORef False + shouldColor <- shouldOutputColor (foColorOption options) + let color = if shouldColor then colorize else nocolor + return Formatter { + header = return (), + footer = checkFooter didOutput color, + onFailure = reportFailure color, + onResult = reportResult didOutput color + } + + +contextSize = 3 +red = 31 +green = 32 +yellow = 33 +cyan = 36 +bold = 1 + +nocolor n = id +colorize n s = (ansi n) ++ s ++ (ansi 0) +ansi n = "\x1B[" ++ show n ++ "m" + +printErr :: ColorFunc -> String -> IO () +printErr color = hPutStrLn stderr . color bold . color red +reportFailure color file msg = printErr color $ file ++ ": " ++ msg + +checkFooter didOutput color = do + output <- readIORef didOutput + unless output $ + printErr color "Issues were detected, but none were auto-fixable. Use another format to see them." + +type ColorFunc = (Int -> String -> String) +data DiffDoc a = DiffDoc String [DiffRegion a] +data DiffRegion a = DiffRegion (Int, Int) (Int, Int) [Diff a] + +reportResult :: (IORef Bool) -> ColorFunc -> CheckResult -> SystemInterface IO -> IO () +reportResult didOutput color result sys = do + let comments = crComments result + let suggestedFixes = mapMaybe pcFix comments + let fixmap = buildFixMap suggestedFixes + mapM_ output $ M.toList fixmap + where + output (name, fix) = do + file <- (siReadFile sys) name + case file of + Right contents -> do + putStrLn $ formatDoc color $ makeDiff name contents fix + writeIORef didOutput True + Left msg -> reportFailure color name msg + +makeDiff :: String -> String -> Fix -> DiffDoc String +makeDiff name contents fix = + DiffDoc name $ findRegions . groupDiff $ computeDiff contents fix + +computeDiff :: String -> Fix -> [Diff String] +computeDiff contents fix = + let old = lines contents + array = listArray (1, fromIntegral $ (length old)) old + new = applyFix fix array + in getDiff old new + +-- Group changes into hunks +groupDiff :: [Diff a] -> [(Bool, [Diff a])] +groupDiff = filter (\(_, l) -> not (null l)) . hunt [] + where + -- Churn through 'Both's until we find a difference + hunt current [] = [(False, reverse current)] + hunt current (x@Both {}:rest) = hunt (x:current) rest + hunt current list = + let (context, previous) = splitAt contextSize current + in (False, reverse previous) : gather context 0 list + + -- Pick out differences until we find a run of Both's + gather current n [] = + let (extras, patch) = splitAt (max 0 $ n - contextSize) current + in [(True, reverse patch), (False, reverse extras)] + + gather current n list@(Both {}:_) | n == contextSize*2 = + let (context, previous) = splitAt contextSize current + in (True, reverse previous) : hunt context list + + gather current n (x@Both {}:rest) = gather (x:current) (n+1) rest + gather current n (x:rest) = gather (x:current) 0 rest + +-- Get line numbers for hunks +findRegions :: [(Bool, [Diff String])] -> [DiffRegion String] +findRegions = find' 1 1 + where + find' _ _ [] = [] + find' left right ((output, run):rest) = + let (dl, dr) = countDelta run + remainder = find' (left+dl) (right+dr) rest + in + if output + then DiffRegion (left, dl) (right, dr) run : remainder + else remainder + +-- Get left/right line counts for a hunk +countDelta :: [Diff a] -> (Int, Int) +countDelta = count' 0 0 + where + count' left right [] = (left, right) + count' left right (x:rest) = + case x of + Both {} -> count' (left+1) (right+1) rest + First {} -> count' (left+1) right rest + Second {} -> count' left (right+1) rest + +formatRegion :: ColorFunc -> DiffRegion String -> String +formatRegion color (DiffRegion left right diffs) = + let header = color cyan ("@@ -" ++ (tup left) ++ " +" ++ (tup right) ++" @@") + in + unlines $ header : map format diffs + where + tup (a,b) = (show a) ++ "," ++ (show b) + format (Both x _) = ' ':x + format (First x) = color red $ '-':x + format (Second x) = color green $ '+':x + +formatDoc color (DiffDoc name regions) = + (color bold $ "--- " ++ ("a" name)) ++ "\n" ++ + (color bold $ "+++ " ++ ("b" name)) ++ "\n" ++ + concatMap (formatRegion color) regions + +-- Create a Map from filename to Fix +buildFixMap :: [Fix] -> M.Map String Fix +buildFixMap fixes = perFile + where + splitFixes = concatMap splitFixByFile fixes + perFile = groupByMap (posFile . repStartPos . head . fixReplacements) splitFixes + +-- There are currently no multi-file fixes, but let's handle it anyways +splitFixByFile :: Fix -> [Fix] +splitFixByFile fix = map makeFix $ groupBy sameFile (fixReplacements fix) + where + sameFile rep1 rep2 = (posFile $ repStartPos rep1) == (posFile $ repStartPos rep2) + makeFix reps = newFix { fixReplacements = reps } + +groupByMap :: (Ord k, Monoid v) => (v -> k) -> [v] -> M.Map k v +groupByMap f = M.fromListWith (<>) . map (\x -> (f x, x)) + +-- For building unit tests +b n = Both n n +l = First +r = Second + +prop_identifiesProperContext = groupDiff [b 1, b 2, b 3, b 4, l 5, b 6, b 7, b 8, b 9] == + [(False, [b 1]), -- Omitted + (True, [b 2, b 3, b 4, l 5, b 6, b 7, b 8]), -- A change with three lines of context + (False, [b 9])] -- Omitted + +prop_includesContextFromStartIfNecessary = groupDiff [b 4, l 5, b 6, b 7, b 8, b 9] == + [ -- Nothing omitted + (True, [b 4, l 5, b 6, b 7, b 8]), -- A change with three lines of context + (False, [b 9])] -- Omitted + +prop_includesContextUntilEndIfNecessary = groupDiff [b 4, l 5] == + [ -- Nothing omitted + (True, [b 4, l 5]) + ] -- Nothing Omitted + +prop_splitsIntoMultipleHunks = groupDiff [l 1, b 1, b 2, b 3, b 4, b 5, b 6, b 7, r 8] == + [ -- Nothing omitted + (True, [l 1, b 1, b 2, b 3]), + (False, [b 4]), + (True, [b 5, b 6, b 7, r 8]) + ] -- Nothing Omitted + +prop_splitsIntoMultipleHunksUnlessTouching = groupDiff [l 1, b 1, b 2, b 3, b 4, b 5, b 6, r 7] == + [ + (True, [l 1, b 1, b 2, b 3, b 4, b 5, b 6, r 7]) + ] + +prop_countDeltasWorks = countDelta [b 1, l 2, r 3, r 4, b 5] == (3,4) +prop_countDeltasWorks2 = countDelta [] == (0,0) + +return [] +runTests = $quickCheckAll diff --git a/src/ShellCheck/Formatter/Format.hs b/src/ShellCheck/Formatter/Format.hs index 11dfd17..cb7dfe6 100644 --- a/src/ShellCheck/Formatter/Format.hs +++ b/src/ShellCheck/Formatter/Format.hs @@ -22,8 +22,12 @@ module ShellCheck.Formatter.Format where import ShellCheck.Data import ShellCheck.Interface import ShellCheck.Fixer + import Control.Monad import Data.Array +import Data.List +import System.IO +import System.Info -- A formatter that carries along an arbitrary piece of data data Formatter = Formatter { @@ -59,6 +63,17 @@ makeNonVirtual comments contents = fixReplacements = map (\r -> removeTabStops r arr) (fixReplacements f) } fix c = (removeTabStops c arr) { - pcFix = liftM untabbedFix (pcFix c) + pcFix = fmap untabbedFix (pcFix c) } + +shouldOutputColor :: ColorOption -> IO Bool +shouldOutputColor colorOption = do + term <- hIsTerminalDevice stdout + let windows = "mingw" `isPrefixOf` os + let isUsableTty = term && not windows + let useColor = case colorOption of + ColorAlways -> True + ColorNever -> False + ColorAuto -> isUsableTty + return useColor diff --git a/src/ShellCheck/Formatter/TTY.hs b/src/ShellCheck/Formatter/TTY.hs index 845feeb..4dabf45 100644 --- a/src/ShellCheck/Formatter/TTY.hs +++ b/src/ShellCheck/Formatter/TTY.hs @@ -188,13 +188,7 @@ code num = "SC" ++ show num getColorFunc :: ColorOption -> IO ColorFunc getColorFunc colorOption = do - term <- hIsTerminalDevice stdout - let windows = "mingw" `isPrefixOf` os - let isUsableTty = term && not windows - let useColor = case colorOption of - ColorAlways -> True - ColorNever -> False - ColorAuto -> isUsableTty + useColor <- shouldOutputColor colorOption return $ if useColor then colorComment else const id where colorComment level comment = diff --git a/test/shellcheck.hs b/test/shellcheck.hs index 8f858d6..d55b140 100644 --- a/test/shellcheck.hs +++ b/test/shellcheck.hs @@ -8,6 +8,7 @@ import qualified ShellCheck.Checker import qualified ShellCheck.Checks.Commands import qualified ShellCheck.Checks.ShellSupport import qualified ShellCheck.Fixer +import qualified ShellCheck.Formatter.Diff import qualified ShellCheck.Parser main = do @@ -19,6 +20,7 @@ main = do ,ShellCheck.Checks.Commands.runTests ,ShellCheck.Checks.ShellSupport.runTests ,ShellCheck.Fixer.runTests + ,ShellCheck.Formatter.Diff.runTests ,ShellCheck.Parser.runTests ] if and results From c5aa171a5f9eefe4f6280112373e0a2f178e7af8 Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Mon, 24 Jun 2019 09:02:35 -0700 Subject: [PATCH 14/35] Use mappend over <> for compatibility --- src/ShellCheck/Formatter/Diff.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/ShellCheck/Formatter/Diff.hs b/src/ShellCheck/Formatter/Diff.hs index f89a756..58fd2f4 100644 --- a/src/ShellCheck/Formatter/Diff.hs +++ b/src/ShellCheck/Formatter/Diff.hs @@ -29,6 +29,7 @@ import Data.Algorithm.Diff import Data.Array import Data.IORef import Data.List +import qualified Data.Monoid as Monoid import Data.Maybe import qualified Data.Map as M import GHC.Exts (sortWith) @@ -181,7 +182,7 @@ splitFixByFile fix = map makeFix $ groupBy sameFile (fixReplacements fix) makeFix reps = newFix { fixReplacements = reps } groupByMap :: (Ord k, Monoid v) => (v -> k) -> [v] -> M.Map k v -groupByMap f = M.fromListWith (<>) . map (\x -> (f x, x)) +groupByMap f = M.fromListWith Monoid.mappend . map (\x -> (f x, x)) -- For building unit tests b n = Both n n From f6ba500d6b5c80f6ec790d7bcde93418bbf064ff Mon Sep 17 00:00:00 2001 From: Benjamin Gordon Date: Fri, 31 May 2019 10:42:53 -0600 Subject: [PATCH 15/35] Add support for basic shflags semantics The shflags command-line flags library creates variables at runtime with a few well-defined functions. This causes shellcheck to spit out lots of warnings about unassigned variables, as well as miss warnings about unused flag variables. We can address this with two parts: 1. Pretend that the shflags global variables are predefined like other shell variables so that shellcheck doesn't expect users to set them. 2. Treat DEFINE_string, DEFINE_int, etc. as new commands that create variables, similar to the existing read, local, mapfile, etc. Part 1 can theoretically be addresssed without this by following sourced files, but that doesn't help if people are otherwise not following external sources. The new behavior is on by default, similar to automatic bats test behavior. Addresses #1597 --- CHANGELOG.md | 1 + src/ShellCheck/Analytics.hs | 2 ++ src/ShellCheck/AnalyzerLib.hs | 11 +++++++++++ src/ShellCheck/Data.hs | 8 ++++++++ 4 files changed, 22 insertions(+) diff --git a/CHANGELOG.md b/CHANGELOG.md index e074894..28fbb4d 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -9,6 +9,7 @@ - Source paths: Use `-P dir1:dir2` or a `source-path=dir1` directive to specify search paths for sourced files. - json1 format like --format=json but treats tabs as single characters +- Recognize FLAGS variables created by the shflags library. - SC2154: Also warn about unassigned uppercase variables (optional) - SC2252: Warn about `[ $a != x ] || [ $a != y ]`, similar to SC2055 - SC2251: Inform about ineffectual ! in front of commands diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index e1523fd..9377fa0 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -2081,6 +2081,8 @@ prop_checkUnused38= verifyTree checkUnusedAssignments "(( a=42 ))" prop_checkUnused39= verifyNotTree checkUnusedAssignments "declare -x -f foo" prop_checkUnused40= verifyNotTree checkUnusedAssignments "arr=(1 2); num=2; echo \"${arr[@]:num}\"" prop_checkUnused41= verifyNotTree checkUnusedAssignments "@test 'foo' {\ntrue\n}\n" +prop_checkUnused42= verifyNotTree checkUnusedAssignments "DEFINE_string foo '' ''; echo \"${FLAGS_foo}\"" +prop_checkUnused43= verifyTree checkUnusedAssignments "DEFINE_string 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 388f871..508b6ee 100644 --- a/src/ShellCheck/AnalyzerLib.hs +++ b/src/ShellCheck/AnalyzerLib.hs @@ -606,6 +606,11 @@ getModifiedVariableCommand base@(T_SimpleCommand _ _ (T_NormalWord _ (T_Literal "mapfile" -> maybeToList $ getMapfileArray base rest "readarray" -> maybeToList $ getMapfileArray base rest + "DEFINE_boolean" -> maybeToList $ getFlagVariable rest + "DEFINE_float" -> maybeToList $ getFlagVariable rest + "DEFINE_integer" -> maybeToList $ getFlagVariable rest + "DEFINE_string" -> maybeToList $ getFlagVariable rest + _ -> [] where flags = map snd $ getAllFlags base @@ -679,6 +684,12 @@ getModifiedVariableCommand base@(T_SimpleCommand _ _ (T_NormalWord _ (T_Literal map (getLiteralArray . snd) (filter (\(x,_) -> getLiteralString x == Just "-a") (zip (args) (tail args))) + -- get the FLAGS_ variable created by a shflags DEFINE_ call + getFlagVariable (n:v:_) = return (base, n, flagName n, DataString $ SourceFrom [v]) + where + flagName varName@(T_NormalWord _ _) = "FLAGS_" ++ (onlyLiteralString varName) + getFlagVariable _ = fail "Invalid flag definition" + getModifiedVariableCommand _ = [] getIndexReferences s = fromMaybe [] $ do diff --git a/src/ShellCheck/Data.hs b/src/ShellCheck/Data.hs index 2eedeeb..1394c04 100644 --- a/src/ShellCheck/Data.hs +++ b/src/ShellCheck/Data.hs @@ -36,6 +36,11 @@ internalVariables = [ -- Ksh , ".sh.version" + + -- shflags + , "FLAGS_ARGC", "FLAGS_ARGV", "FLAGS_ERROR", "FLAGS_FALSE", "FLAGS_HELP", + "FLAGS_PARENT", "FLAGS_RESERVED", "FLAGS_TRUE", "FLAGS_VERSION", + "flags_error", "flags_return" ] specialVariablesWithoutSpaces = [ @@ -45,6 +50,9 @@ variablesWithoutSpaces = specialVariablesWithoutSpaces ++ [ "BASHPID", "BASH_ARGC", "BASH_LINENO", "BASH_SUBSHELL", "EUID", "LINENO", "OPTIND", "PPID", "RANDOM", "SECONDS", "SHELLOPTS", "SHLVL", "UID", "COLUMNS", "HISTFILESIZE", "HISTSIZE", "LINES" + + -- shflags + , "FLAGS_ERROR", "FLAGS_FALSE", "FLAGS_TRUE" ] specialVariables = specialVariablesWithoutSpaces ++ ["@", "*"] From e95d8dd14e2351fb3acb1c5b70c0e890c4c928b7 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Avi=20=D7=93?= Date: Sat, 29 Jun 2019 03:40:05 -0400 Subject: [PATCH 16/35] Bump stack snapshot --- stack.yaml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/stack.yaml b/stack.yaml index d39cada..6dee632 100644 --- a/stack.yaml +++ b/stack.yaml @@ -2,7 +2,7 @@ # For more information, see: https://docs.haskellstack.org/en/stable/yaml_configuration/ # Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2) -resolver: lts-8.5 +resolver: lts-13.26 # Local packages, usually specified by relative directory name packages: From 3116ed3ae59458148eee77325ce72af7a227d19f Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sun, 30 Jun 2019 16:36:03 -0700 Subject: [PATCH 17/35] Filter warnings by annotations in unit tests --- src/ShellCheck/Analytics.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index e1523fd..b3f3cb2 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -273,7 +273,11 @@ producesComments :: (Parameters -> Token -> [TokenComment]) -> String -> Maybe B producesComments f s = do let pr = pScript s prRoot pr - return . not . null $ runList (defaultSpec pr) [f] + let spec = defaultSpec pr + let params = makeParameters spec + return . not . null $ + filterByAnnotation spec params $ + runList spec [f] -- Copied from https://wiki.haskell.org/Edit_distance dist :: Eq a => [a] -> [a] -> Int From eeb7ea01c95a900039abb41091c097af77a8f129 Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sun, 30 Jun 2019 16:36:45 -0700 Subject: [PATCH 18/35] Allow SC2103 to be silenced (fixes #1591) --- src/ShellCheck/Analytics.hs | 33 ++++++++++----------------------- 1 file changed, 10 insertions(+), 23 deletions(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index b3f3cb2..f89c51f 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -2343,27 +2343,18 @@ prop_checkCdAndBack4 = verify checkCdAndBack "cd $tmp; foo; cd -" prop_checkCdAndBack5 = verifyNot checkCdAndBack "cd ..; foo; cd .." prop_checkCdAndBack6 = verify checkCdAndBack "for dir in */; do cd \"$dir\"; some_cmd; cd ..; done" prop_checkCdAndBack7 = verifyNot checkCdAndBack "set -e; for dir in */; do cd \"$dir\"; some_cmd; cd ..; done" -checkCdAndBack params = doLists +prop_checkCdAndBack8 = verifyNot checkCdAndBack "cd tmp\nfoo\n# shellcheck disable=SC2103\ncd ..\n" +checkCdAndBack params t = + unless (hasSetE params) $ mapM_ doList $ getCommandSequences t where - shell = shellType params - doLists (T_ForIn _ _ _ cmds) = doList cmds - doLists (T_ForArithmetic _ _ _ _ cmds) = doList cmds - doLists (T_WhileExpression _ _ cmds) = doList cmds - doLists (T_UntilExpression _ _ cmds) = doList cmds - doLists (T_Script _ _ cmds) = doList cmds - doLists (T_IfExpression _ thens elses) = do - mapM_ (\(_, l) -> doList l) thens - doList elses - doLists _ = return () - isCdRevert t = case oversimplify t of - ["cd", p] -> p `elem` ["..", "-"] + [_, p] -> p `elem` ["..", "-"] _ -> False - getCmd (T_Annotation id _ x) = getCmd x - getCmd (T_Pipeline id _ [x]) = getCommandName x - getCmd _ = Nothing + getCandidate (T_Annotation _ _ x) = getCandidate x + getCandidate (T_Pipeline id _ [x]) | x `isCommand` "cd" = return x + getCandidate _ = Nothing findCdPair list = case list of @@ -2373,13 +2364,9 @@ checkCdAndBack params = doLists else findCdPair (b:rest) _ -> Nothing - doList list = - if hasSetE params - then return () - else let cds = filter ((== Just "cd") . getCmd) list - in potentially $ do - cd <- findCdPair cds - return $ info cd 2103 "Use a ( subshell ) to avoid having to cd back." + doList list = potentially $ do + cd <- findCdPair $ mapMaybe getCandidate list + return $ info cd 2103 "Use a ( subshell ) to avoid having to cd back." prop_checkLoopKeywordScope1 = verify checkLoopKeywordScope "continue 2" prop_checkLoopKeywordScope2 = verify checkLoopKeywordScope "for f; do ( break; ); done" From c381c5746f86eb43cfce91104c47215d1563b349 Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sun, 30 Jun 2019 17:28:15 -0700 Subject: [PATCH 19/35] Remove unnecessary lookahead in readDollarLonely --- src/ShellCheck/Parser.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index cd4bc8f..e00e1f5 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -1698,7 +1698,6 @@ readDollarLonely = do start <- startSpan char '$' id <- endSpan start - n <- lookAhead (anyChar <|> (eof >> return '_')) return $ T_Literal id "$" prop_readHereDoc = isOk readScript "cat << foo\nlol\ncow\nfoo" From 321afa427ef8efcf34f5b2aa0d327f7d1e6715f8 Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sun, 30 Jun 2019 17:38:17 -0700 Subject: [PATCH 20/35] Remove unused parse-time AST warnings --- src/ShellCheck/Parser.hs | 5 ----- 1 file changed, 5 deletions(-) diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index e00e1f5..059f03b 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -138,7 +138,6 @@ almostSpace = return ' ' --------- Message/position annotation on top of user state -data Note = Note Id Severity Code String deriving (Show, Eq) data ParseNote = ParseNote SourcePos SourcePos Severity Code String deriving (Show, Eq) data Context = ContextName SourcePos String @@ -166,10 +165,6 @@ initialUserState = UserState { } codeForParseNote (ParseNote _ _ _ code _) = code -noteToParseNote map (Note id severity code message) = - ParseNote pos pos severity code message - where - pos = fromJust $ Map.lookup id map getLastId = lastId <$> getState From 544047c5afa19fb1551ba4f0d4f56ef34746e391 Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sun, 30 Jun 2019 18:26:41 -0700 Subject: [PATCH 21/35] Warn about ending double quotes just to make $ literal --- CHANGELOG.md | 1 + src/ShellCheck/Parser.hs | 27 ++++++++++++++++++++++++--- 2 files changed, 25 insertions(+), 3 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index e074894..5ea2768 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -19,6 +19,7 @@ - SC2246: Warn if a shebang's interpreter ends with / - SC2245: Warn that Ksh ignores all but the first glob result in `[` - SC2243/SC2244: Suggest using explicit -n for `[ $foo ]` (optional) +- SC1135: Suggest not ending double quotes just to make $ literal ### Changed - If a directive or shebang is not specified, a `.bash/.bats/.dash/.ksh` diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index 059f03b..445d43b 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -1524,10 +1524,10 @@ ensureDollar = readNormalDollar = do ensureDollar - readDollarExp <|> readDollarDoubleQuote <|> readDollarSingleQuote <|> readDollarLonely + readDollarExp <|> readDollarDoubleQuote <|> readDollarSingleQuote <|> readDollarLonely False readDoubleQuotedDollar = do ensureDollar - readDollarExp <|> readDollarLonely + readDollarExp <|> readDollarLonely True prop_readDollarExpression1 = isOk readDollarExpression "$(((1) && 3))" @@ -1689,11 +1689,32 @@ readVariableName = do rest <- many variableChars return (f:rest) -readDollarLonely = do + +prop_readDollarLonely1 = isWarning readNormalWord "\"$\"var" +prop_readDollarLonely2 = isWarning readNormalWord "\"$\"\"var\"" +prop_readDollarLonely3 = isOk readNormalWord "\"$\"$var" +prop_readDollarLonely4 = isOk readNormalWord "\"$\"*" +prop_readDollarLonely5 = isOk readNormalWord "$\"str\"" +readDollarLonely quoted = do start <- startSpan char '$' id <- endSpan start + when quoted $ do + isHack <- quoteForEscape + when isHack $ + parseProblemAtId id StyleC 1135 + "Prefer escape over ending quote to make $ literal. Instead of \"It costs $\"5, use \"It costs \\$5\"." return $ T_Literal id "$" + where + quoteForEscape = option False $ try . lookAhead $ do + char '"' + -- Check for "foo $""bar" + optional $ char '"' + c <- anyVar + -- Don't trigger on [[ x == "$"* ]] or "$"$pattern + return $ c `notElem` "*$" + anyVar = variableStart <|> digit <|> specialVariable + prop_readHereDoc = isOk readScript "cat << foo\nlol\ncow\nfoo" prop_readHereDoc2 = isNotOk readScript "cat <<- EOF\n cow\n EOF" From 9702f1ff9c21e4c6508345bd9a9fbcd37de43c0a Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sun, 30 Jun 2019 20:19:10 -0700 Subject: [PATCH 22/35] Handle diffs for files without trailing linefeed --- src/ShellCheck/Formatter/Diff.hs | 48 ++++++++++++++++++++++++++------ 1 file changed, 40 insertions(+), 8 deletions(-) diff --git a/src/ShellCheck/Formatter/Diff.hs b/src/ShellCheck/Formatter/Diff.hs index 58fd2f4..445d9de 100644 --- a/src/ShellCheck/Formatter/Diff.hs +++ b/src/ShellCheck/Formatter/Diff.hs @@ -75,7 +75,8 @@ checkFooter didOutput color = do printErr color "Issues were detected, but none were auto-fixable. Use another format to see them." type ColorFunc = (Int -> String -> String) -data DiffDoc a = DiffDoc String [DiffRegion a] +data LFStatus = LinefeedMissing | LinefeedOk +data DiffDoc a = DiffDoc String LFStatus [DiffRegion a] data DiffRegion a = DiffRegion (Int, Int) (Int, Int) [Diff a] reportResult :: (IORef Bool) -> ColorFunc -> CheckResult -> SystemInterface IO -> IO () @@ -93,9 +94,25 @@ reportResult didOutput color result sys = do writeIORef didOutput True Left msg -> reportFailure color name msg +hasTrailingLinefeed str = + case str of + [] -> True + _ -> last str == '\n' + +coversLastLine regions = + case regions of + [] -> False + _ -> (fst $ last regions) + +-- TODO: Factor this out into a unified diff library because we're doing a lot +-- of the heavy lifting anyways. makeDiff :: String -> String -> Fix -> DiffDoc String -makeDiff name contents fix = - DiffDoc name $ findRegions . groupDiff $ computeDiff contents fix +makeDiff name contents fix = do + let hunks = groupDiff $ computeDiff contents fix + let lf = if coversLastLine hunks && not (hasTrailingLinefeed contents) + then LinefeedMissing + else LinefeedOk + DiffDoc name lf $ findRegions hunks computeDiff :: String -> Fix -> [Diff String] computeDiff contents fix = @@ -151,21 +168,36 @@ countDelta = count' 0 0 First {} -> count' (left+1) right rest Second {} -> count' left (right+1) rest -formatRegion :: ColorFunc -> DiffRegion String -> String -formatRegion color (DiffRegion left right diffs) = +formatRegion :: ColorFunc -> LFStatus -> DiffRegion String -> String +formatRegion color lf (DiffRegion left right diffs) = let header = color cyan ("@@ -" ++ (tup left) ++ " +" ++ (tup right) ++" @@") in - unlines $ header : map format diffs + unlines $ header : reverse (getStrings lf (reverse diffs)) where + noLF = "\\ No newline at end of file" + + getStrings LinefeedOk list = map format list + getStrings LinefeedMissing list@((Both _ _):_) = noLF : map format list + getStrings LinefeedMissing list@((First _):_) = noLF : map format list + getStrings LinefeedMissing (last:rest) = format last : getStrings LinefeedMissing rest + tup (a,b) = (show a) ++ "," ++ (show b) format (Both x _) = ' ':x format (First x) = color red $ '-':x format (Second x) = color green $ '+':x -formatDoc color (DiffDoc name regions) = +splitLast [] = ([], []) +splitLast x = + let (last, rest) = splitAt 1 $ reverse x + in (reverse rest, last) + +formatDoc color (DiffDoc name lf regions) = + let (most, last) = splitLast regions + in (color bold $ "--- " ++ ("a" name)) ++ "\n" ++ (color bold $ "+++ " ++ ("b" name)) ++ "\n" ++ - concatMap (formatRegion color) regions + concatMap (formatRegion color LinefeedOk) most ++ + concatMap (formatRegion color lf) last -- Create a Map from filename to Fix buildFixMap :: [Fix] -> M.Map String Fix From 3e3e4fd0cd733acf0e13b4ec5fbe577ad941a2cd Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Mon, 1 Jul 2019 23:22:09 -0700 Subject: [PATCH 23/35] Avoid defining flags for non-literal parameters --- src/ShellCheck/Analytics.hs | 1 + src/ShellCheck/AnalyzerLib.hs | 8 ++++---- 2 files changed, 5 insertions(+), 4 deletions(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index 37d97ab..b2cc179 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -2087,6 +2087,7 @@ prop_checkUnused40= verifyNotTree checkUnusedAssignments "arr=(1 2); num=2; echo prop_checkUnused41= verifyNotTree checkUnusedAssignments "@test 'foo' {\ntrue\n}\n" prop_checkUnused42= verifyNotTree checkUnusedAssignments "DEFINE_string foo '' ''; echo \"${FLAGS_foo}\"" prop_checkUnused43= verifyTree checkUnusedAssignments "DEFINE_string foo '' ''" +prop_checkUnused44= verifyNotTree checkUnusedAssignments "DEFINE_string \"foo$ibar\" x y" checkUnusedAssignments params t = execWriter (mapM_ warnFor unused) where flow = variableFlow params diff --git a/src/ShellCheck/AnalyzerLib.hs b/src/ShellCheck/AnalyzerLib.hs index 508b6ee..cf74c65 100644 --- a/src/ShellCheck/AnalyzerLib.hs +++ b/src/ShellCheck/AnalyzerLib.hs @@ -685,10 +685,10 @@ getModifiedVariableCommand base@(T_SimpleCommand _ _ (T_NormalWord _ (T_Literal (filter (\(x,_) -> getLiteralString x == Just "-a") (zip (args) (tail args))) -- get the FLAGS_ variable created by a shflags DEFINE_ call - getFlagVariable (n:v:_) = return (base, n, flagName n, DataString $ SourceFrom [v]) - where - flagName varName@(T_NormalWord _ _) = "FLAGS_" ++ (onlyLiteralString varName) - getFlagVariable _ = fail "Invalid flag definition" + getFlagVariable (n:v:_) = do + name <- getLiteralString v + return (base, n, "FLAGS_" ++ name, DataString $ SourceExternal) + getFlagVariable _ = Nothing getModifiedVariableCommand _ = [] From ef764b60caba1ef87f24e34dd8344894c52e65cb Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Mon, 1 Jul 2019 23:47:13 -0700 Subject: [PATCH 24/35] Fix botched variable usage --- src/ShellCheck/AnalyzerLib.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/ShellCheck/AnalyzerLib.hs b/src/ShellCheck/AnalyzerLib.hs index cf74c65..581a117 100644 --- a/src/ShellCheck/AnalyzerLib.hs +++ b/src/ShellCheck/AnalyzerLib.hs @@ -686,7 +686,7 @@ getModifiedVariableCommand base@(T_SimpleCommand _ _ (T_NormalWord _ (T_Literal -- get the FLAGS_ variable created by a shflags DEFINE_ call getFlagVariable (n:v:_) = do - name <- getLiteralString v + name <- getLiteralString n return (base, n, "FLAGS_" ++ name, DataString $ SourceExternal) getFlagVariable _ = Nothing From bee4303c323271c8d0bd26348eb045b7412e55da Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Tue, 2 Jul 2019 20:07:05 -0700 Subject: [PATCH 25/35] Add an empty Custom.hs to simplify site-specific patching --- CHANGELOG.md | 1 + ShellCheck.cabal | 1 + src/ShellCheck/Analyzer.hs | 2 ++ src/ShellCheck/Checks/Custom.hs | 21 +++++++++++++++++++++ test/shellcheck.hs | 2 ++ 5 files changed, 27 insertions(+) create mode 100644 src/ShellCheck/Checks/Custom.hs diff --git a/CHANGELOG.md b/CHANGELOG.md index dc05c04..c9834f7 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -10,6 +10,7 @@ to specify search paths for sourced files. - json1 format like --format=json but treats tabs as single characters - Recognize FLAGS variables created by the shflags library. +- Site-specific changes can now be made in Custom.hs for ease of patching - SC2154: Also warn about unassigned uppercase variables (optional) - SC2252: Warn about `[ $a != x ] || [ $a != y ]`, similar to SC2055 - SC2251: Inform about ineffectual ! in front of commands diff --git a/ShellCheck.cabal b/ShellCheck.cabal index 781a082..4658dd0 100644 --- a/ShellCheck.cabal +++ b/ShellCheck.cabal @@ -74,6 +74,7 @@ library ShellCheck.AnalyzerLib ShellCheck.Checker ShellCheck.Checks.Commands + ShellCheck.Checks.Custom ShellCheck.Checks.ShellSupport ShellCheck.Data ShellCheck.Fixer diff --git a/src/ShellCheck/Analyzer.hs b/src/ShellCheck/Analyzer.hs index 01440d8..33d2ae0 100644 --- a/src/ShellCheck/Analyzer.hs +++ b/src/ShellCheck/Analyzer.hs @@ -25,6 +25,7 @@ import ShellCheck.Interface import Data.List import Data.Monoid import qualified ShellCheck.Checks.Commands +import qualified ShellCheck.Checks.Custom import qualified ShellCheck.Checks.ShellSupport @@ -41,6 +42,7 @@ analyzeScript spec = newAnalysisResult { checkers params = mconcat $ map ($ params) [ ShellCheck.Checks.Commands.checker, + ShellCheck.Checks.Custom.checker, ShellCheck.Checks.ShellSupport.checker ] diff --git a/src/ShellCheck/Checks/Custom.hs b/src/ShellCheck/Checks/Custom.hs new file mode 100644 index 0000000..76ac83c --- /dev/null +++ b/src/ShellCheck/Checks/Custom.hs @@ -0,0 +1,21 @@ +{- + This empty file is provided for ease of patching in site specific checks. + However, there are no guarantees regarding compatibility between versions. +-} + +{-# LANGUAGE TemplateHaskell #-} +module ShellCheck.Checks.Custom (checker, ShellCheck.Checks.Custom.runTests) where + +import ShellCheck.AnalyzerLib +import Test.QuickCheck + +checker :: Parameters -> Checker +checker params = Checker { + perScript = const $ return (), + perToken = const $ return () + } + +prop_CustomTestsWork = True + +return [] +runTests = $quickCheckAll diff --git a/test/shellcheck.hs b/test/shellcheck.hs index d55b140..ac84116 100644 --- a/test/shellcheck.hs +++ b/test/shellcheck.hs @@ -6,6 +6,7 @@ import qualified ShellCheck.Analytics import qualified ShellCheck.AnalyzerLib import qualified ShellCheck.Checker import qualified ShellCheck.Checks.Commands +import qualified ShellCheck.Checks.Custom import qualified ShellCheck.Checks.ShellSupport import qualified ShellCheck.Fixer import qualified ShellCheck.Formatter.Diff @@ -18,6 +19,7 @@ main = do ,ShellCheck.AnalyzerLib.runTests ,ShellCheck.Checker.runTests ,ShellCheck.Checks.Commands.runTests + ,ShellCheck.Checks.Custom.runTests ,ShellCheck.Checks.ShellSupport.runTests ,ShellCheck.Fixer.runTests ,ShellCheck.Formatter.Diff.runTests From be1f1c1ab76dcd55f06ecf99b585bba719bdbf5b Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Tue, 2 Jul 2019 20:58:08 -0700 Subject: [PATCH 26/35] Don't count 'readonly x' as a reference to x (fixes #1573) --- src/ShellCheck/Analytics.hs | 2 ++ src/ShellCheck/AnalyzerLib.hs | 4 ---- 2 files changed, 2 insertions(+), 4 deletions(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index b2cc179..85e7afe 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -2088,6 +2088,8 @@ prop_checkUnused41= verifyNotTree checkUnusedAssignments "@test 'foo' {\ntrue\n} prop_checkUnused42= verifyNotTree checkUnusedAssignments "DEFINE_string foo '' ''; echo \"${FLAGS_foo}\"" prop_checkUnused43= verifyTree checkUnusedAssignments "DEFINE_string foo '' ''" prop_checkUnused44= verifyNotTree checkUnusedAssignments "DEFINE_string \"foo$ibar\" x y" +prop_checkUnused45= verifyTree checkUnusedAssignments "readonly foo=bar" +prop_checkUnused46= verifyTree checkUnusedAssignments "readonly foo=(bar)" checkUnusedAssignments params t = execWriter (mapM_ warnFor unused) where flow = variableFlow params diff --git a/src/ShellCheck/AnalyzerLib.hs b/src/ShellCheck/AnalyzerLib.hs index 581a117..dc0e3c4 100644 --- a/src/ShellCheck/AnalyzerLib.hs +++ b/src/ShellCheck/AnalyzerLib.hs @@ -546,10 +546,6 @@ getReferencedVariableCommand base@(T_SimpleCommand _ _ (T_NormalWord _ (T_Litera (not $ any (`elem` flags) ["f", "F"]) then concatMap getReference rest else [] - "readonly" -> - if any (`elem` flags) ["f", "p"] - then [] - else concatMap getReference rest "trap" -> case rest of head:_ -> map (\x -> (head, head, x)) $ getVariablesFromLiteralToken head From 4d56852b9f61267c70515b7ae648ae81ea5d119b Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Wed, 3 Jul 2019 19:49:47 -0700 Subject: [PATCH 27/35] Allow SCRIPTDIR in source directives (fixes #1617) --- shellcheck.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/shellcheck.hs b/shellcheck.hs index 4ba8b70..20fb4b6 100644 --- a/shellcheck.hs +++ b/shellcheck.hs @@ -500,8 +500,8 @@ ioInterface options files = do find original original where find filename deflt = do - sources <- filterM ((allowable inputs) `andM` doesFileExist) - (map ( filename) $ map adjustPath $ sourcePathFlag ++ sourcePathAnnotation) + sources <- filterM ((allowable inputs) `andM` doesFileExist) $ + (adjustPath filename):(map ( filename) $ map adjustPath $ sourcePathFlag ++ sourcePathAnnotation) case sources of [] -> return deflt (first:_) -> return first From ba2c20a08a08a9a9d71c5fe8396bdec9479deecb Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Wed, 3 Jul 2019 20:02:14 -0700 Subject: [PATCH 28/35] Improve message for SC1067 --- src/ShellCheck/Parser.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index 445d43b..b2935fd 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -2765,7 +2765,7 @@ readAssignmentWordExt lenient = try $ do variable <- readVariableName when lenient $ optional (readNormalDollar >> parseNoteAt pos ErrorC - 1067 "For indirection, use (associative) arrays or 'read \"var$n\" <<< \"value\"'") + 1067 "For indirection, use arrays, declare \"var$n=value\", or (for sh) read/eval.") indices <- many readArrayIndex hasLeftSpace <- fmap (not . null) spacing pos <- getPosition From 380221a02cc70883658cd89812c97504a424586f Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Wed, 3 Jul 2019 20:35:20 -0700 Subject: [PATCH 29/35] Recognize `read -ra foo` as arrays (fixes #1636) --- src/ShellCheck/Analytics.hs | 1 + src/ShellCheck/AnalyzerLib.hs | 11 +++++++++-- 2 files changed, 10 insertions(+), 2 deletions(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index 85e7afe..c60c6ea 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -840,6 +840,7 @@ prop_checkArrayWithoutIndex6 = verifyTree checkArrayWithoutIndex "echo $PIPESTAT prop_checkArrayWithoutIndex7 = verifyTree checkArrayWithoutIndex "a=(a b); a+=c" prop_checkArrayWithoutIndex8 = verifyTree checkArrayWithoutIndex "declare -a foo; foo=bar;" prop_checkArrayWithoutIndex9 = verifyTree checkArrayWithoutIndex "read -r -a arr <<< 'foo bar'; echo \"$arr\"" +prop_checkArrayWithoutIndex10= verifyTree checkArrayWithoutIndex "read -ra arr <<< 'foo bar'; echo \"$arr\"" checkArrayWithoutIndex params _ = doVariableFlowAnalysis readF writeF defaultMap (variableFlow params) where diff --git a/src/ShellCheck/AnalyzerLib.hs b/src/ShellCheck/AnalyzerLib.hs index dc0e3c4..0640da2 100644 --- a/src/ShellCheck/AnalyzerLib.hs +++ b/src/ShellCheck/AnalyzerLib.hs @@ -676,9 +676,16 @@ getModifiedVariableCommand base@(T_SimpleCommand _ _ (T_NormalWord _ (T_Literal return (base, lastArg, name, DataArray SourceExternal) -- get all the array variables used in read, e.g. read -a arr - getReadArrayVariables args = do + getReadArrayVariables args = map (getLiteralArray . snd) - (filter (\(x,_) -> getLiteralString x == Just "-a") (zip (args) (tail args))) + (filter (isArrayFlag . fst) (zip args (tail args))) + + isArrayFlag x = fromMaybe False $ do + str <- getLiteralString x + return $ case str of + '-':'-':_ -> False + '-':str -> 'a' `elem` str + _ -> False -- get the FLAGS_ variable created by a shflags DEFINE_ call getFlagVariable (n:v:_) = do From c0d3a98fcdd952683714c313bd633ba70d34733f Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Thu, 4 Jul 2019 16:54:42 -0700 Subject: [PATCH 30/35] Add warning for chmod -r (fixes #1321) --- src/ShellCheck/Checks/Commands.hs | 12 ++++++++++++ 1 file changed, 12 insertions(+) diff --git a/src/ShellCheck/Checks/Commands.hs b/src/ShellCheck/Checks/Commands.hs index 851d7f2..c95720a 100644 --- a/src/ShellCheck/Checks/Commands.hs +++ b/src/ShellCheck/Checks/Commands.hs @@ -94,6 +94,7 @@ commandChecks = [ ,checkSudoRedirect ,checkSudoArgs ,checkSourceArgs + ,checkChmodDashr ] buildCommandMap :: [CommandCheck] -> Map.Map CommandName (Token -> Analysis) @@ -1042,5 +1043,16 @@ checkSourceArgs = CommandCheck (Exactly ".") f "The dot command does not support arguments in sh/dash. Set them as variables." _ -> return () +prop_checkChmodDashr1 = verify checkChmodDashr "chmod -r 0755 dir" +prop_checkChmodDashr2 = verifyNot checkChmodDashr "chmod -R 0755 dir" +prop_checkChmodDashr3 = verifyNot checkChmodDashr "chmod a-r dir" +checkChmodDashr = CommandCheck (Basename "chmod") f + where + f t = mapM_ check $ arguments t + check t = potentially $ do + flag <- getLiteralString t + guard $ flag == "-r" + return $ warn (getId t) 2253 "Use -R to recurse, or explicitly a-r to remove read permissions." + return [] runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |]) From 914974bd4f80fa1bddabb0a5d03bef9e8e66e9f9 Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Thu, 4 Jul 2019 17:09:28 -0700 Subject: [PATCH 31/35] Don't consider `.*` a glob-like regex (fixes #1214) --- src/ShellCheck/AnalyzerLib.hs | 2 +- src/ShellCheck/Checks/Commands.hs | 5 ++++- 2 files changed, 5 insertions(+), 2 deletions(-) diff --git a/src/ShellCheck/AnalyzerLib.hs b/src/ShellCheck/AnalyzerLib.hs index 0640da2..70b781e 100644 --- a/src/ShellCheck/AnalyzerLib.hs +++ b/src/ShellCheck/AnalyzerLib.hs @@ -791,7 +791,7 @@ isCommandMatch token matcher = fromMaybe False $ -- False: .*foo.* isConfusedGlobRegex :: String -> Bool isConfusedGlobRegex ('*':_) = True -isConfusedGlobRegex [x,'*'] | x /= '\\' = True +isConfusedGlobRegex [x,'*'] | x `notElem` "\\." = True isConfusedGlobRegex _ = False isVariableStartChar x = x == '_' || isAsciiLower x || isAsciiUpper x diff --git a/src/ShellCheck/Checks/Commands.hs b/src/ShellCheck/Checks/Commands.hs index c95720a..f684130 100644 --- a/src/ShellCheck/Checks/Commands.hs +++ b/src/ShellCheck/Checks/Commands.hs @@ -214,6 +214,9 @@ prop_checkGrepRe17= verifyNot checkGrepRe "grep --exclude 'Foo*' file" prop_checkGrepRe18= verifyNot checkGrepRe "grep --exclude-dir 'Foo*' file" prop_checkGrepRe19= verify checkGrepRe "grep -- 'Foo*' file" prop_checkGrepRe20= verifyNot checkGrepRe "grep --fixed-strings 'Foo*' file" +prop_checkGrepRe21= verifyNot checkGrepRe "grep -o 'x*' file" +prop_checkGrepRe22= verifyNot checkGrepRe "grep --only-matching 'x*' file" +prop_checkGrepRe23= verifyNot checkGrepRe "grep '.*' file" checkGrepRe = CommandCheck (Basename "grep") check where check cmd = f cmd (arguments cmd) @@ -246,7 +249,7 @@ checkGrepRe = CommandCheck (Basename "grep") check where "Note that unlike globs, " ++ [char] ++ "* here matches '" ++ [char, char, char] ++ "' but not '" ++ wordStartingWith char ++ "'." where flags = map snd $ getAllFlags cmd - grepGlobFlags = ["fixed-strings", "F", "include", "exclude", "exclude-dir"] + grepGlobFlags = ["fixed-strings", "F", "include", "exclude", "exclude-dir", "o", "only-matching"] wordStartingWith c = head . filter ([c] `isPrefixOf`) $ candidates From 78b8e760662ee763a745b7b6d9d977ebb72274c2 Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Thu, 4 Jul 2019 17:43:18 -0700 Subject: [PATCH 32/35] Also mention globbing in SC2206 (fixes #1626) --- src/ShellCheck/Analytics.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index c60c6ea..1620d22 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -3095,8 +3095,8 @@ checkSplittingInArrays params t = && not (getBracedReference (bracedString part) `elem` variablesWithoutSpaces) -> warn id 2206 $ if shellType params == Ksh - then "Quote to prevent word splitting, or split robustly with read -A or while read." - else "Quote to prevent word splitting, or split robustly with mapfile or read -a." + then "Quote to prevent word splitting/globbing, or split robustly with read -A or while read." + else "Quote to prevent word splitting/globbing, or split robustly with mapfile or read -a." _ -> return () forCommand id = From 788cf1707639283ac98b6c13400be25d9feee158 Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Thu, 4 Jul 2019 19:10:14 -0700 Subject: [PATCH 33/35] Fix bad advice for SC2251 (fixes #1588) --- src/ShellCheck/Analytics.hs | 30 ++++++++++++++++++++---------- 1 file changed, 20 insertions(+), 10 deletions(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index 1620d22..067a53f 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -3395,18 +3395,23 @@ checkDefaultCase _ t = pg <- wordToExactPseudoGlob pat return $ pseudoGlobIsSuperSetof pg [PGMany] -prop_checkUselessBang1 = verify checkUselessBang "! true; rest" -prop_checkUselessBang2 = verify checkUselessBang "while true; do ! true; done" -prop_checkUselessBang3 = verifyNot checkUselessBang "if ! true; then true; fi" -prop_checkUselessBang4 = verifyNot checkUselessBang "( ! true )" -prop_checkUselessBang5 = verifyNot checkUselessBang "{ ! true; }" -prop_checkUselessBang6 = verifyNot checkUselessBang "x() { ! [ x ]; }" -checkUselessBang params t = mapM_ check (getNonReturningCommands t) +prop_checkUselessBang1 = verify checkUselessBang "set -e; ! true; rest" +prop_checkUselessBang2 = verifyNot checkUselessBang "! true; rest" +prop_checkUselessBang3 = verify checkUselessBang "set -e; while true; do ! true; done" +prop_checkUselessBang4 = verifyNot checkUselessBang "set -e; if ! true; then true; fi" +prop_checkUselessBang5 = verifyNot checkUselessBang "set -e; ( ! true )" +prop_checkUselessBang6 = verify checkUselessBang "set -e; { ! true; }" +prop_checkUselessBang7 = verifyNot checkUselessBang "set -e; x() { ! [ x ]; }" +prop_checkUselessBang8 = verifyNot checkUselessBang "set -e; if { ! true; }; then true; fi" +prop_checkUselessBang9 = verifyNot checkUselessBang "set -e; while ! true; do true; done" +checkUselessBang params t = when (hasSetE params) $ mapM_ check (getNonReturningCommands t) where check t = case t of - T_Banged id _ -> - info id 2251 "This ! is not on a condition and skips errexit. Use { ! ...; } to errexit, or verify usage." + T_Banged id cmd | not $ isCondition (getPath (parentMap params) t) -> + addComment $ makeCommentWithFix InfoC id 2251 + "This ! is not on a condition and skips errexit. Use `&& exit 1` instead, or make sure $? is checked." + (fixWith [replaceStart id params 1 "", replaceEnd (getId cmd) params 0 " && exit 1"]) _ -> return () -- Get all the subcommands that aren't likely to be the return value @@ -3414,7 +3419,7 @@ checkUselessBang params t = mapM_ check (getNonReturningCommands t) getNonReturningCommands t = case t of T_Script _ _ list -> dropLast list - T_BraceGroup _ list -> dropLast list + T_BraceGroup _ list -> if isFunctionBody t then dropLast list else list T_Subshell _ list -> dropLast list T_WhileExpression _ conds cmds -> dropLast conds ++ cmds T_UntilExpression _ conds cmds -> dropLast conds ++ cmds @@ -3425,6 +3430,11 @@ checkUselessBang params t = mapM_ check (getNonReturningCommands t) concatMap (dropLast . fst) conds ++ concatMap snd conds ++ elses _ -> [] + isFunctionBody t = + case getPath (parentMap params) t of + _:T_Function {}:_-> True + _ -> False + dropLast t = case t of [_] -> [] From 023ae5dfdabf5c347fda76694d96c9ef50f8068b Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sat, 20 Jul 2019 15:10:41 -0700 Subject: [PATCH 34/35] Don't warn about printf '%()T' without corresponding argument --- CHANGELOG.md | 3 + src/ShellCheck/Checks/Commands.hs | 91 +++++++++++++++++++++---------- 2 files changed, 64 insertions(+), 30 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index c9834f7..45c9a0e 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -28,6 +28,9 @@ extension will be used to infer the shell type when present. - Disabling SC2120 on a function now disables SC2119 on call sites +### Fixed +- SC2183 no longer warns about missing printf args for `%()T` + ## v0.6.0 - 2018-12-02 ### Added - Command line option --severity/-S for filtering by minimum severity diff --git a/src/ShellCheck/Checks/Commands.hs b/src/ShellCheck/Checks/Commands.hs index f684130..c6346a9 100644 --- a/src/ShellCheck/Checks/Commands.hs +++ b/src/ShellCheck/Checks/Commands.hs @@ -538,52 +538,83 @@ prop_checkPrintfVar15= verifyNot checkPrintfVar "printf '%*s\\n' 1 2" prop_checkPrintfVar16= verifyNot checkPrintfVar "printf $'string'" prop_checkPrintfVar17= verify checkPrintfVar "printf '%-*s\\n' 1" prop_checkPrintfVar18= verifyNot checkPrintfVar "printf '%-*s\\n' 1 2" +prop_checkPrintfVar19= verifyNot checkPrintfVar "printf '%(%s)T'" +prop_checkPrintfVar20= verifyNot checkPrintfVar "printf '%d %(%s)T' 42" +prop_checkPrintfVar21= verify checkPrintfVar "printf '%d %(%s)T'" 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 f (format:params) = check format params f _ = return () - countFormats string = - case string of - '%':'%':rest -> countFormats rest - '%':'(':rest -> 1 + countFormats (dropWhile (/= ')') rest) - '%':rest -> regexBasedCountFormats rest + countFormats (dropWhile (/= '%') rest) - _:rest -> countFormats rest - [] -> 0 - - regexBasedCountFormats rest = - maybe 1 (foldl (\acc group -> acc + (if group == "*" then 1 else 0)) 1) (matchRegex re rest) - where - -- constructed based on specifications in "man printf" - re = mkRegex "#?-?\\+? ?0?(\\*|\\d*).?(\\d*|\\*)[diouxXfFeEgGaAcsb]" - -- \____ _____/\___ ____/ \____ ____/\________ ________/ - -- V V V V - -- flags field width precision format character - -- field width and precision can be specified with a '*' instead of a digit, - -- in which case printf will accept one more argument for each '*' used check format more = do fromMaybe (return ()) $ do string <- getLiteralString format - let vars = countFormats string - - return $ do - when (vars == 0 && more /= []) $ - err (getId format) 2182 - "This printf format string has no variables. Other arguments are ignored." - - when (vars > 0 - && ((length more) `mod` vars /= 0 || null more) - && all (not . mayBecomeMultipleArgs) more) $ - warn (getId format) 2183 $ - "This format string has " ++ show vars ++ " variables, but is passed " ++ show (length more) ++ " arguments." + let formats = getPrintfFormats string + let formatCount = length formats + let argCount = length more + return $ + case () of + () | argCount == 0 && formatCount == 0 -> + return () -- This is fine + () | formatCount == 0 && argCount > 0 -> + err (getId format) 2182 + "This printf format string has no variables. Other arguments are ignored." + () | any mayBecomeMultipleArgs more -> + return () -- We don't know so trust the user + () | argCount < formatCount && onlyTrailingTs formats argCount -> + return () -- Allow trailing %()Ts since they use the current time + () | argCount > 0 && argCount `mod` formatCount == 0 -> + return () -- Great: a suitable number of arguments + () -> + warn (getId format) 2183 $ + "This format string has " ++ show formatCount ++ " variables, but is passed " ++ show argCount ++ " arguments." unless ('%' `elem` concat (oversimplify format) || isLiteral format) $ info (getId format) 2059 "Don't use variables in the printf format string. Use printf \"..%s..\" \"$foo\"." + where + onlyTrailingTs format argCount = + all (== 'T') $ drop argCount format +prop_checkGetPrintfFormats1 = getPrintfFormats "%s" == "s" +prop_checkGetPrintfFormats2 = getPrintfFormats "%0*s" == "*s" +prop_checkGetPrintfFormats3 = getPrintfFormats "%(%s)T" == "T" +prop_checkGetPrintfFormats4 = getPrintfFormats "%d%%%(%s)T" == "dT" +prop_checkGetPrintfFormats5 = getPrintfFormats "%bPassed: %d, %bFailed: %d%b, Skipped: %d, %bErrored: %d%b\\n" == "bdbdbdbdb" +getPrintfFormats = getFormats + where + -- Get the arguments in the string as a string of type characters, + -- e.g. "Hello %s" -> "s" and "%(%s)T %0*d\n" -> "T*d" + getFormats :: String -> String + getFormats string = + case string of + '%':'%':rest -> getFormats rest + '%':'(':rest -> + case dropWhile (/= ')') rest of + ')':c:trailing -> c : getFormats trailing + _ -> "" + '%':rest -> regexBasedGetFormats rest + _:rest -> getFormats rest + [] -> "" + + regexBasedGetFormats rest = + case matchRegex re rest of + Just [width, precision, typ, rest] -> + (if width == "*" then "*" else "") ++ + (if precision == "*" then "*" else "") ++ + typ ++ getFormats rest + Nothing -> take 1 rest ++ getFormats rest + where + -- constructed based on specifications in "man printf" + re = mkRegex "#?-?\\+? ?0?(\\*|\\d*)\\.?(\\d*|\\*)([diouxXfFeEgGaAcsbq])(.*)" + -- \____ _____/\___ ____/ \____ ____/\_________ _________/ \ / + -- V V V V V + -- flags field width precision format character rest + -- field width and precision can be specified with a '*' instead of a digit, + -- in which case printf will accept one more argument for each '*' used prop_checkUuoeCmd1 = verify checkUuoeCmd "echo $(date)" From 38bb156a1cda803b823196ad6015a0b3b70678b4 Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sun, 21 Jul 2019 21:22:16 -0700 Subject: [PATCH 35/35] Warn about $_ in POSIX sh (fixes #1647) --- src/ShellCheck/Checks/ShellSupport.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/ShellCheck/Checks/ShellSupport.hs b/src/ShellCheck/Checks/ShellSupport.hs index 4a86891..83d23fb 100644 --- a/src/ShellCheck/Checks/ShellSupport.hs +++ b/src/ShellCheck/Checks/ShellSupport.hs @@ -175,6 +175,8 @@ prop_checkBashisms91 = verify checkBashisms "#!/bin/sh\nwait -n" prop_checkBashisms92 = verify checkBashisms "#!/bin/sh\necho $((16#FF))" prop_checkBashisms93 = verify checkBashisms "#!/bin/sh\necho $(( 10#$(date +%m) ))" prop_checkBashisms94 = verify checkBashisms "#!/bin/sh\n[ -v var ]" +prop_checkBashisms95 = verify checkBashisms "#!/bin/sh\necho $_" +prop_checkBashisms96 = verifyNot checkBashisms "#!/bin/dash\necho $_" checkBashisms = ForShell [Sh, Dash] $ \t -> do params <- ask kludge params t @@ -408,10 +410,11 @@ checkBashisms = ForShell [Sh, Dash] $ \t -> do ] bashVars = [ "OSTYPE", "MACHTYPE", "HOSTTYPE", "HOSTNAME", - "DIRSTACK", "EUID", "UID", "SHLVL", "PIPESTATUS", "SHELLOPTS" + "DIRSTACK", "EUID", "UID", "SHLVL", "PIPESTATUS", "SHELLOPTS", + "_" ] bashDynamicVars = [ "RANDOM", "SECONDS" ] - dashVars = [ ] + dashVars = [ "_" ] isBashVariable var = (var `elem` bashDynamicVars || var `elem` bashVars && not (isAssigned var))