diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index acd62b1..7d0b84b 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -409,7 +409,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:_)) = - fromMaybe (return ()) $ check <$> getGlobOrLiteralString firstWord + maybe (return ()) check $ getGlobOrLiteralString firstWord where check op = when (op `elem` ["+", "-", "*", "/"]) $ @@ -493,8 +493,8 @@ checkPipePitfalls _ (T_Pipeline id _ commands) = do for ["grep", "wc"] $ \(grep:wc:_) -> - let flagsGrep = fromMaybe [] $ map snd . getAllFlags <$> getCommand grep - flagsWc = fromMaybe [] $ map snd . getAllFlags <$> getCommand wc + let flagsGrep = maybe [] (map snd . getAllFlags) $ getCommand grep + flagsWc = maybe [] (map snd . getAllFlags) $ getCommand wc in unless (any (`elem` ["o", "only-matching", "r", "R", "recursive"]) flagsGrep || any (`elem` ["m", "chars", "w", "words", "c", "bytes", "L", "max-line-length"]) flagsWc || null flagsWc) $ style (getId grep) 2126 "Consider using grep -c instead of grep|wc -l." @@ -563,7 +563,7 @@ checkShebang params (T_Annotation _ list t) = isOverride _ = False checkShebang params (T_Script _ (T_Literal id sb) _) = execWriter $ do unless (shellTypeSpecified params) $ do - when (sb == "") $ + when (null sb) $ err id 2148 "Tips depend on target shell and yours is unknown. Add a shebang." when (executableFromShebang sb == "ash") $ warn id 2187 "Ash scripts will be checked as Dash. Add '# shellcheck shell=dash' to silence." @@ -1234,10 +1234,10 @@ checkLiteralBreakingTest _ t = potentially $ return () comparisonWarning list = do - token <- listToMaybe $ filter hasEquals list + token <- find hasEquals list return $ err (getId token) 2077 "You need spaces around the comparison operator." tautologyWarning t s = do - token <- listToMaybe $ filter isNonEmpty $ getWordParts t + token <- find isNonEmpty $ getWordParts t return $ err (getId token) 2157 s prop_checkConstantNullary = verify checkConstantNullary "[[ '$(foo)' ]]" @@ -1298,7 +1298,7 @@ checkArithmeticDeref params t@(TA_Expansion _ [b@(T_DollarBraced id _ _)]) = unless (isException $ bracedString b) getWarning where isException [] = True - isException s = any (`elem` "/.:#%?*@$-!+=^,") s || isDigit (head s) + isException s@(h:_) = any (`elem` "/.:#%?*@$-!+=^,") s || isDigit h getWarning = fromMaybe noWarning . msum . map warningFor $ parents params t warningFor t = case t of @@ -1644,9 +1644,9 @@ checkSpuriousExec _ = doLists doList = doList' . stripCleanup -- The second parameter is True if we are in a loop -- In that case we should emit the warning also if `exec' is the last statement - doList' t@(current:following:_) False = do + doList' (current:t@(following:_)) False = do commentIfExec current - doList (tail t) False + doList t False doList' (current:tail) True = do commentIfExec current doList tail True @@ -1961,7 +1961,7 @@ prop_checkQuotesInLiterals9 = verifyNotTree checkQuotesInLiterals "param=\"/foo/ checkQuotesInLiterals params t = doVariableFlowAnalysis readF writeF Map.empty (variableFlow params) where - getQuotes name = fmap (Map.lookup name) get + getQuotes name = gets (Map.lookup name) setQuotes name ref = modify $ Map.insert name ref deleteQuotes = modify . Map.delete parents = parentMap params @@ -2332,7 +2332,7 @@ checkWhileReadPitfalls _ (T_WhileExpression id [command] contents) checkMuncher _ = return () stdinRedirect (T_FdRedirect _ fd _) - | fd == "" || fd == "0" = True + | null fd || fd == "0" = True stdinRedirect _ = False checkWhileReadPitfalls _ _ = return () @@ -2635,8 +2635,8 @@ checkMultipleAppends params t = where checkList list = mapM_ checkGroup (groupWith (fmap fst) $ map getTarget list) - checkGroup (f:_:_:_) | isJust f = - style (snd $ fromJust f) 2129 + checkGroup (Just (_,id):_:_:_) = + style id 2129 "Consider using { cmd1; cmd2; } >> file instead of individual redirects." checkGroup _ = return () getTarget (T_Annotation _ _ t) = getTarget t @@ -2844,7 +2844,7 @@ checkReadWithoutR _ t@T_SimpleCommand {} | t `isUnqualifiedCommand` "read" = flags = getAllFlags t has_t0 = fromMaybe False $ do parsed <- getOpts flagsForRead flags - t <- getOpt "t" parsed + t <- lookup "t" parsed str <- getLiteralString t return $ str == "0" @@ -2914,7 +2914,7 @@ checkLoopVariableReassignment params token = where check = do str <- loopVariable token - next <- listToMaybe $ filter (\x -> loopVariable x == Just str) path + next <- find (\x -> loopVariable x == Just str) path return $ do warn (getId token) 2165 "This nested loop overrides the index variable of its parent." warn (getId next) 2167 "This parent loop has its index variable overridden." @@ -3144,9 +3144,9 @@ checkSubshellAsTest _ t = checkParams id first second = do - when (fromMaybe False $ (`elem` unaryTestOps) <$> getLiteralString first) $ + when (maybe False (`elem` unaryTestOps) $ getLiteralString first) $ err id 2204 "(..) is a subshell. Did you mean [ .. ], a test expression?" - when (fromMaybe False $ (`elem` binaryTestOps) <$> getLiteralString second) $ + when (maybe False (`elem` binaryTestOps) $ getLiteralString second) $ warn id 2205 "(..) is a subshell. Did you mean [ .. ], a test expression?" @@ -3173,7 +3173,7 @@ checkSplittingInArrays params t = T_DollarBraced id _ str | not (isCountingReference part) && not (isQuotedAlternativeReference part) - && not (getBracedReference (bracedString part) `elem` variablesWithoutSpaces) + && getBracedReference (bracedString part) `notElem` variablesWithoutSpaces -> warn id 2206 $ if shellType params == Ksh then "Quote to prevent word splitting/globbing, or split robustly with read -A or while read." diff --git a/src/ShellCheck/AnalyzerLib.hs b/src/ShellCheck/AnalyzerLib.hs index 590889c..e4640e7 100644 --- a/src/ShellCheck/AnalyzerLib.hs +++ b/src/ShellCheck/AnalyzerLib.hs @@ -612,8 +612,7 @@ getModifiedVariableCommand base@(T_SimpleCommand id cmdPrefix (T_NormalWord _ (T _ -> [] where flags = map snd $ getAllFlags base - stripEquals s = let rest = dropWhile (/= '=') s in - if rest == "" then "" else tail rest + stripEquals s = drop 1 $ dropWhile (/= '=') s stripEqualsFrom (T_NormalWord id1 (T_Literal id2 s:rs)) = T_NormalWord id1 (T_Literal id2 (stripEquals s):rs) stripEqualsFrom (T_NormalWord id1 [T_DoubleQuoted id2 [T_Literal id3 s]]) = @@ -644,7 +643,7 @@ getModifiedVariableCommand base@(T_SimpleCommand id cmdPrefix (T_NormalWord _ (T getModifierParam _ _ = [] letParamToLiteral token = - if var == "" + if null var then [] else [(base, token, var, DataString $ SourceFrom [stripEqualsFrom token])] where var = takeWhile isVariableChar $ dropWhile (`elem` "+-") $ concat $ oversimplify token @@ -785,8 +784,8 @@ isCommand token str = isCommandMatch token (\cmd -> cmd == str || ('/' : str) ` -- Compare a command to a literal. Like above, but checks full path. isUnqualifiedCommand token str = isCommandMatch token (== str) -isCommandMatch token matcher = fromMaybe False $ - fmap matcher (getCommandName token) +isCommandMatch token matcher = maybe False + matcher (getCommandName token) -- Does this regex look like it was intended as a glob? -- True: *foo* @@ -953,15 +952,13 @@ getOpts string flags = process flags takesArg <- Map.lookup flag1 flagMap if takesArg then do - guard $ flag2 == "" + guard $ null flag2 more <- process rest return $ (flag1, token2) : more else do more <- process rest2 return $ (flag1, token1) : more -getOpt str flags = snd <$> (listToMaybe $ filter (\(f, _) -> f == str) $ flags) - supportsArrays shell = shell == Bash || shell == Ksh -- Returns true if the shell is Bash or Ksh (sorry for the name, Ksh) diff --git a/src/ShellCheck/Checker.hs b/src/ShellCheck/Checker.hs index 2ea950d..6370f75 100644 --- a/src/ShellCheck/Checker.hs +++ b/src/ShellCheck/Checker.hs @@ -88,9 +88,9 @@ checkScript sys spec = do asOptionalChecks = csOptionalChecks spec } where as = newAnalysisSpec root let analysisMessages = - fromMaybe [] $ + maybe [] (arComments . analyzeScript . analysisSpec) - <$> prRoot result + $ prRoot result let translator = tokenToPosition tokenPositions return . nub . sortMessages . filter shouldInclude $ (parseMessages ++ map translator analysisMessages) @@ -104,7 +104,7 @@ checkScript sys spec = do code = cCode (pcComment pc) severity = cSeverity (pcComment pc) - sortMessages = sortBy (comparing order) + sortMessages = sortOn order order pc = let pos = pcStartPos pc comment = pcComment pc in @@ -198,11 +198,11 @@ prop_optionDisablesBadShebang = } prop_annotationDisablesBadShebang = - [] == check "#!/usr/bin/python\n# shellcheck shell=sh\ntrue\n" + null $ check "#!/usr/bin/python\n# shellcheck shell=sh\ntrue\n" prop_canParseDevNull = - [] == check "source /dev/null" + null $ check "source /dev/null" prop_failsWhenNotSourcing = [1091, 2154] == check "source lol; echo \"$bar\"" @@ -218,7 +218,7 @@ prop_worksWhenDotting = -- FIXME: This should really be giving [1093], "recursively sourced" prop_noInfiniteSourcing = - [] == checkWithIncludes [("lib", "source lib")] "source lib" + null $ checkWithIncludes [("lib", "source lib")] "source lib" prop_canSourceBadSyntax = [1094, 2086] == checkWithIncludes [("lib", "for f; do")] "source lib; echo $1" @@ -239,10 +239,10 @@ prop_recursiveParsing = [1037] == checkRecursive [("lib", "echo \"$10\"")] "source lib" prop_nonRecursiveAnalysis = - [] == checkWithIncludes [("lib", "echo $1")] "source lib" + null $ checkWithIncludes [("lib", "echo $1")] "source lib" prop_nonRecursiveParsing = - [] == checkWithIncludes [("lib", "echo \"$10\"")] "source lib" + null $ checkWithIncludes [("lib", "echo \"$10\"")] "source lib" prop_sourceDirectiveDoesntFollowFile = null $ checkWithIncludes @@ -328,7 +328,7 @@ prop_optionIncludes4 = [2154] == checkOptionIncludes (Just [2154]) "#!/bin/sh\n var='a b'\n echo $var\n echo $bar" -prop_readsRcFile = result == [] +prop_readsRcFile = null result where result = checkWithRc "disable=2086" emptyCheckSpec { csScript = "#!/bin/sh\necho $1", diff --git a/src/ShellCheck/Checks/Commands.hs b/src/ShellCheck/Checks/Commands.hs index eb0c434..299a335 100644 --- a/src/ShellCheck/Checks/Commands.hs +++ b/src/ShellCheck/Checks/Commands.hs @@ -345,7 +345,7 @@ returnOrExit multi invalid = (f . arguments) invalid (getId value) f _ = return () - isInvalid s = s == "" || any (not . isDigit) s || length s > 5 + isInvalid s = null s || any (not . isDigit) s || length s > 5 || let value = (read s :: Integer) in value > 255 literal token = fromJust $ getLiteralStringExt lit token @@ -706,7 +706,7 @@ checkReadExpansions = CommandCheck (Exactly "read") check options = getGnuOpts flagsForRead getVars cmd = fromMaybe [] $ do opts <- options cmd - return . map snd $ filter (\(x,_) -> x == "" || x == "a") opts + return [y | (x,y) <- opts, null x || x == "a"] check cmd = mapM_ warning $ getVars cmd warning t = potentially $ do @@ -995,10 +995,9 @@ missingDestination handler token = do _ -> return () where args = getAllFlags token - params = map fst $ filter (\(_,x) -> x == "") args + params = [x | (x,"") <- args] hasTarget = - any (\x -> x /= "" && x `isPrefixOf` "target-directory") $ - map snd args + any (\(_,x) -> x /= "" && x `isPrefixOf` "target-directory") args prop_checkMvArguments1 = verify checkMvArguments "mv 'foo bar'" prop_checkMvArguments2 = verifyNot checkMvArguments "mv foo bar" @@ -1058,7 +1057,7 @@ checkSudoRedirect = CommandCheck (Basename "sudo") f Just (T_Redirecting _ redirs _) -> mapM_ warnAbout redirs warnAbout (T_FdRedirect _ s (T_IoFile id op file)) - | (s == "" || s == "&") && not (special file) = + | (null s || s == "&") && not (special file) = case op of T_Less _ -> info (getId op) 2024 @@ -1084,7 +1083,7 @@ checkSudoArgs = CommandCheck (Basename "sudo") f where f t = potentially $ do opts <- parseOpts t - let nonFlags = map snd $ filter (\(flag, _) -> flag == "") opts + let nonFlags = [x | ("",x) <- opts] commandArg <- nonFlags !!! 0 command <- getLiteralString commandArg guard $ command `elem` builtins diff --git a/src/ShellCheck/Checks/ShellSupport.hs b/src/ShellCheck/Checks/ShellSupport.hs index 07dfdda..b643525 100644 --- a/src/ShellCheck/Checks/ShellSupport.hs +++ b/src/ShellCheck/Checks/ShellSupport.hs @@ -340,8 +340,8 @@ checkBashisms = ForShell [Sh, Dash] $ \t -> do potentially $ do allowed' <- Map.lookup name allowedFlags allowed <- allowed' - (word, flag) <- listToMaybe $ - filter (\x -> (not . null . snd $ x) && snd x `notElem` allowed) flags + (word, flag) <- find + (\x -> (not . null . snd $ x) && snd x `notElem` allowed) flags return . warnMsg (getId word) $ name ++ " -" ++ flag ++ " is" when (name == "source") $ warnMsg id "'source' in place of '.' is" @@ -487,11 +487,11 @@ checkBraceExpansionVars = ForShell [Bash] f T_DollarBraced {} -> return "$" T_DollarExpansion {} -> return "$" T_DollarArithmetic {} -> return "$" - otherwise -> return "-" + _ -> return "-" toString t = fromJust $ getLiteralStringExt literalExt t isEvaled t = do cmd <- getClosestCommandM t - return $ isJust cmd && fromJust cmd `isUnqualifiedCommand` "eval" + return $ maybe False (`isUnqualifiedCommand` "eval") cmd prop_checkMultiDimensionalArrays1 = verify checkMultiDimensionalArrays "foo[a][b]=3" diff --git a/src/ShellCheck/Data.hs b/src/ShellCheck/Data.hs index 732619d..fb4a1e4 100644 --- a/src/ShellCheck/Data.hs +++ b/src/ShellCheck/Data.hs @@ -135,6 +135,6 @@ shellForExecutable name = "ksh" -> return Ksh "ksh88" -> return Ksh "ksh93" -> return Ksh - otherwise -> Nothing + _ -> Nothing flagsForRead = "sreu:n:N:i:p:a:t:" diff --git a/src/ShellCheck/Fixer.hs b/src/ShellCheck/Fixer.hs index 12de3c2..16bdd98 100644 --- a/src/ShellCheck/Fixer.hs +++ b/src/ShellCheck/Fixer.hs @@ -200,7 +200,7 @@ doReplace start end o r = let si = fromIntegral (start-1) ei = fromIntegral (end-1) (x, xs) = splitAt si o - (y, z) = splitAt (ei - si) xs + z = drop (ei - si) xs in x ++ r ++ z @@ -295,7 +295,7 @@ prop_pstreeSumsCorrectly kvs targets = -- Trivial O(n * m) implementation dumbPrefixSums :: [(Int, Int)] -> [Int] -> [Int] dumbPrefixSums kvs targets = - let prefixSum target = sum . map snd . filter (\(k,v) -> k <= target) $ kvs + let prefixSum target = sum [v | (k,v) <- kvs, k <= target] in map prefixSum targets -- PSTree O(n * log m) implementation smartPrefixSums :: [(Int, Int)] -> [Int] -> [Int] diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index 339b50b..025fa98 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -34,7 +34,7 @@ import Control.Monad.Identity import Control.Monad.Trans import Data.Char import Data.Functor -import Data.List (isPrefixOf, isInfixOf, isSuffixOf, partition, sortBy, intercalate, nub) +import Data.List (isPrefixOf, isInfixOf, isSuffixOf, partition, sortBy, intercalate, nub, find) import Data.Maybe import Data.Monoid import Debug.Trace @@ -325,16 +325,15 @@ parseProblem level code msg = do parseProblemAt pos level code msg setCurrentContexts c = Ms.modify (\state -> state { contextStack = c }) -getCurrentContexts = contextStack <$> Ms.get +getCurrentContexts = Ms.gets contextStack popContext = do v <- getCurrentContexts - if not $ null v - then do - let (a:r) = v + case v of + (a:r) -> do setCurrentContexts r return $ Just a - else + [] -> return Nothing pushContext c = do @@ -589,7 +588,7 @@ readConditionContents single = checkTrailingOp x = fromMaybe (return ()) $ do (T_Literal id str) <- getTrailingUnquotedLiteral x - trailingOp <- listToMaybe (filter (`isSuffixOf` str) binaryTestOps) + trailingOp <- find (`isSuffixOf` str) binaryTestOps return $ parseProblemAtId id ErrorC 1108 $ "You need a space before and after the " ++ trailingOp ++ " ." @@ -3169,7 +3168,7 @@ readScriptFile sourced = do Nothing -> parseProblemAt pos ErrorC 1008 "This shebang was unrecognized. ShellCheck only supports sh/bash/dash/ksh. Add a 'shell' directive to specify." isValidShell s = - let good = s == "" || any (`isPrefixOf` s) goodShells + let good = null s || any (`isPrefixOf` s) goodShells bad = any (`isPrefixOf` s) badShells in if good