diff --git a/ShellCheck/ASTLib.hs b/ShellCheck/ASTLib.hs index e8c2a2c..8e5b8f6 100644 --- a/ShellCheck/ASTLib.hs +++ b/ShellCheck/ASTLib.hs @@ -237,7 +237,7 @@ getCommand t = T_Redirecting _ _ w -> getCommand w T_SimpleCommand _ _ (w:_) -> return t T_Annotation _ _ t -> getCommand t - _otherwise -> Nothing + _ -> Nothing -- Maybe get the command name of a token representing a command getCommandName t = do @@ -259,7 +259,7 @@ getCommandNameFromExpansion t = T_DollarExpansion _ [c] -> extract c T_Backticked _ [c] -> extract c T_DollarBraceCommandExpansion _ [c] -> extract c - _otherwise -> Nothing + _ -> Nothing where extract (T_Pipeline _ _ [cmd]) = getCommandName cmd extract _ = Nothing @@ -275,7 +275,7 @@ isAssignment t = T_SimpleCommand _ (w:_) [] -> True T_Assignment {} -> True T_Annotation _ _ w -> isAssignment w - _otherwise -> False + _ -> False isOnlyRedirection t = case t of @@ -283,7 +283,7 @@ isOnlyRedirection t = T_Annotation _ _ w -> isOnlyRedirection w T_Redirecting _ (_:_) c -> isOnlyRedirection c T_SimpleCommand _ [] [] -> True - _otherwise -> False + _ -> False isFunction t = case t of T_Function {} -> True; _ -> False @@ -301,7 +301,7 @@ getCommandSequences t = T_ForIn _ _ _ cmds -> [cmds] T_ForArithmetic _ _ _ _ cmds -> [cmds] T_IfExpression _ thens elses -> map snd thens ++ [elses] - _otherwise -> [] + _ -> [] -- Get a list of names of associative arrays getAssociativeArrays t = @@ -321,7 +321,7 @@ getAssociativeArrays t = nameAssignments t = case t of T_Assignment _ _ name _ _ -> return name - _otherwise -> Nothing + _ -> Nothing -- A Pseudoglob is a wildcard pattern used for checking if a match can succeed. -- For example, [[ $(cmd).jpg == [a-z] ]] will give the patterns *.jpg and ?, which diff --git a/ShellCheck/Analytics.hs b/ShellCheck/Analytics.hs index c7fd320..b28fecc 100644 --- a/ShellCheck/Analytics.hs +++ b/ShellCheck/Analytics.hs @@ -968,7 +968,7 @@ checkConditionalAndOrs _ t = (TC_Or id SingleBracket "-o" _ _) -> warn id 2166 "Prefer [ p ] || [ q ] as [ p -o q ] is not well defined." - _otherwise -> return () + _ -> return () prop_checkQuotedCondRegex1 = verify checkQuotedCondRegex "[[ $foo =~ \"bar.*\" ]]" prop_checkQuotedCondRegex2 = verify checkQuotedCondRegex "[[ $foo =~ '(cow|bar)' ]]" @@ -1241,7 +1241,7 @@ checkUuoeVar _ p = unless (isCovered first rest || "-" `isPrefixOf` onlyLiteralString first) $ when (all couldBeOptimized vars) $ style id 2116 "Useless echo? Instead of 'cmd $(echo foo)', just use 'cmd foo'." - _otherwise -> return () + _ -> return () prop_checkTestRedirects1 = verify checkTestRedirects "test 3 > 1" @@ -1257,12 +1257,12 @@ checkTestRedirects _ (T_Redirecting id redirs cmd) | cmd `isCommand` "test" = suspicious t = -- Ignore redirections of stderr because these are valid for squashing e.g. int errors, case t of -- and >> and similar redirections because these are probably not comparisons. T_FdRedirect _ fd (T_IoFile _ op _) -> fd /= "2" && isComparison op - _otherwise -> False + _ -> False isComparison t = case t of T_Greater _ -> True T_Less _ -> True - _otherwise -> False + _ -> False checkTestRedirects _ _ = return () prop_checkSudoRedirect1 = verify checkSudoRedirect "sudo echo 3 > /proc/file" @@ -1696,7 +1696,7 @@ checkQuotesInLiterals params t = squashesQuotes t = case t of T_DollarBraced id _ -> "#" `isPrefixOf` bracedString t - _otherwise -> False + _ -> False readF _ expr name = do assignment <- getQuotes name @@ -1997,7 +1997,7 @@ checkPrefixAssignmentReference params t@(T_DollarBraced id value) = check (t:rest) = case t of T_SimpleCommand _ vars (_:_) -> mapM_ checkVar vars - _otherwise -> check rest + _ -> check rest checkVar (T_Assignment aId mode aName [] value) | aName == name && (aId `notElem` idPath) = do warn aId 2097 "This assignment is only seen by the forked process." @@ -2313,7 +2313,7 @@ shellSupport t = case t of T_CaseExpression _ _ list -> forCase (map (\(a,_,_) -> a) list) T_DollarBraceCommandExpansion {} -> ("${ ..; } command expansion", [Ksh]) - _otherwise -> ("", []) + _ -> ("", []) where forCase seps | CaseContinue `elem` seps = ("cases with ;;&", [Bash]) forCase seps | CaseFallThrough `elem` seps = ("cases with ;&", [Bash, Ksh]) @@ -2555,7 +2555,7 @@ prop_checkTrailingBracket5 = verifyNot checkTrailingBracket "run bar ']'" checkTrailingBracket _ token = case token of T_SimpleCommand _ _ tokens@(_:_) -> check (last tokens) token - _otherwise -> return () + _ -> return () where check t command = case t of @@ -2566,7 +2566,7 @@ checkTrailingBracket _ token = guard $ opposite `notElem` parameters return $ warn id 2171 $ "Found trailing " ++ str ++ " outside test. Missing " ++ opposite ++ "?" - _otherwise -> return () + _ -> return () invert s = case s of "]]" -> "[[" @@ -2590,7 +2590,7 @@ checkReturnAgainstZero _ token = when (isExitCode exp) $ message (getId exp) TA_Sequence _ [exp] -> when (isExitCode exp) $ message (getId exp) - _otherwise -> return () + _ -> return () where check lhs rhs = if isZero rhs && isExitCode lhs @@ -2600,7 +2600,7 @@ checkReturnAgainstZero _ token = isExitCode t = case getWordParts t of [exp@T_DollarBraced {}] -> bracedString exp == "?" - _otherwise -> False + _ -> False message id = style id 2181 "Check exit code directly with e.g. 'if mycmd;', not indirectly with $?." prop_checkRedirectedNowhere1 = verify checkRedirectedNowhere "> file"