From 5e4c288cf483959cbc4a3de69edeebdfd6e8c435 Mon Sep 17 00:00:00 2001 From: "mr.Shu" Date: Mon, 15 May 2017 11:26:12 +0200 Subject: [PATCH 01/15] SC2174: Do not warn at `mkdir -pm 0700 ../foo` * Do not warn when `mkdir -pm 0700` is used with combination of paths like `..` and `.` * Fixes #854 Signed-off-by: mr.Shu --- ShellCheck/Checks/Commands.hs | 13 +++++++++++-- 1 file changed, 11 insertions(+), 2 deletions(-) diff --git a/ShellCheck/Checks/Commands.hs b/ShellCheck/Checks/Commands.hs index b6ae98b..38cc2a2 100644 --- a/ShellCheck/Checks/Commands.hs +++ b/ShellCheck/Checks/Commands.hs @@ -385,17 +385,26 @@ prop_checkMkdirDashPM11 = verifyNot checkMkdirDashPM "mkdir --parents a/b" prop_checkMkdirDashPM12 = verifyNot checkMkdirDashPM "mkdir --mode=0755 a/b" prop_checkMkdirDashPM13 = verifyNot checkMkdirDashPM "mkdir_func -pm 0755 a/b" prop_checkMkdirDashPM14 = verifyNot checkMkdirDashPM "mkdir -p -m 0755 singlelevel" +prop_checkMkdirDashPM15 = verifyNot checkMkdirDashPM "mkdir -p -m 0755 ../bin" +prop_checkMkdirDashPM16 = verify checkMkdirDashPM "mkdir -p -m 0755 ../bin/laden" +prop_checkMkdirDashPM17 = verifyNot checkMkdirDashPM "mkdir -p -m 0755 ./bin" +prop_checkMkdirDashPM18 = verify checkMkdirDashPM "mkdir -p -m 0755 ./bin/laden" +prop_checkMkdirDashPM19 = verifyNot checkMkdirDashPM "mkdir -p -m 0755 ./../bin" +prop_checkMkdirDashPM20 = verifyNot checkMkdirDashPM "mkdir -p -m 0755 .././bin" +prop_checkMkdirDashPM21 = verifyNot checkMkdirDashPM "mkdir -p -m 0755 ../../bin" checkMkdirDashPM = CommandCheck (Basename "mkdir") check where check t = potentially $ do let flags = getAllFlags t dashP <- find ((\f -> f == "p" || f == "parents") . snd) flags dashM <- find ((\f -> f == "m" || f == "mode") . snd) flags - guard $ any couldHaveSubdirs (drop 1 $ arguments t) -- mkdir -pm 0700 dir is fine, but dir/subdir is not. + -- mkdir -pm 0700 dir is fine, so is ../dir, but dir/subdir is not. + guard $ any couldHaveSubdirs (drop 1 $ arguments t) return $ warn (getId $ fst dashM) 2174 "When used with -p, -m only applies to the deepest directory." couldHaveSubdirs t = fromMaybe True $ do name <- getLiteralString t - return $ '/' `elem` name + return $ '/' `elem` name && not (name `matches` re) + re = mkRegex "^(\\.\\.?\\/)+[^/]+$" prop_checkNonportableSignals1 = verify checkNonportableSignals "trap f 8" From d943ef6f7752c7876f847e8d002c367896352372 Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sat, 20 May 2017 21:13:53 -0700 Subject: [PATCH 02/15] Update Docker instructions. --- README.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index e21f00a..c7c94da 100644 --- a/README.md +++ b/README.md @@ -129,9 +129,9 @@ From Docker Hub: Using the Docker image can be done like so: - docker run -v $(pwd):/scripts koalaman/shellcheck /scripts/myscript.sh + docker run -v "$PWD:/mnt" koalaman/shellcheck myscript -Here the local directory ( $(pwd) ) is mounted into the containers directory "/scripts". The script "myscript.sh" is checked. +Here the current directory `$PWD` is mounted as the container's directory `/mnt`, which is ShellCheck's working directory in the image. The script `myscript` is checked. ## Compiling from source From 5099ebf9b9552aa780ef96dbeb4c2844064f9f39 Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sun, 21 May 2017 13:56:22 -0700 Subject: [PATCH 03/15] Allow comments after shellcheck directives. --- ShellCheck/AnalyzerLib.hs | 56 ++++++++++++++++++++++++++++++--------- ShellCheck/Parser.hs | 36 ++++++++++++++++++------- 2 files changed, 71 insertions(+), 21 deletions(-) diff --git a/ShellCheck/AnalyzerLib.hs b/ShellCheck/AnalyzerLib.hs index dc7a02c..4568fc2 100644 --- a/ShellCheck/AnalyzerLib.hs +++ b/ShellCheck/AnalyzerLib.hs @@ -72,11 +72,11 @@ composeAnalyzers :: (a -> Analysis) -> (a -> Analysis) -> a -> Analysis composeAnalyzers f g x = f x >> g x data Parameters = Parameters { - variableFlow :: [StackData], - parentMap :: Map.Map Id Token, - shellType :: Shell, - shellTypeSpecified :: Bool, - rootNode :: Token + variableFlow :: [StackData], -- A linear (bad) analysis of data flow + parentMap :: Map.Map Id Token, -- A map from Id to parent Token + shellType :: Shell, -- The shell type, such as Bash or Ksh + shellTypeSpecified :: Bool, -- True if shell type was forced via flags + rootNode :: Token -- The root node of the AST } -- TODO: Cache results of common AST ops here @@ -184,8 +184,10 @@ executableFromShebang = shellFor shellFor s = reverse . takeWhile (/= '/') . reverse $ s ---- Context seeking +-- Given a root node, make a map from Id to parent Token. +-- This is used to populate parentMap in Parameters +getParentTree :: Token -> Map.Map Id Token getParentTree t = snd . snd $ runState (doStackAnalysis pre post t) ([], Map.empty) where @@ -195,18 +197,24 @@ getParentTree t = case rest of [] -> put (rest, map) (x:_) -> put (rest, Map.insert (getId t) x map) +-- Given a root node, make a map from Id to Token +getTokenMap :: Token -> Map.Map Id Token getTokenMap t = execState (doAnalysis f t) Map.empty where f t = modify (Map.insert (getId t) t) --- Is this node self quoting for a regular element? -isQuoteFree = isQuoteFreeNode False - --- Is this node striclty self quoting, for array expansions +-- Is this token in a quoting free context? (i.e. would variable expansion split) +-- True: Assignments, [[ .. ]], here docs, already in double quotes +-- False: Regular words isStrictlyQuoteFree = isQuoteFreeNode True +-- Like above, but also allow some cases where splitting may be desired. +-- True: Like above + for loops +-- False: Like above +isQuoteFree = isQuoteFreeNode False + isQuoteFreeNode strict tree t = (isQuoteFreeElement t == Just True) || @@ -239,6 +247,9 @@ isQuoteFreeNode strict tree t = T_SelectIn {} -> return (not strict) _ -> Nothing +-- Check if a token is a parameter to a certain command by name: +-- Example: isParamTo (parentMap params) "sed" t +isParamTo :: Map.Map Id Token -> String -> Token -> Bool isParamTo tree cmd = go where @@ -254,16 +265,20 @@ isParamTo tree cmd = T_Redirecting {} -> isCommand t cmd _ -> False +-- Get the parent command (T_Redirecting) of a Token, if any. +getClosestCommand :: Map.Map Id Token -> Token -> Maybe Token getClosestCommand tree t = msum . map getCommand $ getPath tree t where getCommand t@T_Redirecting {} = return t getCommand _ = Nothing +-- Like above, if koala_man knew Haskell when starting this project. getClosestCommandM t = do tree <- asks parentMap return $ getClosestCommand tree t +-- Is the token used as a command name (the first word in a T_SimpleCommand)? usedAsCommandName tree token = go (getId token) (tail $ getPath tree token) where go currentId (T_NormalWord id [word]:rest) @@ -274,7 +289,7 @@ usedAsCommandName tree token = go (getId token) (tail $ getPath tree token) | currentId == getId word = True go _ _ = False --- A list of the element and all its parents +-- A list of the element and all its parents up to the root node. getPath tree t = t : case Map.lookup (getId t) tree of Nothing -> [] @@ -623,13 +638,20 @@ dataTypeFrom defaultType v = (case v of T_Array {} -> DataArray; _ -> defaultTyp --- Command specific checks +-- Compare a command to a string: t `isCommand` "sed" (also matches /usr/bin/sed) isCommand token str = isCommandMatch token (\cmd -> cmd == str || ('/' : str) `isSuffixOf` cmd) + +-- Compare a command to a literal. Like above, but checks full path. isUnqualifiedCommand token str = isCommandMatch token (== str) isCommandMatch token matcher = fromMaybe False $ do cmd <- getCommandName token return $ matcher cmd +-- Does this regex look like it was intended as a glob? +-- True: *foo* +-- False: .*foo.* +isConfusedGlobRegex :: String -> Bool isConfusedGlobRegex ('*':_) = True isConfusedGlobRegex [x,'*'] | x /= '\\' = True isConfusedGlobRegex _ = False @@ -656,6 +678,7 @@ getVariablesFromLiteral string = where variableRegex = mkRegex "\\$\\{?([A-Za-z0-9_]+)" +-- Get the variable name from an expansion like ${var:-foo} prop_getBracedReference1 = getBracedReference "foo" == "foo" prop_getBracedReference2 = getBracedReference "#foo" == "foo" prop_getBracedReference3 = getBracedReference "#" == "#" @@ -706,13 +729,22 @@ getBracedModifier s = fromMaybe "" . listToMaybe $ do dropModifier (c:rest) | c `elem` "#!" = [rest, c:rest] dropModifier x = [x] --- Useful generic functions +-- Useful generic functions. + +-- Run an action in a Maybe (or do nothing). +-- Example: +-- potentially $ do +-- s <- getLiteralString cmd +-- guard $ s `elem` ["--recursive", "-r"] +-- return $ warn .. "Something something recursive" potentially :: Monad m => Maybe (m ()) -> m () potentially = fromMaybe (return ()) +-- Get element 0 or a default. Like `head` but safe. headOrDefault _ (a:_) = a headOrDefault def _ = def +--- Get element n of a list, or Nothing. Like `!!` but safe. (!!!) list i = case drop i list of [] -> Nothing diff --git a/ShellCheck/Parser.hs b/ShellCheck/Parser.hs index 1ea40aa..cc63e4e 100644 --- a/ShellCheck/Parser.hs +++ b/ShellCheck/Parser.hs @@ -889,10 +889,13 @@ prop_readAnnotation1 = isOk readAnnotation "# shellcheck disable=1234,5678\n" prop_readAnnotation2 = isOk readAnnotation "# shellcheck disable=SC1234 disable=SC5678\n" prop_readAnnotation3 = isOk readAnnotation "# shellcheck disable=SC1234 source=/dev/null disable=SC5678\n" prop_readAnnotation4 = isWarning readAnnotation "# shellcheck cats=dogs disable=SC1234\n" +prop_readAnnotation5 = isOk readAnnotation "# shellcheck disable=SC2002 # All cats are precious\n" +prop_readAnnotation6 = isOk readAnnotation "# shellcheck disable=SC1234 # shellcheck foo=bar\n" readAnnotation = called "shellcheck annotation" $ do try readAnnotationPrefix many1 linewhitespace values <- many1 (readDisable <|> readSourceOverride <|> readShellOverride <|> anyKey) + optional readAnyComment linefeed many linewhitespace return $ concat values @@ -926,7 +929,8 @@ readAnnotation = called "shellcheck annotation" $ do anyKey = do pos <- getPosition - anyChar `reluctantlyTill1` whitespace + noneOf "#\r\n" + anyChar `reluctantlyTill` whitespace many linewhitespace parseNoteAt pos WarningC 1107 "This directive is unknown. It will be ignored." return [] @@ -937,6 +941,9 @@ readAnnotations = do readComment = do unexpecting "shellcheck annotation" readAnnotationPrefix + readAnyComment + +readAnyComment = do char '#' many $ noneOf "\r\n" @@ -2729,14 +2736,18 @@ readScript = do script <- readScriptFile reparseIndices script -isWarning p s = parsesCleanly p s == Just False -isOk p s = parsesCleanly p s == Just True -isNotOk p s = parsesCleanly p s == Nothing -testParse string = runIdentity $ do - (res, _) <- runParser (mockedSystemInterface []) readScript "-" string +-- Interactively run a parser in ghci: +-- debugParse readScript "echo 'hello world'" +debugParse p string = runIdentity $ do + (res, _) <- runParser (mockedSystemInterface []) p "-" string return res + +isOk p s = parsesCleanly p s == Just True -- The string parses with no warnings +isWarning p s = parsesCleanly p s == Just False -- The string parses with warnings +isNotOk p s = parsesCleanly p s == Nothing -- The string does not parse + parsesCleanly parser string = runIdentity $ do (res, sys) <- runParser (mockedSystemInterface []) (parser >> eof >> getState) "-" string @@ -2745,6 +2756,16 @@ parsesCleanly parser string = runIdentity $ do return $ Just . null $ parseNotes userState ++ parseProblems systemState (Left _, _) -> return Nothing +-- For printf debugging: print the value of an expression +-- Example: return $ dump $ T_Literal id [c] +dump :: Show a => a -> a +dump x = trace (show x) x + +-- Like above, but print a specific expression: +-- Example: return $ dumps ("Returning: " ++ [c]) $ T_Literal id [c] +dumps :: Show x => x -> a -> a +dumps t = trace (show t) + parseWithNotes parser = do item <- parser state <- getState @@ -2877,9 +2898,6 @@ parseScript sys spec = parseShell sys (psFilename spec) (psScript spec) -lt x = trace (show x) x -ltt t = trace (show t) - return [] runTests = $quickCheckAll From 8bc89bc4515bd13149836ee92872b67d63eba2d4 Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sun, 21 May 2017 17:15:51 -0700 Subject: [PATCH 04/15] Mention DevGuide in the README --- README.md | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/README.md b/README.md index c7c94da..c4868ea 100644 --- a/README.md +++ b/README.md @@ -349,7 +349,9 @@ https://github.com/koalaman/shellcheck/issues ## Contributing -Please submit patches to code or documentation as GitHub pull requests! +Please submit patches to code or documentation as GitHub pull requests! Check +out the [DevGuide](https://github.com/koalaman/shellcheck/wiki/DevGuide) on the +ShellCheck Wiki. Contributions must be licensed under the GNU GPLv3. The contributor retains the copyright. From 4243c6a0bf59450f22debb613d2ed64e087e10da Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Wed, 24 May 2017 19:20:28 -0700 Subject: [PATCH 05/15] Treat + like :+ to squash SC2068 --- ShellCheck/Analytics.hs | 8 +++----- ShellCheck/AnalyzerLib.hs | 4 +++- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/ShellCheck/Analytics.hs b/ShellCheck/Analytics.hs index 33d81fb..b555f90 100644 --- a/ShellCheck/Analytics.hs +++ b/ShellCheck/Analytics.hs @@ -659,15 +659,12 @@ prop_checkUnquotedDollarAt6 = verifyNot checkUnquotedDollarAt "a=$@" prop_checkUnquotedDollarAt7 = verify checkUnquotedDollarAt "for f in ${var[@]}; do true; done" prop_checkUnquotedDollarAt8 = verifyNot checkUnquotedDollarAt "echo \"${args[@]:+${args[@]}}\"" prop_checkUnquotedDollarAt9 = verifyNot checkUnquotedDollarAt "echo ${args[@]:+\"${args[@]}\"}" +prop_checkUnquotedDollarAt10 = verifyNot checkUnquotedDollarAt "echo ${@+\"$@\"}" checkUnquotedDollarAt p word@(T_NormalWord _ parts) | not $ isStrictlyQuoteFree (parentMap p) word = forM_ (take 1 $ filter isArrayExpansion parts) $ \x -> - unless (isAlternative x) $ + unless (isQuotedAlternativeReference x) $ err (getId x) 2068 "Double quote array expansions to avoid re-splitting elements." - where - -- Fixme: should detect whether the alternative is quoted - isAlternative b@(T_DollarBraced _ t) = ":+" `isInfixOf` bracedString b - isAlternative _ = False checkUnquotedDollarAt _ _ = return () prop_checkConcatenatedDollarAt1 = verify checkConcatenatedDollarAt "echo \"foo$@\"" @@ -1609,6 +1606,7 @@ prop_checkSpacefulness31= verifyNotTree checkSpacefulness "echo \"`echo \\\"$1\\ prop_checkSpacefulness32= verifyNotTree checkSpacefulness "var=$1; [ -v var ]" prop_checkSpacefulness33= verifyTree checkSpacefulness "for file; do echo $file; done" prop_checkSpacefulness34= verifyTree checkSpacefulness "declare foo$n=$1" +prop_checkSpacefulness35= verifyNotTree checkSpacefulness "echo ${1+\"$1\"}" checkSpacefulness params t = doVariableFlowAnalysis readF writeF (Map.fromList defaults) (variableFlow params) diff --git a/ShellCheck/AnalyzerLib.hs b/ShellCheck/AnalyzerLib.hs index 4568fc2..a58111c 100644 --- a/ShellCheck/AnalyzerLib.hs +++ b/ShellCheck/AnalyzerLib.hs @@ -784,8 +784,10 @@ isCountingReference _ = False isQuotedAlternativeReference t = case t of T_DollarBraced _ _ -> - ":+" `isInfixOf` bracedString t + getBracedModifier (bracedString t) `matches` re _ -> False + where + re = mkRegex "(^|\\]):?\\+" From 070a465b64f0760023e081563d6f783fb608b155 Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sun, 28 May 2017 13:38:04 -0700 Subject: [PATCH 06/15] Recognize missing and superfluous cases in getopts loops. --- ShellCheck/AnalyzerLib.hs | 21 +++++++++-- ShellCheck/Checks/Commands.hs | 71 ++++++++++++++++++++++++++++++++++- 2 files changed, 87 insertions(+), 5 deletions(-) diff --git a/ShellCheck/AnalyzerLib.hs b/ShellCheck/AnalyzerLib.hs index a58111c..605b015 100644 --- a/ShellCheck/AnalyzerLib.hs +++ b/ShellCheck/AnalyzerLib.hs @@ -268,10 +268,13 @@ isParamTo tree cmd = -- Get the parent command (T_Redirecting) of a Token, if any. getClosestCommand :: Map.Map Id Token -> Token -> Maybe Token getClosestCommand tree t = - msum . map getCommand $ getPath tree t + findFirst findCommand $ getPath tree t where - getCommand t@T_Redirecting {} = return t - getCommand _ = Nothing + findCommand t = + case t of + T_Redirecting {} -> return True + T_Script {} -> return False + _ -> Nothing -- Like above, if koala_man knew Haskell when starting this project. getClosestCommandM t = do @@ -310,6 +313,18 @@ pathTo t = do parents <- reader parentMap return $ getPath parents t +-- Find the first match in a list where the predicate is Just True. +-- Stops if it's Just False and ignores Nothing. +findFirst :: (a -> Maybe Bool) -> [a] -> Maybe a +findFirst p l = + case l of + [] -> Nothing + (x:xs) -> + case p x of + Just True -> return x + Just False -> Nothing + Nothing -> findFirst p xs + -- Check whether a word is entirely output from a single command tokenIsJustCommandOutput t = case t of T_NormalWord id [T_DollarExpansion _ cmds] -> check cmds diff --git a/ShellCheck/Checks/Commands.hs b/ShellCheck/Checks/Commands.hs index 38cc2a2..4a17f69 100644 --- a/ShellCheck/Checks/Commands.hs +++ b/ShellCheck/Checks/Commands.hs @@ -38,7 +38,7 @@ import Control.Monad.RWS import Data.Char import Data.List import Data.Maybe -import qualified Data.Map as Map +import qualified Data.Map.Strict as Map import Test.QuickCheck.All (forAllProperties) import Test.QuickCheck.Test (quickCheckWithResult, stdArgs, maxSuccess) @@ -85,13 +85,14 @@ commandChecks = [ ,checkDeprecatedTempfile ,checkDeprecatedEgrep ,checkDeprecatedFgrep + ,checkWhileGetoptsCase ] buildCommandMap :: [CommandCheck] -> Map.Map CommandName (Token -> Analysis) buildCommandMap = foldl' addCheck Map.empty where addCheck map (CommandCheck name function) = - Map.insertWith' composeAnalyzers name function map + Map.insertWith composeAnalyzers name function map checkCommand :: Map.Map CommandName (Token -> Analysis) -> Token -> Analysis @@ -690,5 +691,71 @@ prop_checkDeprecatedFgrep = verify checkDeprecatedFgrep "fgrep '*' files" checkDeprecatedFgrep = CommandCheck (Basename "fgrep") $ \t -> info (getId t) 2197 "fgrep is non-standard and deprecated. Use grep -F instead." +prop_checkWhileGetoptsCase1 = verify checkWhileGetoptsCase "while getopts 'a:b' x; do case $x in a) foo;; esac; done" +prop_checkWhileGetoptsCase2 = verify checkWhileGetoptsCase "while getopts 'a:' x; do case $x in a) foo;; b) bar;; esac; done" +prop_checkWhileGetoptsCase3 = verifyNot checkWhileGetoptsCase "while getopts 'a:b' x; do case $x in a) foo;; b) bar;; esac; done" +prop_checkWhileGetoptsCase4 = verifyNot checkWhileGetoptsCase "while getopts 'a:123' x; do case $x in a) foo;; [0-9]) bar;; esac; done" +prop_checkWhileGetoptsCase5 = verifyNot checkWhileGetoptsCase "while getopts 'a:' x; do case $x in a) foo;; \\?) bar;; *) baz;; esac; done" +checkWhileGetoptsCase = CommandCheck (Exactly "getopts") f + where + f :: Token -> Analysis + f t@(T_SimpleCommand _ _ (cmd:arg1:_)) = do + path <- getPathM t + potentially $ do + options <- getLiteralString arg1 + (T_WhileExpression _ _ body) <- findFirst whileLoop path + caseCmd <- mapMaybe findCase body !!! 0 + return $ check (getId arg1) (map (:[]) $ filter (/= ':') options) caseCmd + f _ = return () + + check :: Id -> [String] -> Token -> Analysis + check optId opts (T_CaseExpression id _ list) = do + unless (Nothing `Map.member` handledMap) $ + mapM_ (warnUnhandled optId id) $ catMaybes $ Map.keys notHandled + + mapM_ warnRedundant $ Map.toList notRequested + + where + handledMap = Map.fromList (concatMap getHandledStrings list) + requestedMap = Map.fromList $ map (\x -> (Just x, ())) opts + + notHandled = Map.difference requestedMap handledMap + notRequested = Map.difference handledMap requestedMap + + warnUnhandled optId caseId str = + warn caseId 2213 $ "getopts specified -" ++ str ++ ", but it's not handled by this 'case'." + + warnRedundant (key, expr) = potentially $ do + str <- key + guard $ str `notElem` ["*", ":", "?"] + return $ warn (getId expr) 2214 "This case is not specified by getopts." + + getHandledStrings (_, globs, _) = + map (\x -> (literal x, x)) globs + + literal :: Token -> Maybe String + literal t = do + getLiteralString t <> fromGlob t + + fromGlob t = + case t of + T_Glob _ ('[':c:']':[]) -> return [c] + T_Glob _ "*" -> return "*" + _ -> Nothing + + whileLoop t = + case t of + T_WhileExpression {} -> return True + T_Script {} -> return False + _ -> Nothing + + findCase t = + case t of + T_Annotation _ _ x -> findCase x + T_Pipeline _ _ [x] -> findCase x + T_Redirecting _ _ x@(T_CaseExpression {}) -> return x + _ -> Nothing + + return [] runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |]) From ac3f0b3360061e833f3e7e31609a880fb11bd5cd Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sun, 28 May 2017 14:44:58 -0700 Subject: [PATCH 07/15] SC2114 about rm -rf /usr is no longer silenced by -- --- ShellCheck/Analytics.hs | 67 ----------------------------------- ShellCheck/Checks/Commands.hs | 60 +++++++++++++++++++++++++++++++ 2 files changed, 60 insertions(+), 67 deletions(-) diff --git a/ShellCheck/Analytics.hs b/ShellCheck/Analytics.hs index b555f90..77206e9 100644 --- a/ShellCheck/Analytics.hs +++ b/ShellCheck/Analytics.hs @@ -141,7 +141,6 @@ nodeChecks = [ ,checkWrongArithmeticAssignment ,checkConditionalAndOrs ,checkFunctionDeclarations - ,checkCatastrophicRm ,checkStderrPipe ,checkOverridingPath ,checkArrayAsString @@ -2135,72 +2134,6 @@ checkFunctionDeclarations params checkFunctionDeclarations _ _ = return () -prop_checkCatastrophicRm1 = verify checkCatastrophicRm "rm -r $1/$2" -prop_checkCatastrophicRm2 = verify checkCatastrophicRm "rm -r /home/$foo" -prop_checkCatastrophicRm3 = verifyNot checkCatastrophicRm "rm -r /home/${USER:?}/*" -prop_checkCatastrophicRm4 = verify checkCatastrophicRm "rm -fr /home/$(whoami)/*" -prop_checkCatastrophicRm5 = verifyNot checkCatastrophicRm "rm -r /home/${USER:-thing}/*" -prop_checkCatastrophicRm6 = verify checkCatastrophicRm "rm --recursive /etc/*$config*" -prop_checkCatastrophicRm8 = verify checkCatastrophicRm "rm -rf /home" -prop_checkCatastrophicRm9 = verifyNot checkCatastrophicRm "rm -rf -- /home" -prop_checkCatastrophicRm10= verifyNot checkCatastrophicRm "rm -r \"${DIR}\"/{.gitignore,.gitattributes,ci}" -prop_checkCatastrophicRm11= verify checkCatastrophicRm "rm -r /{bin,sbin}/$exec" -prop_checkCatastrophicRm12= verify checkCatastrophicRm "rm -r /{{usr,},{bin,sbin}}/$exec" -prop_checkCatastrophicRm13= verifyNot checkCatastrophicRm "rm -r /{{a,b},{c,d}}/$exec" -prop_checkCatastrophicRmA = verify checkCatastrophicRm "rm -rf /usr /lib/nvidia-current/xorg/xorg" -prop_checkCatastrophicRmB = verify checkCatastrophicRm "rm -rf \"$STEAMROOT/\"*" -checkCatastrophicRm params t@(T_SimpleCommand id _ tokens) | t `isCommand` "rm" = - when (any isRecursiveFlag simpleArgs) $ - mapM_ (mapM_ checkWord . braceExpand) tokens - where - simpleArgs = oversimplify t - - checkWord token = - case getLiteralString token of - Just str -> - when (notElem "--" simpleArgs && (fixPath str `elem` importantPaths)) $ - warn (getId token) 2114 "Warning: deletes a system directory. Use 'rm --' to disable this message." - Nothing -> - checkWord' token - - checkWord' token = fromMaybe (return ()) $ do - filename <- getPotentialPath token - let path = fixPath filename - return . when (path `elem` importantPaths) $ - warn (getId token) 2115 $ "Use \"${var:?}\" to ensure this never expands to " ++ path ++ " ." - - fixPath filename = - let normalized = skipRepeating '/' . skipRepeating '*' $ filename in - if normalized == "/" then normalized else stripTrailing '/' normalized - - getPotentialPath = getLiteralStringExt f - where - f (T_Glob _ str) = return str - f (T_DollarBraced _ word) = - let var = onlyLiteralString word in - if any (`isInfixOf` var) [":?", ":-", ":="] - then Nothing - else return "" - f _ = return "" - - isRecursiveFlag "--recursive" = True - isRecursiveFlag ('-':'-':_) = False - isRecursiveFlag ('-':str) = 'r' `elem` str || 'R' `elem` str - isRecursiveFlag _ = False - - stripTrailing c = reverse . dropWhile (== c) . reverse - skipRepeating c (a:b:rest) | a == b && b == c = skipRepeating c (b:rest) - skipRepeating c (a:r) = a:skipRepeating c r - skipRepeating _ [] = [] - - paths = [ - "", "/bin", "/etc", "/home", "/mnt", "/usr", "/usr/share", "/usr/local", - "/var", "/lib" - ] - importantPaths = filter (not . null) $ - ["", "/", "/*", "/*/*"] >>= (\x -> map (++x) paths) -checkCatastrophicRm _ _ = return () - prop_checkStderrPipe1 = verify checkStderrPipe "#!/bin/ksh\nfoo |& bar" prop_checkStderrPipe2 = verifyNot checkStderrPipe "#!/bin/bash\nfoo |& bar" diff --git a/ShellCheck/Checks/Commands.hs b/ShellCheck/Checks/Commands.hs index 4a17f69..80ffed9 100644 --- a/ShellCheck/Checks/Commands.hs +++ b/ShellCheck/Checks/Commands.hs @@ -86,6 +86,7 @@ commandChecks = [ ,checkDeprecatedEgrep ,checkDeprecatedFgrep ,checkWhileGetoptsCase + ,checkCatastrophicRm ] buildCommandMap :: [CommandCheck] -> Map.Map CommandName (Token -> Analysis) @@ -756,6 +757,65 @@ checkWhileGetoptsCase = CommandCheck (Exactly "getopts") f T_Redirecting _ _ x@(T_CaseExpression {}) -> return x _ -> Nothing +prop_checkCatastrophicRm1 = verify checkCatastrophicRm "rm -r $1/$2" +prop_checkCatastrophicRm2 = verify checkCatastrophicRm "rm -r /home/$foo" +prop_checkCatastrophicRm3 = verifyNot checkCatastrophicRm "rm -r /home/${USER:?}/*" +prop_checkCatastrophicRm4 = verify checkCatastrophicRm "rm -fr /home/$(whoami)/*" +prop_checkCatastrophicRm5 = verifyNot checkCatastrophicRm "rm -r /home/${USER:-thing}/*" +prop_checkCatastrophicRm6 = verify checkCatastrophicRm "rm --recursive /etc/*$config*" +prop_checkCatastrophicRm8 = verify checkCatastrophicRm "rm -rf /home" +prop_checkCatastrophicRm10= verifyNot checkCatastrophicRm "rm -r \"${DIR}\"/{.gitignore,.gitattributes,ci}" +prop_checkCatastrophicRm11= verify checkCatastrophicRm "rm -r /{bin,sbin}/$exec" +prop_checkCatastrophicRm12= verify checkCatastrophicRm "rm -r /{{usr,},{bin,sbin}}/$exec" +prop_checkCatastrophicRm13= verifyNot checkCatastrophicRm "rm -r /{{a,b},{c,d}}/$exec" +prop_checkCatastrophicRmA = verify checkCatastrophicRm "rm -rf /usr /lib/nvidia-current/xorg/xorg" +prop_checkCatastrophicRmB = verify checkCatastrophicRm "rm -rf \"$STEAMROOT/\"*" +checkCatastrophicRm = CommandCheck (Basename "rm") $ \t -> + when (isRecursive t) $ + mapM_ (mapM_ checkWord . braceExpand) $ arguments t + where + isRecursive = any (`elem` ["r", "R", "recursive"]) . map snd . getAllFlags + + checkWord token = + case getLiteralString token of + Just str -> + when (fixPath str `elem` importantPaths) $ + warn (getId token) 2114 "Warning: deletes a system directory." + Nothing -> + checkWord' token + + checkWord' token = fromMaybe (return ()) $ do + filename <- getPotentialPath token + let path = fixPath filename + return . when (path `elem` importantPaths) $ + warn (getId token) 2115 $ "Use \"${var:?}\" to ensure this never expands to " ++ path ++ " ." + + fixPath filename = + let normalized = skipRepeating '/' . skipRepeating '*' $ filename in + if normalized == "/" then normalized else stripTrailing '/' normalized + + getPotentialPath = getLiteralStringExt f + where + f (T_Glob _ str) = return str + f (T_DollarBraced _ word) = + let var = onlyLiteralString word in + -- This shouldn't handle non-colon cases. + if any (`isInfixOf` var) [":?", ":-", ":="] + then Nothing + else return "" + f _ = return "" + + stripTrailing c = reverse . dropWhile (== c) . reverse + skipRepeating c (a:b:rest) | a == b && b == c = skipRepeating c (b:rest) + skipRepeating c (a:r) = a:skipRepeating c r + skipRepeating _ [] = [] + + paths = [ + "", "/bin", "/etc", "/home", "/mnt", "/usr", "/usr/share", "/usr/local", + "/var", "/lib", "/dev", "/media", "/boot", "/lib64", "/usr/bin" + ] + importantPaths = filter (not . null) $ + ["", "/", "/*", "/*/*"] >>= (\x -> map (++x) paths) return [] runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |]) From 505ff7832fb611bc43332bf994be0c2b853e505a Mon Sep 17 00:00:00 2001 From: Vladimir Panteleev Date: Mon, 22 May 2017 05:12:50 +0000 Subject: [PATCH 08/15] Recognize bash's `shopt -s lastpipe` Fixes #732. --- ShellCheck/Analytics.hs | 5 +++-- ShellCheck/AnalyzerLib.hs | 20 ++++++++++++++------ 2 files changed, 17 insertions(+), 8 deletions(-) diff --git a/ShellCheck/Analytics.hs b/ShellCheck/Analytics.hs index 77206e9..b4abc47 100644 --- a/ShellCheck/Analytics.hs +++ b/ShellCheck/Analytics.hs @@ -1521,6 +1521,7 @@ prop_subshellAssignmentCheck15 = verifyNotTree subshellAssignmentCheck "#!/bin/k prop_subshellAssignmentCheck16 = verifyNotTree subshellAssignmentCheck "(set -e); echo $@" prop_subshellAssignmentCheck17 = verifyNotTree subshellAssignmentCheck "foo=${ { bar=$(baz); } 2>&1; }; echo $foo $bar" prop_subshellAssignmentCheck18 = verifyTree subshellAssignmentCheck "( exec {n}>&2; ); echo $n" +prop_subshellAssignmentCheck19 = verifyNotTree subshellAssignmentCheck "#!/bin/bash\nshopt -s lastpipe; echo a | read -r b; echo \"$b\"" subshellAssignmentCheck params t = let flow = variableFlow params check = findSubshelled flow [("oops",[])] Map.empty @@ -2105,7 +2106,7 @@ checkLoopKeywordScope params t | where name = getCommandName t path = let p = getPath (parentMap params) t in filter relevant p - subshellType t = case leadType (shellType params) (parentMap params) t of + subshellType t' = case leadType (shellType params) (parentMap params) t' t of NoneScope -> Nothing SubshellScope str -> return str relevant t = isLoop t || isFunction t || isJust (subshellType t) @@ -2167,7 +2168,7 @@ checkUnpassedInFunctions params root = functions = execWriter $ doAnalysis (tell . maybeToList . findFunction) root findFunction t@(T_Function id _ _ name body) = - let flow = getVariableFlow (shellType params) (parentMap params) body + let flow = getVariableFlow (shellType params) (parentMap params) body root in if any (isPositionalReference t) flow && not (any isPositionalAssignment flow) then return t diff --git a/ShellCheck/AnalyzerLib.hs b/ShellCheck/AnalyzerLib.hs index 605b015..e82949d 100644 --- a/ShellCheck/AnalyzerLib.hs +++ b/ShellCheck/AnalyzerLib.hs @@ -145,7 +145,7 @@ makeParameters spec = shellTypeSpecified = isJust $ asShellType spec, parentMap = getParentTree root, variableFlow = - getVariableFlow (shellType params) (parentMap params) root + getVariableFlow (shellType params) (parentMap params) root root } in params where root = asScript spec @@ -337,18 +337,18 @@ tokenIsJustCommandOutput t = case t of check _ = False -- TODO: Replace this with a proper Control Flow Graph -getVariableFlow shell parents t = +getVariableFlow shell parents t root = let (_, stack) = runState (doStackAnalysis startScope endScope t) [] in reverse stack where startScope t = - let scopeType = leadType shell parents t + let scopeType = leadType shell parents t root in do when (scopeType /= NoneScope) $ modify (StackScope scopeType:) when (assignFirst t) $ setWritten t endScope t = - let scopeType = leadType shell parents t + let scopeType = leadType shell parents t root in do setRead t unless (assignFirst t) $ setWritten t @@ -367,7 +367,7 @@ getVariableFlow shell parents t = in mapM_ (\v -> modify (Assignment v:)) written -leadType shell parents t = +leadType shell parents t root = case t of T_DollarExpansion _ _ -> SubshellScope "$(..) expansion" T_Backticked _ _ -> SubshellScope "`..` expansion" @@ -396,11 +396,19 @@ leadType shell parents t = lastCreatesSubshell = case shell of - Bash -> True + Bash -> not hasShoptLastPipe Dash -> True Sh -> True Ksh -> False + hasShoptLastPipe = isNothing $ doAnalysis (guard . not . isShoptLastPipe) root + isShoptLastPipe t = + case t of + T_SimpleCommand {} -> + t `isUnqualifiedCommand` "shopt" && + ("lastpipe" `elem` oversimplify t) + _ -> False + getModifiedVariables t = case t of T_SimpleCommand _ vars [] -> From 6f4e06d83c00faaed2cd8aebef58a689a828262b Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sun, 28 May 2017 16:04:42 -0700 Subject: [PATCH 09/15] Avoid rescanning tree for lastpipe on every node. --- ShellCheck/Analytics.hs | 17 +++------- ShellCheck/AnalyzerLib.hs | 70 +++++++++++++++++++++++++-------------- 2 files changed, 51 insertions(+), 36 deletions(-) diff --git a/ShellCheck/Analytics.hs b/ShellCheck/Analytics.hs index b4abc47..ad93e79 100644 --- a/ShellCheck/Analytics.hs +++ b/ShellCheck/Analytics.hs @@ -2106,7 +2106,7 @@ checkLoopKeywordScope params t | where name = getCommandName t path = let p = getPath (parentMap params) t in filter relevant p - subshellType t' = case leadType (shellType params) (parentMap params) t' t of + subshellType t = case leadType params t of NoneScope -> Nothing SubshellScope str -> return str relevant t = isLoop t || isFunction t || isJust (subshellType t) @@ -2168,7 +2168,7 @@ checkUnpassedInFunctions params root = functions = execWriter $ doAnalysis (tell . maybeToList . findFunction) root findFunction t@(T_Function id _ _ name body) = - let flow = getVariableFlow (shellType params) (parentMap params) body root + let flow = getVariableFlow params body in if any (isPositionalReference t) flow && not (any isPositionalAssignment flow) then return t @@ -2471,7 +2471,9 @@ prop_checkUncheckedCd6 = verifyNotTree checkUncheckedCd "cd .." prop_checkUncheckedCd7 = verifyNotTree checkUncheckedCd "#!/bin/bash -e\ncd foo\nrm bar" prop_checkUncheckedCd8 = verifyNotTree checkUncheckedCd "set -o errexit; cd foo; rm bar" checkUncheckedCd params root = - if hasSetE then [] else execWriter $ doAnalysis checkElement root + if hasSetE params + then [] + else execWriter $ doAnalysis checkElement root where checkElement t@T_SimpleCommand {} = when(t `isUnqualifiedCommand` "cd" @@ -2480,15 +2482,6 @@ checkUncheckedCd params root = warn (getId t) 2164 "Use 'cd ... || exit' or 'cd ... || return' in case cd fails." checkElement _ = return () isCdDotDot t = oversimplify t == ["cd", ".."] - hasSetE = isNothing $ doAnalysis (guard . not . isSetE) root - isSetE t = - case t of - T_Script _ str _ -> str `matches` re - T_SimpleCommand {} -> - t `isUnqualifiedCommand` "set" && - ("errexit" `elem` oversimplify t || "e" `elem` map snd (getAllFlags t)) - _ -> False - re = mkRegex "[[:space:]]-[^-]*e" prop_checkLoopVariableReassignment1 = verify checkLoopVariableReassignment "for i in *; do for i in *.bar; do true; done; done" prop_checkLoopVariableReassignment2 = verify checkLoopVariableReassignment "for i in *; do for((i=0; i<3; i++)); do true; done; done" diff --git a/ShellCheck/AnalyzerLib.hs b/ShellCheck/AnalyzerLib.hs index e82949d..a119d9b 100644 --- a/ShellCheck/AnalyzerLib.hs +++ b/ShellCheck/AnalyzerLib.hs @@ -72,6 +72,8 @@ composeAnalyzers :: (a -> Analysis) -> (a -> Analysis) -> a -> Analysis composeAnalyzers f g x = f x >> g x data Parameters = Parameters { + hasLastpipe :: Bool, -- Whether this script has the 'lastpipe' option set/default. + hasSetE :: Bool, -- Whether this script has 'set -e' anywhere. variableFlow :: [StackData], -- A linear (bad) analysis of data flow parentMap :: Map.Map Id Token, -- A map from Id to parent Token shellType :: Shell, -- The shell type, such as Bash or Ksh @@ -142,13 +144,48 @@ makeParameters spec = let params = Parameters { rootNode = root, shellType = fromMaybe (determineShell root) $ asShellType spec, + hasSetE = containsSetE root, + hasLastpipe = + case shellType params of + Bash -> containsLastpipe root + Dash -> False + Sh -> False + Ksh -> True, + shellTypeSpecified = isJust $ asShellType spec, parentMap = getParentTree root, - variableFlow = - getVariableFlow (shellType params) (parentMap params) root root + variableFlow = getVariableFlow params root } in params where root = asScript spec + +-- Does this script mention 'set -e' anywhere? +-- Used as a hack to disable certain warnings. +containsSetE root = isNothing $ doAnalysis (guard . not . isSetE) root + where + isSetE t = + case t of + T_Script _ str _ -> str `matches` re + T_SimpleCommand {} -> + t `isUnqualifiedCommand` "set" && + ("errexit" `elem` oversimplify t || + "e" `elem` map snd (getAllFlags t)) + _ -> False + re = mkRegex "[[:space:]]-[^-]*e" + +-- Does this script mention 'shopt -s lastpipe' anywhere? +-- Also used as a hack. +containsLastpipe root = + isNothing $ doAnalysis (guard . not . isShoptLastPipe) root + where + isShoptLastPipe t = + case t of + T_SimpleCommand {} -> + t `isUnqualifiedCommand` "shopt" && + ("lastpipe" `elem` oversimplify t) + _ -> False + + prop_determineShell0 = determineShell (fromJust $ pScript "#!/bin/sh") == Sh prop_determineShell1 = determineShell (fromJust $ pScript "#!/usr/bin/env ksh") == Ksh prop_determineShell2 = determineShell (fromJust $ pScript "") == Bash @@ -337,18 +374,18 @@ tokenIsJustCommandOutput t = case t of check _ = False -- TODO: Replace this with a proper Control Flow Graph -getVariableFlow shell parents t root = +getVariableFlow params t = let (_, stack) = runState (doStackAnalysis startScope endScope t) [] in reverse stack where startScope t = - let scopeType = leadType shell parents t root + let scopeType = leadType params t in do when (scopeType /= NoneScope) $ modify (StackScope scopeType:) when (assignFirst t) $ setWritten t endScope t = - let scopeType = leadType shell parents t root + let scopeType = leadType params t in do setRead t unless (assignFirst t) $ setWritten t @@ -359,7 +396,7 @@ getVariableFlow shell parents t root = assignFirst _ = False setRead t = - let read = getReferencedVariables parents t + let read = getReferencedVariables (parentMap params) t in mapM_ (\v -> modify (Reference v:)) read setWritten t = @@ -367,7 +404,7 @@ getVariableFlow shell parents t root = in mapM_ (\v -> modify (Assignment v:)) written -leadType shell parents t root = +leadType params t = case t of T_DollarExpansion _ _ -> SubshellScope "$(..) expansion" T_Backticked _ _ -> SubshellScope "`..` expansion" @@ -381,7 +418,7 @@ leadType shell parents t root = _ -> NoneScope where parentPipeline = do - parent <- Map.lookup (getId t) parents + parent <- Map.lookup (getId t) (parentMap params) case parent of T_Pipeline {} -> return parent _ -> Nothing @@ -390,25 +427,10 @@ leadType shell parents t root = (T_Pipeline _ _ list) <- parentPipeline if length list <= 1 then return False - else if lastCreatesSubshell + else if not $ hasLastpipe params then return True else return . not $ (getId . head $ reverse list) == getId t - lastCreatesSubshell = - case shell of - Bash -> not hasShoptLastPipe - Dash -> True - Sh -> True - Ksh -> False - - hasShoptLastPipe = isNothing $ doAnalysis (guard . not . isShoptLastPipe) root - isShoptLastPipe t = - case t of - T_SimpleCommand {} -> - t `isUnqualifiedCommand` "shopt" && - ("lastpipe" `elem` oversimplify t) - _ -> False - getModifiedVariables t = case t of T_SimpleCommand _ vars [] -> From f8e75d3e89e9cd22858998681f2d1e94f84736ee Mon Sep 17 00:00:00 2001 From: Royce Remer Date: Sun, 28 Feb 2016 14:28:40 -0800 Subject: [PATCH 10/15] add compilation documentation for test runners --- README.md | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/README.md b/README.md index c4868ea..adcaa87 100644 --- a/README.md +++ b/README.md @@ -154,6 +154,10 @@ Verify that `cabal` is installed and update its dependency list with $ cabal install +Or if you intend to run the tests: + + $ cabal install --enable-tests + This will compile ShellCheck and install it to your `~/.cabal/bin` directory. Add this directory to your `PATH` (for bash, add this to your `~/.bashrc`): From ce950edbfded8e0cea0b78d424cd05f9f7e08d02 Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sat, 3 Jun 2017 09:38:47 -0700 Subject: [PATCH 11/15] Don't trigger SC2026 when followed by empty literals (#923) --- ShellCheck/Analytics.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/ShellCheck/Analytics.hs b/ShellCheck/Analytics.hs index ad93e79..f850275 100644 --- a/ShellCheck/Analytics.hs +++ b/ShellCheck/Analytics.hs @@ -1369,10 +1369,11 @@ prop_checkInexplicablyUnquoted4 = verify checkInexplicablyUnquoted "echo \"VALUE prop_checkInexplicablyUnquoted5 = verifyNot checkInexplicablyUnquoted "\"$dir\"/\"$file\"" prop_checkInexplicablyUnquoted6 = verifyNot checkInexplicablyUnquoted "\"$dir\"some_stuff\"$file\"" prop_checkInexplicablyUnquoted7 = verifyNot checkInexplicablyUnquoted "${dir/\"foo\"/\"bar\"}" +prop_checkInexplicablyUnquoted8 = verifyNot checkInexplicablyUnquoted " 'foo'\\\n 'bar'" checkInexplicablyUnquoted _ (T_NormalWord id tokens) = mapM_ check (tails tokens) where check (T_SingleQuoted _ _:T_Literal id str:_) - | all isAlphaNum str = + | not (null str) && all isAlphaNum str = info id 2026 "This word is outside of quotes. Did you intend to 'nest '\"'single quotes'\"' instead'? " check (T_DoubleQuoted _ a:trapped:T_DoubleQuoted _ b:_) = From 50c8172de4ddc4e8d9ca8128796cba11fd9e2601 Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sat, 3 Jun 2017 11:45:25 -0700 Subject: [PATCH 12/15] Allow escaping ( with quotes in [ .. ] (#925) --- ShellCheck/Parser.hs | 75 ++++++++++++++++++++++++-------------------- 1 file changed, 41 insertions(+), 34 deletions(-) diff --git a/ShellCheck/Parser.hs b/ShellCheck/Parser.hs index cc63e4e..fb198f5 100644 --- a/ShellCheck/Parser.hs +++ b/ShellCheck/Parser.hs @@ -440,19 +440,9 @@ readConditionContents single = getOp = do id <- getNextId - op <- anyQuotedOp <|> anyEscapedOp <|> anyOp + op <- readRegularOrEscaped anyOp return $ TC_Binary id typ op - -- hacks to read quoted operators without having to read a shell word - anyEscapedOp = try $ do - char '\\' - escaped <$> anyOp - anyQuotedOp = try $ do - c <- oneOf "'\"" - s <- anyOp - char c - return $ escaped s - anyOp = flagOp <|> flaglessOp <|> fail "Expected comparison operator (don't wrap commands in []/[[]])" flagOp = try $ do @@ -461,7 +451,22 @@ readConditionContents single = return s flaglessOp = choice $ map (try . string) flaglessOps - escaped s = if any (`elem` s) "<>" then '\\':s else s + + -- hacks to read quoted operators without having to read a shell word + readEscaped p = try $ withEscape <|> withQuotes + where + withEscape = do + char '\\' + escaped <$> p + withQuotes = do + c <- oneOf "'\"" + s <- p + char c + return $ escaped s + escaped s = if any (`elem` s) "<>()" then '\\':s else s + + readRegularOrEscaped p = readEscaped p <|> p + guardArithmetic = do try . lookAhead $ disregard (oneOf "+*/%") <|> disregard (string "- ") @@ -560,29 +565,30 @@ readConditionContents single = "You need a space before and after the " ++ trailingOp ++ " ." readCondGroup = do - id <- getNextId - pos <- getPosition - lparen <- try $ string "(" <|> string "\\(" - when (single && lparen == "(") $ - parseProblemAt pos ErrorC 1028 "In [..] you have to escape (). Use [[..]] instead." - when (not single && lparen == "\\(") $ - parseProblemAt pos ErrorC 1029 "In [[..]] you shouldn't escape ()." - condSpacing single - x <- readCondContents - cpos <- getPosition - rparen <- string ")" <|> string "\\)" - condSpacing single - when (single && rparen == ")") $ - parseProblemAt cpos ErrorC 1030 "In [..] you have to escape (). Use [[..]] instead." - when (not single && rparen == "\\)") $ - parseProblemAt cpos ErrorC 1031 "In [[..]] you shouldn't escape ()." - when (isEscaped lparen `xor` isEscaped rparen) $ - parseProblemAt pos ErrorC 1032 "Did you just escape one half of () but not the other?" - return $ TC_Group id typ x + id <- getNextId + pos <- getPosition + lparen <- try $ readRegularOrEscaped (string "(") + when (single && lparen == "(") $ + singleWarning pos + when (not single && lparen == "\\(") $ + doubleWarning pos + condSpacing single + x <- readCondContents + cpos <- getPosition + rparen <- readRegularOrEscaped (string ")") + condSpacing single + when (single && rparen == ")") $ + singleWarning cpos + when (not single && rparen == "\\)") $ + doubleWarning cpos + return $ TC_Group id typ x + where - isEscaped ('\\':_) = True - isEscaped _ = False - xor x y = x && not y || not x && y + singleWarning pos = + parseProblemAt pos ErrorC 1028 "In [..] you have to escape \\( \\) or preferably combine [..] expressions." + doubleWarning pos = + parseProblemAt pos ErrorC 1029 "In [[..]] you shouldn't escape ( or )." + -- Currently a bit of a hack since parsing rules are obscure regexOperatorAhead = lookAhead (do @@ -849,6 +855,7 @@ prop_readCondition15= isOk readCondition "[ foo \">=\" bar ]" prop_readCondition16= isOk readCondition "[ foo \\< bar ]" prop_readCondition17= isOk readCondition "[[ ${file::1} = [-.\\|/\\\\] ]]" prop_readCondition18= isOk readCondition "[ ]" +prop_readCondition19= isOk readCondition "[ '(' x \")\" ]" readCondition = called "test expression" $ do opos <- getPosition id <- getNextId From 5cece759cc5572715b11da28da66429e6806eb29 Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Fri, 9 Jun 2017 19:41:57 -0700 Subject: [PATCH 13/15] Autobuild Windows .exe files --- .travis.yml | 28 ++++++++++++++++++++++++++-- 1 file changed, 26 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index 7884805..0234368 100644 --- a/.travis.yml +++ b/.travis.yml @@ -11,11 +11,35 @@ before_install: export TAG=$([ "$TRAVIS_BRANCH" == "master" ] && echo "latest" || ([ -n "$TRAVIS_TAG" ] && echo "$TRAVIS_TAG") || echo "$TRAVIS_BRANCH") script: + - mkdir deploy + # Windows .exe + - rm -rf dist cabal || true + - docker pull koalaman/winghc + - docker run -v "$PWD:/appdata" koalaman/winghc cuib + - cp "dist/build/ShellCheck/shellcheck.exe" "deploy/windows-$TAG.exe" + # Linux Docker - docker build -t builder -f Dockerfile_builder . - - docker run --rm -it -v $(pwd):/mnt builder - - docker build -t $DOCKER_REPO:$TAG . + - docker run --rm -it -v "$(pwd):/mnt" builder + - docker build -t "$DOCKER_REPO:$TAG" . after_success: - docker login -e="$DOCKER_EMAIL" -u="$DOCKER_USERNAME" -p="$DOCKER_PASSWORD" - |- ([ "$TRAVIS_BRANCH" == "master" ] || [ -n "$TRAVIS_TAG" ]) && docker push "$DOCKER_REPO:$TAG" + +after_failure: + - pwd + - df -h + - find . -name '*.log' -type f -exec grep "" /dev/null {} + + - find . + +deploy: + provider: gcs + skip_cleanup: true + access_key_id: GOOG7MDN7WEH6IIGBDCA + secret_access_key: + secure: Bcx2cT0/E2ikj7sdamVq52xlLZF9dz9ojGPtoKfPyQhkkZa+McVI4xgUSuyyoSxyKj77sofx2y8m6PJYYumT4g5hREV1tfeUkl0J2DQFMbGDYEt7kxVkXCxojNvhHwTzLFv0ezstrxWWxQm81BfQQ4U9lggRXtndAP4czZnOeHPINPSiue1QNwRAEw05r5UoIUJXy/5xyUrjIxn381pAs+gJqP2COeN9kTKYH53nS/AAws29RprfZFnPlo7xxWmcjRcdS5KPdGXI/c6tQp5zl2iTh510VC1PN2w1Wvnn/oNWhiNdqPyVDsojIX5+sS3nejzJA+KFMxXSBlyXIY3wPpS/MdscU79X6Q5f9ivsFfsm7gNBmxHUPNn0HAvU4ROT/CCE9j6jSbs5PC7QBo3CK4++jxAwE/pd9HUc2rs3k0ofx3rgveJ7txpy5yPKfwIIBi98kVKlC4w7dLvNTOfjW1Imt2yH87XTfsE0UIG9st1WII6s4l/WgBx2GuwKdt6+3QUYiAlCFckkxWi+fAvpHZUEL43Qxub5fN+ZV7Zib1n7opchH4QKGBb6/y0WaDCmtCfu0lppoe/TH6saOTjDFj67NJSElK6ZDxGZ3uw4R+ret2gm6WRKT2Oeub8J33VzSa7VkmFpMPrAAfPa9N1Z4ewBLoTmvxSg2A0dDrCdJio= + bucket: shellcheck + local-dir: deploy + on: + repo: koalaman/shellcheck From 5fad708df581fd60caf08fe9eebe9482d227df88 Mon Sep 17 00:00:00 2001 From: Vidar Holen Date: Sat, 10 Jun 2017 09:26:08 -0700 Subject: [PATCH 14/15] Zip compiled Windows executables. --- .prepare_deploy | 34 ++++++++++++++++++++++++++++++++++ .travis.yml | 4 ++-- 2 files changed, 36 insertions(+), 2 deletions(-) create mode 100755 .prepare_deploy diff --git a/.prepare_deploy b/.prepare_deploy new file mode 100755 index 0000000..41db852 --- /dev/null +++ b/.prepare_deploy @@ -0,0 +1,34 @@ +#!/bin/bash +# This script packages up Travis compiled binaries +set -ex +shopt -s nullglob +cd deploy + +cp ../LICENSE LICENSE.txt +sed -e $'s/$/\r/' > README.txt << END +This is a precompiled ShellCheck binary. + http://www.shellcheck.net/ + +ShellCheck is a static analysis tool for shell scripts. +It's licensed under the GNU General Public License v3.0. +Information and source code is available on the website. + +This binary was compiled on $(date -u). + + + + ====== Latest commits ====== + +$(git log -n 3) +END + +for file in ./*.exe +do + zip "${file%.*}.zip" README.txt LICENSE.txt "$file" +done + +for file in ./* +do + sha512sum "$file" > "$file.sha512sum" +done + diff --git a/.travis.yml b/.travis.yml index 0234368..b09848d 100644 --- a/.travis.yml +++ b/.travis.yml @@ -13,16 +13,16 @@ before_install: script: - mkdir deploy # Windows .exe - - rm -rf dist cabal || true - docker pull koalaman/winghc - docker run -v "$PWD:/appdata" koalaman/winghc cuib - - cp "dist/build/ShellCheck/shellcheck.exe" "deploy/windows-$TAG.exe" + - cp "dist/build/ShellCheck/shellcheck.exe" "deploy/shellcheck-$TAG.exe" # Linux Docker - docker build -t builder -f Dockerfile_builder . - docker run --rm -it -v "$(pwd):/mnt" builder - docker build -t "$DOCKER_REPO:$TAG" . after_success: + - ./.prepare_deploy - docker login -e="$DOCKER_EMAIL" -u="$DOCKER_USERNAME" -p="$DOCKER_PASSWORD" - |- ([ "$TRAVIS_BRANCH" == "master" ] || [ -n "$TRAVIS_TAG" ]) && docker push "$DOCKER_REPO:$TAG" From bf9b841b07a440aeceb68b00a5465f5eb2d9cc8a Mon Sep 17 00:00:00 2001 From: koalaman Date: Sat, 10 Jun 2017 10:10:09 -0700 Subject: [PATCH 15/15] Link to Windows executables in the Readme --- README.md | 8 ++------ 1 file changed, 2 insertions(+), 6 deletions(-) diff --git a/README.md b/README.md index adcaa87..9ad48fc 100644 --- a/README.md +++ b/README.md @@ -25,7 +25,7 @@ There are a variety of ways to use ShellCheck! #### On the web Paste a shell script on http://www.shellcheck.net for instant feedback. -[ShellCheck.net](http://www.shellcheck.net) is always synchronized to the latest git commit, and is the simplest way to give ShellCheck a go. Tell your friends! +[ShellCheck.net](http://www.shellcheck.net) is always synchronized to the latest git commit, and is the easiest way to give ShellCheck a go. Tell your friends! #### From your terminal @@ -126,13 +126,9 @@ or use OneClickInstall - https://software.opensuse.org/package/ShellCheck From Docker Hub: docker pull koalaman/shellcheck - -Using the Docker image can be done like so: - docker run -v "$PWD:/mnt" koalaman/shellcheck myscript -Here the current directory `$PWD` is mounted as the container's directory `/mnt`, which is ShellCheck's working directory in the image. The script `myscript` is checked. - +For Windows, you can download [precompiled Windows executables](https://storage.googleapis.com/shellcheck/shellcheck-latest.zip). ## Compiling from source This section describes how to build ShellCheck from a source directory. ShellCheck is written in Haskell and requires 2GB of RAM to compile.