From 1e32139f6618953d60ce81860a3319062c92129b Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 19:18:43 -0500 Subject: [PATCH 01/26] Replace mapMaybe and concatMap with list comprehensions --- src/ShellCheck/Analytics.hs | 11 ++--------- 1 file changed, 2 insertions(+), 9 deletions(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index 8a2902c..c58e97a 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -87,13 +87,8 @@ runList spec list = notes getEnableDirectives root = case root of - T_Annotation _ list _ -> mapMaybe getEnable list + T_Annotation _ list _ -> [s | EnableComment s <- list] _ -> [] - where - getEnable t = - case t of - EnableComment s -> return s - _ -> Nothing checkList l t = concatMap (\f -> f t) l @@ -3123,9 +3118,7 @@ checkUnmatchableCases params t = Just l -> " on line " <> show l <> "." _ -> "." - valids = concatMap f rest - f (x, Just y) = [(x,y)] - f _ = [] + valids = [(x,y) | (x, Just y) <- rest] checkDoms _ = return () From cb01cbf7eb3428e08a79bcc40ce4f54e4d1b3c7b Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 19:33:36 -0500 Subject: [PATCH 02/26] Use mapM instead of implementing a slower version of it --- 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 c58e97a..e91810b 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -431,7 +431,7 @@ checkWrongArithmeticAssignment params (T_SimpleCommand id (T_Assignment _ _ _ _ insertRef _ = Prelude.id getNormalString (T_NormalWord _ words) = do - parts <- foldl (liftM2 (\x y -> x ++ [y])) (Just []) $ map getLiterals words + parts <- mapM getLiterals words return $ concat parts getNormalString _ = Nothing From cc424bac11864e5c445b18490e0507457b86b5a5 Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 19:40:57 -0500 Subject: [PATCH 03/26] Use find instead of take 1 and filter --- src/ShellCheck/Analytics.hs | 6 +++--- src/ShellCheck/Checks/Commands.hs | 2 +- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index e91810b..fa640b1 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -790,7 +790,7 @@ prop_checkUnquotedDollarAt8 = verifyNot checkUnquotedDollarAt "echo \"${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 -> + forM_ (find isArrayExpansion parts) $ \x -> unless (isQuotedAlternativeReference x) $ err (getId x) 2068 "Double quote array expansions to avoid re-splitting elements." @@ -807,7 +807,7 @@ checkConcatenatedDollarAt p word@T_NormalWord {} mapM_ for array where parts = getWordParts word - array = take 1 $ filter isArrayExpansion parts + array = find isArrayExpansion parts for t = err (getId t) 2145 "Argument mixes string and array. Use * or separate argument." checkConcatenatedDollarAt _ _ = return () @@ -1059,7 +1059,7 @@ checkNumberComparisons params (TC_Binary id typ op lhs rhs) = do "Either use integers only, or use bc or awk to compare." checkStrings = - mapM_ stringError . take 1 . filter isNonNum + mapM_ stringError . find isNonNum isNonNum t = fromMaybe False $ do s <- getLiteralStringExt (const $ return "") t diff --git a/src/ShellCheck/Checks/Commands.hs b/src/ShellCheck/Checks/Commands.hs index 299a335..881dd9d 100644 --- a/src/ShellCheck/Checks/Commands.hs +++ b/src/ShellCheck/Checks/Commands.hs @@ -748,7 +748,7 @@ checkAliasesExpandEarly = CommandCheck (Exactly "alias") (f . arguments) where f = mapM_ checkArg checkArg arg | '=' `elem` concat (oversimplify arg) = - forM_ (take 1 $ filter (not . isLiteral) $ getWordParts arg) $ + forM_ (find (not . isLiteral) $ getWordParts arg) $ \x -> warn (getId x) 2139 "This expands when defined, not when used. Consider escaping." checkArg _ = return () From ffbbfcfe25a9d03fde4ce6f65e0fb0852d3bc6e6 Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 19:53:18 -0500 Subject: [PATCH 04/26] Use mapM_ and sequence_ instead of reimplementing them --- src/ShellCheck/ASTLib.hs | 2 +- src/ShellCheck/Analytics.hs | 12 +++++------- src/ShellCheck/Checks/Commands.hs | 6 +++--- src/ShellCheck/Parser.hs | 2 +- 4 files changed, 10 insertions(+), 12 deletions(-) diff --git a/src/ShellCheck/ASTLib.hs b/src/ShellCheck/ASTLib.hs index 03a2f9a..2e08f4d 100644 --- a/src/ShellCheck/ASTLib.hs +++ b/src/ShellCheck/ASTLib.hs @@ -382,7 +382,7 @@ getAssociativeArrays t = nub . execWriter $ doAnalysis f t where f :: Token -> Writer [String] () - f t@T_SimpleCommand {} = fromMaybe (return ()) $ do + f t@T_SimpleCommand {} = sequence_ $ do name <- getCommandName t let assocNames = ["declare","local","typeset"] guard $ elem name assocNames diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index fa640b1..b4b3096 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -404,7 +404,7 @@ prop_checkArithmeticOpCommand1 = verify checkArithmeticOpCommand "i=i + 1" prop_checkArithmeticOpCommand2 = verify checkArithmeticOpCommand "foo=bar * 2" prop_checkArithmeticOpCommand3 = verifyNot checkArithmeticOpCommand "foo + opts" checkArithmeticOpCommand _ (T_SimpleCommand id [T_Assignment {}] (firstWord:_)) = - maybe (return ()) check $ getGlobOrLiteralString firstWord + mapM_ check $ getGlobOrLiteralString firstWord where check op = when (op `elem` ["+", "-", "*", "/"]) $ @@ -415,7 +415,7 @@ checkArithmeticOpCommand _ _ = return () prop_checkWrongArit = verify checkWrongArithmeticAssignment "i=i+1" prop_checkWrongArit2 = verify checkWrongArithmeticAssignment "n=2; i=n*2" checkWrongArithmeticAssignment params (T_SimpleCommand id (T_Assignment _ _ _ _ val:[]) []) = - fromMaybe (return ()) $ do + sequence_ $ do str <- getNormalString val match <- matchRegex regex str var <- match !!! 0 @@ -2524,7 +2524,7 @@ checkUnpassedInFunctions params root = referenceList :: [(String, Bool, Token)] referenceList = execWriter $ - doAnalysis (fromMaybe (return ()) . checkCommand) root + doAnalysis (sequence_ . checkCommand) root checkCommand :: Token -> Maybe (Writer [(String, Bool, Token)] ()) checkCommand t@(T_SimpleCommand _ _ (cmd:args)) = do str <- getLiteralString cmd @@ -2648,9 +2648,7 @@ prop_checkSuspiciousIFS1 = verify checkSuspiciousIFS "IFS=\"\\n\"" prop_checkSuspiciousIFS2 = verifyNot checkSuspiciousIFS "IFS=$'\\t'" prop_checkSuspiciousIFS3 = verify checkSuspiciousIFS "IFS=' \\t\\n'" checkSuspiciousIFS params (T_Assignment _ _ "IFS" [] value) = - potentially $ do - str <- getLiteralString value - return $ check str + mapM_ check $ getLiteralString value where hasDollarSingle = shellType params == Bash || shellType params == Ksh n = if hasDollarSingle then "$'\\n'" else "''" @@ -3465,7 +3463,7 @@ prop_checkTranslatedStringVariable3 = verifyNot checkTranslatedStringVariable "$ prop_checkTranslatedStringVariable4 = verifyNot checkTranslatedStringVariable "var=val; $\"$var\"" prop_checkTranslatedStringVariable5 = verifyNot checkTranslatedStringVariable "foo=var; bar=val2; $\"foo bar\"" checkTranslatedStringVariable params (T_DollarDoubleQuoted id [T_Literal _ s]) = - fromMaybe (return ()) $ do + sequence_ $ do guard $ all isVariableChar s Map.lookup s assignments return $ diff --git a/src/ShellCheck/Checks/Commands.hs b/src/ShellCheck/Checks/Commands.hs index 881dd9d..4842341 100644 --- a/src/ShellCheck/Checks/Commands.hs +++ b/src/ShellCheck/Checks/Commands.hs @@ -122,7 +122,7 @@ buildCommandMap = foldl' addCheck Map.empty checkCommand :: Map.Map CommandName (Token -> Analysis) -> Token -> Analysis -checkCommand map t@(T_SimpleCommand id cmdPrefix (cmd:rest)) = fromMaybe (return ()) $ do +checkCommand map t@(T_SimpleCommand id cmdPrefix (cmd:rest)) = sequence_ $ do name <- getLiteralString cmd return $ if '/' `elem` name @@ -575,7 +575,7 @@ checkPrintfVar = CommandCheck (Exactly "printf") (f . arguments) where f _ = return () check format more = do - fromMaybe (return ()) $ do + sequence_ $ do string <- getLiteralString format let formats = getPrintfFormats string let formatCount = length formats @@ -945,7 +945,7 @@ checkCatastrophicRm = CommandCheck (Basename "rm") $ \t -> Nothing -> checkWord' token - checkWord' token = fromMaybe (return ()) $ do + checkWord' token = sequence_ $ do filename <- getPotentialPath token let path = fixPath filename return . when (path `elem` importantPaths) $ diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index 025fa98..30529e0 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -586,7 +586,7 @@ readConditionContents single = return $ TC_Nullary id typ x ) - checkTrailingOp x = fromMaybe (return ()) $ do + checkTrailingOp x = sequence_ $ do (T_Literal id str) <- getTrailingUnquotedLiteral x trailingOp <- find (`isSuffixOf` str) binaryTestOps return $ parseProblemAtId id ErrorC 1108 $ From 4bfe6496d94786ebd8c234638aee89622cc4868a Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 20:09:25 -0500 Subject: [PATCH 05/26] Simplify check and checkTranslatedStringVariable Avoid the "potentially" and "Maybe" business, and just use regular guards. --- src/ShellCheck/Analytics.hs | 29 +++++++++++++---------------- 1 file changed, 13 insertions(+), 16 deletions(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index b4b3096..91345ed 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -2933,16 +2933,15 @@ checkTrailingBracket _ token = T_SimpleCommand _ _ tokens@(_:_) -> check (last tokens) token _ -> return () where - check t command = - case t of - T_NormalWord id [T_Literal _ str] -> potentially $ do - guard $ str `elem` [ "]]", "]" ] - let opposite = invert str - parameters = oversimplify command - guard $ opposite `notElem` parameters - return $ warn id 2171 $ - "Found trailing " ++ str ++ " outside test. Add missing " ++ opposite ++ " or quote if intentional." - _ -> return () + check (T_NormalWord id [T_Literal _ str]) command + | str `elem` [ "]]", "]" ] + && opposite `notElem` parameters + = warn id 2171 $ + "Found trailing " ++ str ++ " outside test. Add missing " ++ opposite ++ " or quote if intentional." + where + opposite = invert str + parameters = oversimplify command + check _ _ = return () invert s = case s of "]]" -> "[[" @@ -3462,12 +3461,10 @@ prop_checkTranslatedStringVariable2 = verifyNot checkTranslatedStringVariable "$ prop_checkTranslatedStringVariable3 = verifyNot checkTranslatedStringVariable "$\"..\"" prop_checkTranslatedStringVariable4 = verifyNot checkTranslatedStringVariable "var=val; $\"$var\"" prop_checkTranslatedStringVariable5 = verifyNot checkTranslatedStringVariable "foo=var; bar=val2; $\"foo bar\"" -checkTranslatedStringVariable params (T_DollarDoubleQuoted id [T_Literal _ s]) = - sequence_ $ do - guard $ all isVariableChar s - Map.lookup s assignments - return $ - warnWithFix id 2256 "This translated string is the name of a variable. Flip leading $ and \" if this should be a quoted substitution." (fix id) +checkTranslatedStringVariable params (T_DollarDoubleQuoted id [T_Literal _ s]) + | all isVariableChar s + && Map.member s assignments + = warnWithFix id 2256 "This translated string is the name of a variable. Flip leading $ and \" if this should be a quoted substitution." (fix id) where assignments = foldl (flip ($)) Map.empty (map insertAssignment $ variableFlow params) insertAssignment (Assignment (_, token, name, _)) | isVariableName name = From 7e6a556ef155bb50f554235b93097928145dc74e Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 20:10:09 -0500 Subject: [PATCH 06/26] Get rid of potentially This already exists as sequence_. --- src/ShellCheck/Analytics.hs | 38 +++++++++++++-------------- src/ShellCheck/AnalyzerLib.hs | 9 ------- src/ShellCheck/Checks/Commands.hs | 18 ++++++------- src/ShellCheck/Checks/ShellSupport.hs | 8 +++--- 4 files changed, 32 insertions(+), 41 deletions(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index 91345ed..4100b2d 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -1209,7 +1209,7 @@ prop_checkLiteralBreakingTest6 = verify checkLiteralBreakingTest "[ -z $(true)z prop_checkLiteralBreakingTest7 = verifyNot checkLiteralBreakingTest "[ -z $(true) ]" prop_checkLiteralBreakingTest8 = verifyNot checkLiteralBreakingTest "[ $(true)$(true) ]" prop_checkLiteralBreakingTest10 = verify checkLiteralBreakingTest "[ -z foo ]" -checkLiteralBreakingTest _ t = potentially $ +checkLiteralBreakingTest _ t = sequence_ $ case t of (TC_Nullary _ _ w@(T_NormalWord _ l)) -> do guard . not $ isConstant w -- Covered by SC2078 @@ -1257,7 +1257,7 @@ checkConstantNullary _ _ = return () prop_checkForDecimals1 = verify checkForDecimals "((3.14*c))" prop_checkForDecimals2 = verify checkForDecimals "foo[1.2]=bar" prop_checkForDecimals3 = verifyNot checkForDecimals "declare -A foo; foo[1.2]=bar" -checkForDecimals params t@(TA_Expansion id _) = potentially $ do +checkForDecimals params t@(TA_Expansion id _) = sequence_ $ do guard $ not (hasFloatingPoint params) str <- getLiteralString t first <- str !!! 0 @@ -1310,7 +1310,7 @@ checkArithmeticDeref _ _ = return () prop_checkArithmeticBadOctal1 = verify checkArithmeticBadOctal "(( 0192 ))" prop_checkArithmeticBadOctal2 = verifyNot checkArithmeticBadOctal "(( 0x192 ))" prop_checkArithmeticBadOctal3 = verifyNot checkArithmeticBadOctal "(( 1 ^ 0777 ))" -checkArithmeticBadOctal _ t@(TA_Expansion id _) = potentially $ do +checkArithmeticBadOctal _ t@(TA_Expansion id _) = sequence_ $ do str <- getLiteralString t guard $ str `matches` octalRE return $ err id 2080 "Numbers with leading 0 are considered octal." @@ -1392,7 +1392,7 @@ checkOrNeq _ (TA_Binary id "||" (TA_Binary _ "!=" word1 _) (TA_Binary _ "!=" wor 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 +checkOrNeq _ (T_OrIf id lhs rhs) = sequence_ $ do (lhs1, op1, rhs1) <- getExpr lhs (lhs2, op2, rhs2) <- getExpr rhs guard $ op1 == op2 && op1 `elem` ["-ne", "!="] @@ -1407,7 +1407,7 @@ checkOrNeq _ (T_OrIf id lhs rhs) = potentially $ do T_Redirecting _ _ c -> getExpr c T_Condition _ _ c -> getExpr c TC_Binary _ _ op lhs rhs -> return (lhs, op, rhs) - _ -> fail "" + _ -> Nothing checkOrNeq _ _ = return () @@ -2068,7 +2068,7 @@ checkFunctionsUsedExternally params t = in when ('=' `elem` string) $ modify ((takeWhile (/= '=') string, getId arg):) - checkArg cmd (_, arg) = potentially $ do + checkArg cmd (_, arg) = sequence_ $ do literalArg <- getUnquotedLiteral arg -- only consider unquoted literals definitionId <- Map.lookup literalArg functions return $ do @@ -2312,7 +2312,7 @@ checkWhileReadPitfalls _ (T_WhileExpression id [command] contents) (T_IfExpression _ thens elses) -> mapM_ checkMuncher . concat $ map fst thens ++ map snd thens ++ [elses] - _ -> potentially $ do + _ -> sequence_ $ do name <- getCommandBasename cmd guard $ name `elem` munchers @@ -2410,7 +2410,7 @@ checkCdAndBack params t = else findCdPair (b:rest) _ -> Nothing - doList list = potentially $ do + doList list = sequence_ $ do cd <- findCdPair $ mapMaybe getCandidate list return $ info cd 2103 "Use a ( subshell ) to avoid having to cd back." @@ -2673,7 +2673,7 @@ prop_checkGrepQ4= verifyNot checkShouldUseGrepQ "[ -z $(grep bar | cmd) ]" prop_checkGrepQ5= verifyNot checkShouldUseGrepQ "rm $(ls | grep file)" prop_checkGrepQ6= verifyNot checkShouldUseGrepQ "[[ -n $(pgrep foo) ]]" checkShouldUseGrepQ params t = - potentially $ case t of + sequence_ $ case t of TC_Nullary id _ token -> check id True token TC_Unary id _ "-n" token -> check id True token TC_Unary id _ "-z" token -> check id False token @@ -2807,7 +2807,7 @@ prop_checkMaskedReturns2 = verify checkMaskedReturns "declare a=$(false)" prop_checkMaskedReturns3 = verify checkMaskedReturns "declare a=\"`false`\"" prop_checkMaskedReturns4 = verifyNot checkMaskedReturns "declare a; a=$(false)" prop_checkMaskedReturns5 = verifyNot checkMaskedReturns "f() { local -r a=$(false); }" -checkMaskedReturns _ t@(T_SimpleCommand id _ (cmd:rest)) = potentially $ do +checkMaskedReturns _ t@(T_SimpleCommand id _ (cmd:rest)) = sequence_ $ do name <- getCommandName t guard $ name `elem` ["declare", "export"] || name == "local" && "r" `notElem` map snd (getAllFlags t) @@ -2900,7 +2900,7 @@ prop_checkLoopVariableReassignment1 = verify checkLoopVariableReassignment "for prop_checkLoopVariableReassignment2 = verify checkLoopVariableReassignment "for i in *; do for((i=0; i<3; i++)); do true; done; done" prop_checkLoopVariableReassignment3 = verifyNot checkLoopVariableReassignment "for i in *; do for j in *.bar; do true; done; done" checkLoopVariableReassignment params token = - potentially $ case token of + sequence_ $ case token of T_ForIn {} -> check T_ForArithmetic {} -> check _ -> Nothing @@ -2988,12 +2988,12 @@ prop_checkRedirectedNowhere7 = verifyNot checkRedirectedNowhere "var=$(< file)" prop_checkRedirectedNowhere8 = verifyNot checkRedirectedNowhere "var=`< file`" checkRedirectedNowhere params token = case token of - T_Pipeline _ _ [single] -> potentially $ do + T_Pipeline _ _ [single] -> sequence_ $ do redir <- getDanglingRedirect single guard . not $ isInExpansion token return $ warn (getId redir) 2188 "This redirection doesn't have a command. Move to its command (or use 'true' as no-op)." - T_Pipeline _ _ list -> forM_ list $ \x -> potentially $ do + T_Pipeline _ _ list -> forM_ list $ \x -> sequence_ $ do redir <- getDanglingRedirect x return $ err (getId redir) 2189 "You can't have | between this redirection and the command it should apply to." @@ -3080,7 +3080,7 @@ checkUnmatchableCases params t = if isConstant word then warn (getId word) 2194 "This word is constant. Did you forget the $ on a variable?" - else potentially $ do + else sequence_ $ do pg <- wordToPseudoGlob word return $ mapM_ (check pg) allpatterns @@ -3095,7 +3095,7 @@ checkUnmatchableCases params t = fst3 (x,_,_) = x snd3 (_,x,_) = x tp = tokenPositions params - check target candidate = potentially $ do + check target candidate = sequence_ $ do candidateGlob <- wordToPseudoGlob candidate guard . not $ pseudoGlobsCanOverlap target candidateGlob return $ warn (getId candidate) 2195 @@ -3189,7 +3189,7 @@ prop_checkRedirectionToNumber2 = verify checkRedirectionToNumber "foo 1>2" prop_checkRedirectionToNumber3 = verifyNot checkRedirectionToNumber "echo foo > '2'" prop_checkRedirectionToNumber4 = verifyNot checkRedirectionToNumber "foo 1>&2" checkRedirectionToNumber _ t = case t of - T_IoFile id _ word -> potentially $ do + T_IoFile id _ word -> sequence_ $ do file <- getUnquotedLiteral word guard $ all isDigit file return $ warn id 2210 "This is a file redirection. Was it supposed to be a comparison or fd operation?" @@ -3238,7 +3238,7 @@ checkPipeToNowhere _ t = T_Redirecting _ redirects cmd -> when (any redirectsStdin redirects) $ checkRedir cmd _ -> return () where - checkPipe redir = potentially $ do + checkPipe redir = sequence_ $ do cmd <- getCommand redir name <- getCommandBasename cmd guard $ name `elem` nonReadingCommands @@ -3251,7 +3251,7 @@ checkPipeToNowhere _ t = return $ warn (getId cmd) 2216 $ "Piping to '" ++ name ++ "', a command that doesn't read stdin. " ++ suggestion - checkRedir cmd = potentially $ do + checkRedir cmd = sequence_ $ do name <- getCommandBasename cmd guard $ name `elem` nonReadingCommands guard . not $ hasAdditionalConsumers cmd @@ -3299,7 +3299,7 @@ checkUseBeforeDefinition _ t = mapM_ (checkUsage m) $ concatMap recursiveSequences cmds _ -> return () - checkUsage map cmd = potentially $ do + checkUsage map cmd = sequence_ $ do name <- getCommandName cmd def <- Map.lookup name map return $ diff --git a/src/ShellCheck/AnalyzerLib.hs b/src/ShellCheck/AnalyzerLib.hs index e4640e7..69eaf63 100644 --- a/src/ShellCheck/AnalyzerLib.hs +++ b/src/ShellCheck/AnalyzerLib.hs @@ -870,15 +870,6 @@ getBracedModifier s = fromMaybe "" . listToMaybe $ do -- 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 diff --git a/src/ShellCheck/Checks/Commands.hs b/src/ShellCheck/Checks/Commands.hs index 4842341..97de0f6 100644 --- a/src/ShellCheck/Checks/Commands.hs +++ b/src/ShellCheck/Checks/Commands.hs @@ -270,7 +270,7 @@ checkGrepRe = CommandCheck (Basename "grep") check where let string = concat $ oversimplify re if isConfusedGlobRegex string then warn (getId re) 2063 "Grep uses regex, but this looks like a glob." - else potentially $ do + else sequence_ $ do char <- getSuspiciousRegexWildcard string return $ info (getId re) 2022 $ "Note that unlike globs, " ++ [char] ++ "* here matches '" ++ [char, char, char] ++ "' but not '" ++ wordStartingWith char ++ "'." @@ -461,7 +461,7 @@ 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 + check t = sequence_ $ do let flags = getAllFlags t dashP <- find ((\f -> f == "p" || f == "parents") . snd) flags dashM <- find ((\f -> f == "m" || f == "mode") . snd) flags @@ -487,7 +487,7 @@ checkNonportableSignals = CommandCheck (Exactly "trap") (f . arguments) first:rest -> unless (isFlag first) $ mapM_ check rest _ -> return () - check param = potentially $ do + check param = sequence_ $ do str <- getLiteralString param let id = getId param return $ sequence_ $ mapMaybe (\f -> f id str) [ @@ -687,7 +687,7 @@ prop_checkExportedExpansions3 = verifyNot checkExportedExpansions "export foo" prop_checkExportedExpansions4 = verifyNot checkExportedExpansions "export ${foo?}" checkExportedExpansions = CommandCheck (Exactly "export") (mapM_ check . arguments) where - check t = potentially $ do + check t = sequence_ $ do var <- getSingleUnmodifiedVariable t let name = bracedString var return . warn (getId t) 2163 $ @@ -709,7 +709,7 @@ checkReadExpansions = CommandCheck (Exactly "read") check return [y | (x,y) <- opts, null x || x == "a"] check cmd = mapM_ warning $ getVars cmd - warning t = potentially $ do + warning t = sequence_ $ do var <- getSingleUnmodifiedVariable t let name = bracedString var guard $ isVariableName name -- e.g. not $1 @@ -859,7 +859,7 @@ checkWhileGetoptsCase = CommandCheck (Exactly "getopts") f f :: Token -> Analysis f t@(T_SimpleCommand _ _ (cmd:arg1:_)) = do path <- getPathM t - potentially $ do + sequence_ $ do options <- getLiteralString arg1 (T_WhileExpression _ _ body) <- findFirst whileLoop path caseCmd <- mapMaybe findCase body !!! 0 @@ -886,7 +886,7 @@ checkWhileGetoptsCase = CommandCheck (Exactly "getopts") f warnUnhandled optId caseId str = warn caseId 2213 $ "getopts specified -" ++ str ++ ", but it's not handled by this 'case'." - warnRedundant (key, expr) = potentially $ do + warnRedundant (key, expr) = sequence_ $ do str <- key guard $ str `notElem` ["*", ":", "?"] return $ warn (getId expr) 2214 "This case is not specified by getopts." @@ -1081,7 +1081,7 @@ prop_checkSudoArgs6 = verifyNot checkSudoArgs "sudo -n -u export ls" prop_checkSudoArgs7 = verifyNot checkSudoArgs "sudo docker export foo" checkSudoArgs = CommandCheck (Basename "sudo") f where - f t = potentially $ do + f t = sequence_ $ do opts <- parseOpts t let nonFlags = [x | ("",x) <- opts] commandArg <- nonFlags !!! 0 @@ -1109,7 +1109,7 @@ prop_checkChmodDashr3 = verifyNot checkChmodDashr "chmod a-r dir" checkChmodDashr = CommandCheck (Basename "chmod") f where f t = mapM_ check $ arguments t - check t = potentially $ do + check t = sequence_ $ do flag <- getLiteralString t guard $ flag == "-r" return $ warn (getId t) 2253 "Use -R to recurse, or explicitly a-r to remove read permissions." diff --git a/src/ShellCheck/Checks/ShellSupport.hs b/src/ShellCheck/Checks/ShellSupport.hs index b643525..4e0655d 100644 --- a/src/ShellCheck/Checks/ShellSupport.hs +++ b/src/ShellCheck/Checks/ShellSupport.hs @@ -73,7 +73,7 @@ prop_checkForDecimals2 = verify checkForDecimals "foo[1.2]=bar" prop_checkForDecimals3 = verifyNot checkForDecimals "declare -A foo; foo[1.2]=bar" checkForDecimals = ForShell [Sh, Dash, Bash] f where - f t@(TA_Expansion id _) = potentially $ do + f t@(TA_Expansion id _) = sequence_ $ do str <- getLiteralString t first <- str !!! 0 guard $ isDigit first && '.' `elem` str @@ -337,7 +337,7 @@ checkBashisms = ForShell [Sh, Dash] $ \t -> do in do when (name `elem` unsupportedCommands) $ warnMsg id $ "'" ++ name ++ "' is" - potentially $ do + sequence_ $ do allowed' <- Map.lookup name allowedFlags allowed <- allowed' (word, flag) <- find @@ -347,7 +347,7 @@ checkBashisms = ForShell [Sh, Dash] $ \t -> do when (name == "source") $ warnMsg id "'source' in place of '.' is" when (name == "trap") $ let - check token = potentially $ do + check token = sequence_ $ do str <- getLiteralString token let upper = map toUpper str return $ do @@ -362,7 +362,7 @@ checkBashisms = ForShell [Sh, Dash] $ \t -> do in mapM_ check (drop 1 rest) - when (name == "printf") $ potentially $ do + when (name == "printf") $ sequence_ $ do format <- rest !!! 0 -- flags are covered by allowedFlags let literal = onlyLiteralString format guard $ "%q" `isInfixOf` literal From 0ca50159ec24f2aa6495317927a943bfd69272c2 Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 20:12:57 -0500 Subject: [PATCH 07/26] Use head instead of reimplementing it Normally I wouldn't use head, but this code is partial anyway. --- src/ShellCheck/Analytics.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index 4100b2d..cfe9301 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -565,10 +565,8 @@ checkShebang params (T_Script _ (T_Literal id sb) _) = execWriter $ do unless (null sb) $ do unless ("/" `isPrefixOf` sb) $ err id 2239 "Ensure the shebang uses an absolute path to the interpreter." - case words sb of - first:_ -> - when ("/" `isSuffixOf` first) $ - err id 2246 "This shebang specifies a directory. Ensure the interpreter is a file." + when ("/" `isSuffixOf` head (words sb)) $ + err id 2246 "This shebang specifies a directory. Ensure the interpreter is a file." prop_checkForInQuoted = verify checkForInQuoted "for f in \"$(ls)\"; do echo foo; done" From 0e00249eaed3a13e78bdcd9f146661963959f685 Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 20:22:06 -0500 Subject: [PATCH 08/26] Use void instead of do and return () --- src/ShellCheck/Analytics.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index cfe9301..6bd1e5d 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -500,11 +500,10 @@ checkPipePitfalls _ (T_Pipeline id _ commands) = do for' ["ls", "xargs"] $ \x -> warn x 2011 "Use 'find .. -print0 | xargs -0 ..' or 'find .. -exec .. +' to allow non-alphanumeric filenames." ] - unless didLs $ do + unless didLs $ void $ for ["ls", "?"] $ \(ls:_) -> unless (hasShortParameter 'N' (oversimplify ls)) $ info (getId ls) 2012 "Use find instead of ls to better handle non-alphanumeric filenames." - return () where for l f = let indices = indexOfSublists l (map (headOrDefault "" . oversimplify) commands) From 057cc714b3afc3530ab07978bd24320e84ab1137 Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 20:36:14 -0500 Subject: [PATCH 09/26] Simplify matchToken --- src/ShellCheck/Analytics.hs | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index 6bd1e5d..854dac7 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -1220,10 +1220,7 @@ checkLiteralBreakingTest _ t = sequence_ $ where hasEquals = matchToken ('=' `elem`) isNonEmpty = matchToken (not . null) - matchToken m t = isJust $ do - str <- getLiteralString t - guard $ m str - return () + matchToken m t = maybe False m (getLiteralString t) comparisonWarning list = do token <- find hasEquals list From a6efd02807ad7ae6c8047d4f42fb46150c8bd018 Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 20:45:05 -0500 Subject: [PATCH 10/26] Simplify <> for SpaceStatus --- src/ShellCheck/Analytics.hs | 12 +++++------- 1 file changed, 5 insertions(+), 7 deletions(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index 854dac7..9581b7c 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -1804,13 +1804,11 @@ prop_checkSpacefulness40= verifyNotTree checkSpacefulness "a=$((x+1)); echo $a" data SpaceStatus = SpaceSome | SpaceNone | SpaceEmpty deriving (Eq) instance Semigroup SpaceStatus where - (<>) x y = - case (x,y) of - (SpaceNone, SpaceNone) -> SpaceNone - (SpaceSome, _) -> SpaceSome - (_, SpaceSome) -> SpaceSome - (SpaceEmpty, x) -> x - (x, SpaceEmpty) -> x + SpaceNone <> SpaceNone = SpaceNone + SpaceSome <> _ = SpaceSome + _ <> SpaceSome = SpaceSome + SpaceEmpty <> x = x + x <> SpaceEmpty = x instance Monoid SpaceStatus where mempty = SpaceEmpty mappend = (<>) From c290eace543f35ce15b89432f97ef1b0e4b240d3 Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 20:51:41 -0500 Subject: [PATCH 11/26] Inline an uncurry --- 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 9581b7c..b02ad0f 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -2223,14 +2223,14 @@ checkUnassignedReferences' includeGlobals params t = warnings match <- getBestMatch var return $ " (did you mean '" ++ match ++ "'?)" - warningFor var place = do + warningFor (var, place) = do guard $ isVariableName var guard . not $ isInArray var place || isGuarded place (if includeGlobals || isLocal var then warningForLocals else warningForGlobals) var place - warnings = execWriter . sequence $ mapMaybe (uncurry warningFor) unassigned + warnings = execWriter . sequence $ mapMaybe warningFor unassigned -- Due to parsing, foo=( [bar]=baz ) parses 'bar' as a reference even for assoc arrays. -- Similarly, ${foo[bar baz]} may not be referencing bar/baz. Just skip these. From 172aa7c4fc1014cb2418471e2eb73ac1f43fd3ff Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 20:55:49 -0500 Subject: [PATCH 12/26] Avoid unnecessary use of when and unless --- src/ShellCheck/Analytics.hs | 124 ++++++++++++++++++------------------ 1 file changed, 61 insertions(+), 63 deletions(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index b02ad0f..5f19352 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -257,12 +257,12 @@ verifyTree f s = producesComments f s == Just True verifyNotTree :: (Parameters -> Token -> [TokenComment]) -> String -> Bool verifyNotTree f s = producesComments f s == Just False -checkCommand str f t@(T_SimpleCommand id _ (cmd:rest)) = - when (t `isCommand` str) $ f cmd rest +checkCommand str f t@(T_SimpleCommand id _ (cmd:rest)) + | t `isCommand` str = f cmd rest checkCommand _ _ _ = return () -checkUnqualifiedCommand str f t@(T_SimpleCommand id _ (cmd:rest)) = - when (t `isUnqualifiedCommand` str) $ f cmd rest +checkUnqualifiedCommand str f t@(T_SimpleCommand id _ (cmd:rest)) + | t `isUnqualifiedCommand` str = f cmd rest checkUnqualifiedCommand _ _ _ = return () @@ -450,7 +450,7 @@ prop_checkUuoc6 = verifyNot checkUuoc "cat -n | grep bar" checkUuoc _ (T_Pipeline _ _ (T_Redirecting _ _ cmd:_:_)) = checkCommand "cat" (const f) cmd where - f [word] = unless (mayBecomeMultipleArgs word || isOption word) $ + f [word] | not (mayBecomeMultipleArgs word || isOption word) = style (getId word) 2002 "Useless cat. Consider 'cmd < file | ..' or 'cmd file | ..' instead." f _ = return () isOption word = "-" `isPrefixOf` onlyLiteralString word @@ -577,16 +577,15 @@ prop_checkForInQuoted4 = verify checkForInQuoted "for f in 1,2,3; do true; done" prop_checkForInQuoted4a = verifyNot checkForInQuoted "for f in foo{1,2,3}; do true; done" prop_checkForInQuoted5 = verify checkForInQuoted "for f in ls; do true; done" prop_checkForInQuoted6 = verifyNot checkForInQuoted "for f in \"${!arr}\"; do true; done" -checkForInQuoted _ (T_ForIn _ f [T_NormalWord _ [word@(T_DoubleQuoted id list)]] _) = - when (any (\x -> willSplit x && not (mayBecomeMultipleArgs x)) list - || (fmap wouldHaveBeenGlob (getLiteralString word) == Just True)) $ +checkForInQuoted _ (T_ForIn _ f [T_NormalWord _ [word@(T_DoubleQuoted id list)]] _) + | any (\x -> willSplit x && not (mayBecomeMultipleArgs x)) list + || (fmap wouldHaveBeenGlob (getLiteralString word) == Just True) = err id 2066 "Since you double quoted this, it will not word split, and the loop will only run once." checkForInQuoted _ (T_ForIn _ f [T_NormalWord _ [T_SingleQuoted id _]] _) = warn id 2041 "This is a literal string. To run as a command, use $(..) instead of '..' . " checkForInQuoted _ (T_ForIn _ f [T_NormalWord _ [T_Literal id s]] _) = - if ',' `elem` s - then unless ('{' `elem` s) $ - warn id 2042 "Use spaces, not commas, to separate loop elements." + if ',' `elem` s && '{' `notElem` s + then warn id 2042 "Use spaces, not commas, to separate loop elements." else warn id 2043 "This loop will only ever run once for a constant value. Did you perhaps mean to loop over dir/*, $var or $(cmd)?" checkForInQuoted _ _ = return () @@ -705,13 +704,13 @@ checkRedirectToSame params s@(T_Pipeline _ _ list) = where note x = makeComment InfoC x 2094 "Make sure not to read and write the same file in the same pipeline." - checkOccurrences t@(T_NormalWord exceptId x) u@(T_NormalWord newId y) = - when (exceptId /= newId + checkOccurrences t@(T_NormalWord exceptId x) u@(T_NormalWord newId y) | + exceptId /= newId && x == y && not (isOutput t && isOutput u) && not (special t) && not (any isHarmlessCommand [t,u]) - && not (any containsAssignment [u])) $ do + && not (any containsAssignment [u]) = do addComment $ note newId addComment $ note exceptId checkOccurrences _ _ = return () @@ -769,9 +768,9 @@ prop_checkDollarStar = verify checkDollarStar "for f in $*; do ..; done" prop_checkDollarStar2 = verifyNot checkDollarStar "a=$*" prop_checkDollarStar3 = verifyNot checkDollarStar "[[ $* = 'a b' ]]" checkDollarStar p t@(T_NormalWord _ [b@(T_DollarBraced id _ _)]) - | bracedString b == "*" = - unless (isStrictlyQuoteFree (parentMap p) t) $ - warn id 2048 "Use \"$@\" (with quotes) to prevent whitespace problems." + | bracedString b == "*" && + not (isStrictlyQuoteFree (parentMap p) t) = + warn id 2048 "Use \"$@\" (with quotes) to prevent whitespace problems." checkDollarStar _ _ = return () @@ -799,9 +798,9 @@ prop_checkConcatenatedDollarAt3 = verify checkConcatenatedDollarAt "echo $a$@" prop_checkConcatenatedDollarAt4 = verifyNot checkConcatenatedDollarAt "echo $@" prop_checkConcatenatedDollarAt5 = verifyNot checkConcatenatedDollarAt "echo \"${arr[@]}\"" checkConcatenatedDollarAt p word@T_NormalWord {} - | not $ isQuoteFree (parentMap p) word = - unless (null $ drop 1 parts) $ - mapM_ for array + | not $ isQuoteFree (parentMap p) word + || null (drop 1 parts) = + mapM_ for array where parts = getWordParts word array = find isArrayExpansion parts @@ -1099,8 +1098,8 @@ checkNumberComparisons params (TC_Binary id typ op lhs rhs) = do checkNumberComparisons _ _ = return () prop_checkSingleBracketOperators1 = verify checkSingleBracketOperators "[ test =~ foo ]" -checkSingleBracketOperators params (TC_Binary id SingleBracket "=~" lhs rhs) = - when (shellType params `elem` [Bash, Ksh]) $ +checkSingleBracketOperators params (TC_Binary id SingleBracket "=~" lhs rhs) + | shellType params `elem` [Bash, Ksh] = err id 2074 $ "Can't use =~ in [ ]. Use [[..]] instead." checkSingleBracketOperators _ _ = return () @@ -1165,10 +1164,10 @@ prop_checkGlobbedRegex5 = verifyNot checkGlobbedRegex "[[ $foo =~ \\* ]]" prop_checkGlobbedRegex6 = verifyNot checkGlobbedRegex "[[ $foo =~ (o*) ]]" prop_checkGlobbedRegex7 = verifyNot checkGlobbedRegex "[[ $foo =~ \\*foo ]]" prop_checkGlobbedRegex8 = verifyNot checkGlobbedRegex "[[ $foo =~ x\\* ]]" -checkGlobbedRegex _ (TC_Binary _ DoubleBracket "=~" _ rhs) = - let s = concat $ oversimplify rhs in - when (isConfusedGlobRegex s) $ - warn (getId rhs) 2049 "=~ is for regex, but this looks like a glob. Use = instead." +checkGlobbedRegex _ (TC_Binary _ DoubleBracket "=~" _ rhs) + | isConfusedGlobRegex s = + warn (getId rhs) 2049 "=~ is for regex, but this looks like a glob. Use = instead." + where s = concat $ oversimplify rhs checkGlobbedRegex _ _ = return () @@ -1512,8 +1511,8 @@ prop_checkIndirectExpansion2 = verifyNot checkIndirectExpansion "${foo//$n/lol}" prop_checkIndirectExpansion3 = verify checkIndirectExpansion "${$#}" prop_checkIndirectExpansion4 = verify checkIndirectExpansion "${var${n}_$((i%2))}" prop_checkIndirectExpansion5 = verifyNot checkIndirectExpansion "${bar}" -checkIndirectExpansion _ (T_DollarBraced i _ (T_NormalWord _ contents)) = - when (isIndirection contents) $ +checkIndirectExpansion _ (T_DollarBraced i _ (T_NormalWord _ contents)) + | isIndirection contents = err i 2082 "To expand via indirection, use arrays, ${!name} or (for sh only) eval." where isIndirection vars = @@ -1550,8 +1549,8 @@ checkInexplicablyUnquoted params (T_NormalWord id tokens) = mapM_ check (tails t case trapped of T_DollarExpansion id _ -> warnAboutExpansion id T_DollarBraced id _ _ -> warnAboutExpansion id - T_Literal id s -> - unless (quotesSingleThing a && quotesSingleThing b || isRegex (getPath (parentMap params) trapped)) $ + T_Literal id s + | not (quotesSingleThing a && quotesSingleThing b || isRegex (getPath (parentMap params) trapped)) -> warnAboutLiteral id _ -> return () @@ -1644,8 +1643,8 @@ checkSpuriousExec _ = doLists commentIfExec (T_Pipeline id _ list) = mapM_ commentIfExec $ take 1 list commentIfExec (T_Redirecting _ _ f@( - T_SimpleCommand id _ (cmd:arg:_))) = - when (f `isUnqualifiedCommand` "exec") $ + T_SimpleCommand id _ (cmd:arg:_))) + | f `isUnqualifiedCommand` "exec" = warn id 2093 "Remove \"exec \" if script should continue after this command." commentIfExec _ = return () @@ -1922,8 +1921,8 @@ prop_CheckVariableBraces3 = verifyNot checkVariableBraces "#shellcheck disable=S prop_CheckVariableBraces4 = verifyNot checkVariableBraces "echo $* $1" checkVariableBraces params t = case t of - T_DollarBraced id False _ -> - unless (name `elem` unbracedVariables) $ + T_DollarBraced id False _ + | name `notElem` unbracedVariables -> styleWithFix id 2250 "Prefer putting braces around variable references even when not strictly required." (fixFor t) @@ -2532,13 +2531,12 @@ checkUnpassedInFunctions params root = updateWith x@(name, _, _) = Map.insertWith (++) name [x] warnForGroup group = - when (all isArgumentless group) $ - -- Allow ignoring SC2120 on the function to ignore all calls - let (name, func) = getFunction group - ignoring = shouldIgnoreCode params 2120 func - in unless ignoring $ do - mapM_ suggestParams group - warnForDeclaration func name + -- Allow ignoring SC2120 on the function to ignore all calls + when (all isArgumentless group && not ignoring) $ do + mapM_ suggestParams group + warnForDeclaration func name + where (name, func) = getFunction group + ignoring = shouldIgnoreCode params 2120 func suggestParams (name, _, thing) = info (getId thing) 2119 $ @@ -2562,11 +2560,11 @@ prop_checkOverridingPath8 = verifyNot checkOverridingPath "PATH=$PATH:/stuff" checkOverridingPath _ (T_SimpleCommand _ vars []) = mapM_ checkVar vars where - checkVar (T_Assignment id Assign "PATH" [] word) = - let string = concat $ oversimplify word - in unless (any (`isInfixOf` string) ["/bin", "/sbin" ]) $ do + checkVar (T_Assignment id Assign "PATH" [] word) + | not $ any (`isInfixOf` string) ["/bin", "/sbin" ] = do when ('/' `elem` string && ':' `notElem` string) $ notify id when (isLiteral word && ':' `notElem` string && '/' `notElem` string) $ notify id + where string = concat $ oversimplify word checkVar _ = return () notify id = warn id 2123 "PATH is the shell search path. Use another name." checkOverridingPath _ _ = return () @@ -2577,8 +2575,8 @@ prop_checkTildeInPath3 = verifyNot checkTildeInPath "PATH=~/bin" checkTildeInPath _ (T_SimpleCommand _ vars _) = mapM_ checkVar vars where - checkVar (T_Assignment id Assign "PATH" [] (T_NormalWord _ parts)) = - when (any (\x -> isQuoted x && hasTilde x) parts) $ + checkVar (T_Assignment id Assign "PATH" [] (T_NormalWord _ parts)) + | any (\x -> isQuoted x && hasTilde x) parts = warn id 2147 "Literal tilde in PATH works poorly across programs." checkVar _ = return () @@ -2822,8 +2820,8 @@ prop_checkReadWithoutR3 = verifyNot checkReadWithoutR "read -t 0" prop_checkReadWithoutR4 = verifyNot checkReadWithoutR "read -t 0 && read --d '' -r bar" prop_checkReadWithoutR5 = verifyNot checkReadWithoutR "read -t 0 foo < file.txt" prop_checkReadWithoutR6 = verifyNot checkReadWithoutR "read -u 3 -t 0" -checkReadWithoutR _ t@T_SimpleCommand {} | t `isUnqualifiedCommand` "read" = - unless ("r" `elem` map snd flags || has_t0) $ +checkReadWithoutR _ t@T_SimpleCommand {} | t `isUnqualifiedCommand` "read" + && "r" `notElem` map snd flags && not has_t0 = info (getId $ getCommandTokenOrThis t) 2162 "read without -r will mangle backslashes." where flags = getAllFlags t @@ -2872,15 +2870,15 @@ checkUncheckedCdPushdPopd params root = [] else execWriter $ doAnalysis checkElement root where - checkElement t@T_SimpleCommand {} = do - let name = getName t - when(name `elem` ["cd", "pushd", "popd"] + checkElement t@T_SimpleCommand {} + | name `elem` ["cd", "pushd", "popd"] && not (isSafeDir t) && not (name `elem` ["pushd", "popd"] && ("n" `elem` map snd (getAllFlags t))) - && not (isCondition $ getPath (parentMap params) t)) $ + && not (isCondition $ getPath (parentMap params) t) = warnWithFix (getId t) 2164 ("Use '" ++ name ++ " ... || exit' or '" ++ name ++ " ... || return' in case " ++ name ++ " fails.") (fixWith [replaceEnd (getId t) params 0 " || exit"]) + where name = getName t checkElement _ = return () getName t = fromMaybe "" $ getCommandName t isSafeDir t = case oversimplify t of @@ -2953,10 +2951,10 @@ checkReturnAgainstZero _ token = case token of TC_Binary id _ _ lhs rhs -> check lhs rhs TA_Binary id _ lhs rhs -> check lhs rhs - TA_Unary id _ exp -> - when (isExitCode exp) $ message (getId exp) - TA_Sequence _ [exp] -> - when (isExitCode exp) $ message (getId exp) + TA_Unary id _ exp + | isExitCode exp -> message (getId exp) + TA_Sequence _ [exp] + | isExitCode exp -> message (getId exp) _ -> return () where check lhs rhs = @@ -3191,8 +3189,8 @@ prop_checkGlobAsCommand1 = verify checkGlobAsCommand "foo*" prop_checkGlobAsCommand2 = verify checkGlobAsCommand "$(var[i])" prop_checkGlobAsCommand3 = verifyNot checkGlobAsCommand "echo foo*" checkGlobAsCommand _ t = case t of - T_SimpleCommand _ _ (first:_) -> - when (isGlob first) $ + T_SimpleCommand _ _ (first:_) + | isGlob first -> warn (getId first) 2211 "This is a glob used as a command name. Was it supposed to be in ${..}, array, or is it missing quoting?" _ -> return () @@ -3202,8 +3200,8 @@ prop_checkFlagAsCommand2 = verify checkFlagAsCommand "foo\n --bar=baz" prop_checkFlagAsCommand3 = verifyNot checkFlagAsCommand "'--myexec--' args" prop_checkFlagAsCommand4 = verifyNot checkFlagAsCommand "var=cmd --arg" -- Handled by SC2037 checkFlagAsCommand _ t = case t of - T_SimpleCommand _ [] (first:_) -> - when (isUnquotedFlag first) $ + T_SimpleCommand _ [] (first:_) + | isUnquotedFlag first -> warn (getId first) 2215 "This flag is used as a command name. Bad line break or missing [ .. ]?" _ -> return () @@ -3227,7 +3225,7 @@ checkPipeToNowhere :: Parameters -> Token -> WriterT [TokenComment] Identity () checkPipeToNowhere _ t = case t of T_Pipeline _ _ (first:rest) -> mapM_ checkPipe rest - T_Redirecting _ redirects cmd -> when (any redirectsStdin redirects) $ checkRedir cmd + T_Redirecting _ redirects cmd | any redirectsStdin redirects -> checkRedir cmd _ -> return () where checkPipe redir = sequence_ $ do @@ -3408,8 +3406,8 @@ prop_checkRedirectionToCommand2 = verifyNot checkRedirectionToCommand "ls > 'rm' prop_checkRedirectionToCommand3 = verifyNot checkRedirectionToCommand "ls > myfile" checkRedirectionToCommand _ t = case t of - T_IoFile _ _ (T_NormalWord id [T_Literal _ str]) | str `elem` commonCommands -> - unless (str == "file") $ -- This would be confusing + T_IoFile _ _ (T_NormalWord id [T_Literal _ str]) | str `elem` commonCommands + && str /= "file" -> -- This would be confusing warn id 2238 "Redirecting to/from command name instead of file. Did you want pipes/xargs (or quote to ignore)?" _ -> return () From 21ad4196dba4fd47275319ccf8bb3e2d7745567f Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 21:08:32 -0500 Subject: [PATCH 13/26] Simplify findFunction --- src/ShellCheck/Analytics.hs | 10 ++++------ 1 file changed, 4 insertions(+), 6 deletions(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index 5f19352..31213f8 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -2488,12 +2488,10 @@ checkUnpassedInFunctions params root = map (\t@(T_Function _ _ _ name _) -> (name,t)) functions functions = execWriter $ doAnalysis (tell . maybeToList . findFunction) root - findFunction t@(T_Function id _ _ name body) = - let flow = getVariableFlow params body - in - if any (isPositionalReference t) flow && not (any isPositionalAssignment flow) - then return t - else Nothing + findFunction t@(T_Function id _ _ name body) + | any (isPositionalReference t) flow && not (any isPositionalAssignment flow) + = return t + where flow = getVariableFlow params body findFunction _ = Nothing isPositionalAssignment x = From 43c24cf79c6629799c76bdfa35ef957da193fbe2 Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 21:14:52 -0500 Subject: [PATCH 14/26] Use Map.! instead of reimplementing it --- 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 31213f8..1806b7d 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -2544,7 +2544,7 @@ checkUnpassedInFunctions params root = name ++ " references arguments, but none are ever passed." getFunction ((name, _, _):_) = - (name, fromJust $ Map.lookup name functionMap) + (name, functionMap Map.! name) prop_checkOverridingPath1 = verify checkOverridingPath "PATH=\"$var/$foo\"" From 292b0840d9598d64cd5097444fb47ef1b7825004 Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 21:39:02 -0500 Subject: [PATCH 15/26] Simplify a double negative --- 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 1806b7d..4d5f460 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -2588,7 +2588,7 @@ prop_checkUnsupported3 = verify checkUnsupported "#!/bin/sh\ncase foo in bar) ba prop_checkUnsupported4 = verify checkUnsupported "#!/bin/ksh\ncase foo in bar) baz ;;& esac" prop_checkUnsupported5 = verify checkUnsupported "#!/bin/bash\necho \"${ ls; }\"" checkUnsupported params t = - when (not (null support) && (shellType params `notElem` support)) $ + unless (null support || (shellType params `elem` support)) $ report name where (name, support) = shellSupport t From 8e9290badba48894fa54af9128d63a83a2a23293 Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 21:40:05 -0500 Subject: [PATCH 16/26] Do toLower earlier --- 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 4d5f460..aed0e22 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -2594,7 +2594,7 @@ checkUnsupported params t = (name, support) = shellSupport t report s = err (getId t) 2127 $ "To use " ++ s ++ ", specify #!/usr/bin/env " ++ - (map toLower . intercalate " or " . map show $ support) + (intercalate " or " . map (map toLower . show) $ support) -- TODO: Move more of these checks here shellSupport t = From a223a7a5a58eb8f380faea6743d7ced3cf7b6cfc Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 21:50:40 -0500 Subject: [PATCH 17/26] Remove unnecessary fromMaybes --- src/ShellCheck/Analytics.hs | 5 ++--- src/ShellCheck/AnalyzerLib.hs | 2 +- 2 files changed, 3 insertions(+), 4 deletions(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index aed0e22..f275229 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -2823,11 +2823,10 @@ checkReadWithoutR _ t@T_SimpleCommand {} | t `isUnqualifiedCommand` "read" info (getId $ getCommandTokenOrThis t) 2162 "read without -r will mangle backslashes." where flags = getAllFlags t - has_t0 = fromMaybe False $ do + has_t0 = Just "0" == do parsed <- getOpts flagsForRead flags t <- lookup "t" parsed - str <- getLiteralString t - return $ str == "0" + getLiteralString t checkReadWithoutR _ _ = return () diff --git a/src/ShellCheck/AnalyzerLib.hs b/src/ShellCheck/AnalyzerLib.hs index 69eaf63..5ff1c7d 100644 --- a/src/ShellCheck/AnalyzerLib.hs +++ b/src/ShellCheck/AnalyzerLib.hs @@ -454,7 +454,7 @@ leadType params t = T_BatsTest {} -> SubshellScope "@bats test" T_CoProcBody _ _ -> SubshellScope "coproc" T_Redirecting {} -> - if fromMaybe False causesSubshell + if causesSubshell == Just True then SubshellScope "pipeline" else NoneScope _ -> NoneScope From 962fad038c194006e8b1db2efb875c9d49f4daf8 Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 22:02:11 -0500 Subject: [PATCH 18/26] Avoid a zip that breaks fusion --- 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 f275229..61b8515 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -3088,7 +3088,7 @@ checkUnmatchableCases params t = return $ warn (getId candidate) 2195 "This pattern will never match the case statement's word. Double check them." - tupMap f l = zip l (map f l) + tupMap f l = map (\x -> (x, f x)) l checkDoms ((glob, Just x), rest) = case filter (\(_, p) -> x `pseudoGlobIsSuperSetof` p) valids of ((first,_):_) -> do From 7fc94963204b85547918d48d458e67530a530227 Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 22:08:31 -0500 Subject: [PATCH 19/26] Use forM_ instead of reimplementing it --- src/ShellCheck/Analytics.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index 61b8515..794c3f5 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -3090,11 +3090,10 @@ checkUnmatchableCases params t = tupMap f l = map (\x -> (x, f x)) l checkDoms ((glob, Just x), rest) = - case filter (\(_, p) -> x `pseudoGlobIsSuperSetof` p) valids of - ((first,_):_) -> do + forM_ (find (\(_, p) -> x `pseudoGlobIsSuperSetof` p) valids) $ + \(first,_) -> do warn (getId glob) 2221 $ "This pattern always overrides a later one" <> patternContext (getId first) warn (getId first) 2222 $ "This pattern never matches because of a previous pattern" <> patternContext (getId glob) - _ -> return () where patternContext :: Id -> String patternContext id = From 8f0448133ca7437f704e584c018519e2ac3b033c Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 22:14:44 -0500 Subject: [PATCH 20/26] Use isNothing instead of reimplementing it --- src/ShellCheck/Analytics.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index 794c3f5..a082753 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -3250,9 +3250,8 @@ checkPipeToNowhere _ t = "Redirecting to '" ++ name ++ "', a command that doesn't read stdin. " ++ suggestion -- Could any words in a SimpleCommand consume stdin (e.g. echo "$(cat)")? - hasAdditionalConsumers t = fromMaybe True $ do + hasAdditionalConsumers t = isNothing $ doAnalysis (guard . not . mayConsume) t - return False mayConsume t = case t of From ea24e25efd79ff893c540269e9747d1a662640ea Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 22:22:32 -0500 Subject: [PATCH 21/26] Use Map.member instead of isJust and Map.lookup --- 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 a082753..aabb22b 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -849,7 +849,7 @@ checkArrayWithoutIndex params _ = readF _ _ _ = return [] writeF _ (T_Assignment id mode name [] _) _ (DataString _) = do - isArray <- gets (isJust . Map.lookup name) + isArray <- gets (Map.member name) return $ if not isArray then [] else case mode of Assign -> [makeComment WarningC id 2178 "Variable was used as an array but is now assigned a string."] From c95914f9b3326d92748017b7777e23767c8b955a Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 22:41:02 -0500 Subject: [PATCH 22/26] Simplify determineShell --- src/ShellCheck/AnalyzerLib.hs | 18 +++++++----------- 1 file changed, 7 insertions(+), 11 deletions(-) diff --git a/src/ShellCheck/AnalyzerLib.hs b/src/ShellCheck/AnalyzerLib.hs index 5ff1c7d..212e7bc 100644 --- a/src/ShellCheck/AnalyzerLib.hs +++ b/src/ShellCheck/AnalyzerLib.hs @@ -239,19 +239,15 @@ prop_determineShell8 = determineShellTest' (Just Ksh) "#!/bin/sh" == Sh determineShellTest = determineShellTest' Nothing determineShellTest' fallbackShell = determineShell fallbackShell . fromJust . prRoot . pScript -determineShell fallbackShell t = fromMaybe Bash $ do - shellString <- foldl mplus Nothing $ getCandidates t +determineShell fallbackShell t = fromMaybe Bash $ shellForExecutable shellString `mplus` fallbackShell where - forAnnotation t = - case t of - (ShellOverride s) -> return s - _ -> fail "" - getCandidates :: Token -> [Maybe String] - getCandidates t@T_Script {} = [Just $ fromShebang t] - getCandidates (T_Annotation _ annotations s) = - map forAnnotation annotations ++ - [Just $ fromShebang s] + shellString = getCandidate t + getCandidate :: Token -> String + getCandidate t@T_Script {} = fromShebang t + getCandidate (T_Annotation _ annotations s) = + fromMaybe (fromShebang s) $ + listToMaybe [s | ShellOverride s <- annotations] fromShebang (T_Script _ (T_Literal _ s) _) = executableFromShebang s -- Given a string like "/bin/bash" or "/usr/bin/env dash", From 6d06103cab35e3179046cedcda1fd6ea45555790 Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 22:51:10 -0500 Subject: [PATCH 23/26] Remove unnecessary uses of head --- src/ShellCheck/Analytics.hs | 2 +- src/ShellCheck/AnalyzerLib.hs | 9 ++++----- src/ShellCheck/Checks/Commands.hs | 4 ++-- src/ShellCheck/Checks/ShellSupport.hs | 4 ++-- src/ShellCheck/Parser.hs | 10 +++++----- 5 files changed, 14 insertions(+), 15 deletions(-) diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index aabb22b..ffa04c8 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -2293,7 +2293,7 @@ checkWhileReadPitfalls _ (T_WhileExpression id [command] contents) isStdinReadCommand (T_Pipeline _ _ [T_Redirecting id redirs cmd]) = let plaintext = oversimplify cmd - in head (plaintext ++ [""]) == "read" + in headOrDefault "" plaintext == "read" && ("-u" `notElem` plaintext) && all (not . stdinRedirect) redirs isStdinReadCommand _ = False diff --git a/src/ShellCheck/AnalyzerLib.hs b/src/ShellCheck/AnalyzerLib.hs index 212e7bc..364722b 100644 --- a/src/ShellCheck/AnalyzerLib.hs +++ b/src/ShellCheck/AnalyzerLib.hs @@ -255,7 +255,7 @@ determineShell fallbackShell t = fromMaybe Bash $ executableFromShebang :: String -> String executableFromShebang = shellFor where - shellFor s | "/env " `isInfixOf` s = head (drop 1 (words s)++[""]) + shellFor s | "/env " `isInfixOf` s = headOrDefault "" (drop 1 $ words s) shellFor s | ' ' `elem` s = shellFor $ takeWhile (/= ' ') s shellFor s = reverse . takeWhile (/= '/') . reverse $ s @@ -295,7 +295,7 @@ isQuoteFree = isQuoteFreeNode False isQuoteFreeNode strict tree t = (isQuoteFreeElement t == Just True) || - head (mapMaybe isQuoteFreeContext (drop 1 $ getPath tree t) ++ [False]) + headOrDefault False (mapMaybe isQuoteFreeContext (drop 1 $ getPath tree t)) where -- Is this node self-quoting in itself? isQuoteFreeElement t = @@ -758,9 +758,8 @@ getReferencedVariables parents t = _ -> Nothing getIfReference context token = maybeToList $ do - str <- getLiteralStringExt literalizer token - guard . not $ null str - when (isDigit $ head str) $ fail "is a number" + str@(h:_) <- getLiteralStringExt literalizer token + when (isDigit h) $ fail "is a number" return (context, token, getBracedReference str) isDereferencing = (`elem` ["-eq", "-ne", "-lt", "-le", "-gt", "-ge"]) diff --git a/src/ShellCheck/Checks/Commands.hs b/src/ShellCheck/Checks/Commands.hs index 97de0f6..3407030 100644 --- a/src/ShellCheck/Checks/Commands.hs +++ b/src/ShellCheck/Checks/Commands.hs @@ -279,10 +279,10 @@ checkGrepRe = CommandCheck (Basename "grep") check where grepGlobFlags = ["fixed-strings", "F", "include", "exclude", "exclude-dir", "o", "only-matching"] wordStartingWith c = - head . filter ([c] `isPrefixOf`) $ candidates + headOrDefault (c:"test") . filter ([c] `isPrefixOf`) $ candidates where candidates = - sampleWords ++ map (\(x:r) -> toUpper x : r) sampleWords ++ [c:"test"] + sampleWords ++ map (\(x:r) -> toUpper x : r) sampleWords getSuspiciousRegexWildcard str = if not $ str `matches` contra diff --git a/src/ShellCheck/Checks/ShellSupport.hs b/src/ShellCheck/Checks/ShellSupport.hs index 4e0655d..924b002 100644 --- a/src/ShellCheck/Checks/ShellSupport.hs +++ b/src/ShellCheck/Checks/ShellSupport.hs @@ -457,8 +457,8 @@ checkEchoSed = ForShell [Bash, Ksh] f -- This should have used backreferences, but TDFA doesn't support them sedRe = mkRegex "^s(.)([^\n]*)g?$" isSimpleSed s = fromMaybe False $ do - [first,rest] <- matchRegex sedRe s - let delimiters = filter (== head first) rest + [h:_,rest] <- matchRegex sedRe s + let delimiters = filter (== h) rest guard $ length delimiters == 2 return True checkIn id s = diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index 30529e0..f37a56a 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -186,12 +186,12 @@ getNextIdSpanningTokens startTok endTok = do -- Get an ID starting from the first token of the list, and ending after the last getNextIdSpanningTokenList list = - if null list - then do + case list of + [] -> do pos <- getPosition getNextIdBetween pos pos - else - getNextIdSpanningTokens (head list) (last list) + (h:_) -> + getNextIdSpanningTokens h (last list) -- Get the span covered by an id getSpanForId :: Monad m => Id -> SCParser m (SourcePos, SourcePos) @@ -1826,7 +1826,7 @@ readPendingHereDocs = do let thereIsNoTrailer = null trailingSpace && null trailer let leaderIsOk = null leadingSpace || dashed == Dashed && leadingSpacesAreTabs - let trailerStart = if null trailer then '\0' else head trailer + let trailerStart = case trailer of [] -> '\0'; (h:_) -> h let hasTrailingSpace = not $ null trailingSpace let hasTrailer = not $ null trailer let ppt = parseProblemAt trailerPos ErrorC From d5c51281158d0b29408b6aae5035c6b6ee700b5b Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 23:06:12 -0500 Subject: [PATCH 24/26] Use isJust instead of reimplementing it --- src/ShellCheck/Checks/ShellSupport.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/ShellCheck/Checks/ShellSupport.hs b/src/ShellCheck/Checks/ShellSupport.hs index 924b002..83d7887 100644 --- a/src/ShellCheck/Checks/ShellSupport.hs +++ b/src/ShellCheck/Checks/ShellSupport.hs @@ -456,11 +456,10 @@ checkEchoSed = ForShell [Bash, Ksh] f -- This should have used backreferences, but TDFA doesn't support them sedRe = mkRegex "^s(.)([^\n]*)g?$" - isSimpleSed s = fromMaybe False $ do + isSimpleSed s = isJust $ do [h:_,rest] <- matchRegex sedRe s let delimiters = filter (== h) rest guard $ length delimiters == 2 - return True checkIn id s = when (isSimpleSed s) $ style id 2001 "See if you can use ${variable//search/replace} instead." From 42abcb7ae2a68b283f3592b13736d988bcfb51e5 Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 23:12:27 -0500 Subject: [PATCH 25/26] Simplify shellFromFilename --- src/ShellCheck/Checker.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/ShellCheck/Checker.hs b/src/ShellCheck/Checker.hs index 6370f75..60280ec 100644 --- a/src/ShellCheck/Checker.hs +++ b/src/ShellCheck/Checker.hs @@ -48,7 +48,7 @@ tokenToPosition startMap t = fromMaybe fail $ do where fail = error "Internal shellcheck error: id doesn't exist. Please report!" -shellFromFilename filename = foldl mplus Nothing candidates +shellFromFilename filename = listToMaybe candidates where shellExtensions = [(".ksh", Ksh) ,(".bash", Bash) @@ -57,7 +57,7 @@ shellFromFilename filename = foldl mplus Nothing candidates -- The `.sh` is too generic to determine the shell: -- We fallback to Bash in this case and emit SC2148 if there is no shebang candidates = - map (\(ext,sh) -> if ext `isSuffixOf` filename then Just sh else Nothing) shellExtensions + [sh | (ext,sh) <- shellExtensions, ext `isSuffixOf` filename] checkScript :: Monad m => SystemInterface m -> CheckSpec -> m CheckResult checkScript sys spec = do From 85c49a8af9aed6e26604ea6756ed783b6ca9ee90 Mon Sep 17 00:00:00 2001 From: "Joseph C. Sible" Date: Sun, 9 Feb 2020 23:50:48 -0500 Subject: [PATCH 26/26] Simplify mockedSystemInterface --- src/ShellCheck/Interface.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/ShellCheck/Interface.hs b/src/ShellCheck/Interface.hs index aa12fc2..e51359e 100644 --- a/src/ShellCheck/Interface.hs +++ b/src/ShellCheck/Interface.hs @@ -316,10 +316,10 @@ mockedSystemInterface files = SystemInterface { siGetConfig = const $ return Nothing } where - rf file = - case filter ((== file) . fst) files of - [] -> return $ Left "File not included in mock." - [(_, contents)] -> return $ Right contents + rf file = return $ + case find ((== file) . fst) files of + Nothing -> Left "File not included in mock." + Just (_, contents) -> Right contents fs _ _ file = return file mockRcFile rcfile mock = mock {