diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index ae8e81d..2888047 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -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." @@ -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 () diff --git a/src/ShellCheck/AnalyzerLib.hs b/src/ShellCheck/AnalyzerLib.hs index 4dd3f9d..e4640e7 100644 --- a/src/ShellCheck/AnalyzerLib.hs +++ b/src/ShellCheck/AnalyzerLib.hs @@ -643,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 @@ -952,7 +952,7 @@ 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 diff --git a/src/ShellCheck/Checker.hs b/src/ShellCheck/Checker.hs index b423f2d..6370f75 100644 --- a/src/ShellCheck/Checker.hs +++ b/src/ShellCheck/Checker.hs @@ -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 21c6cb7..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 [y | (x,y) <- opts, x == "" || x == "a"] + return [y | (x,y) <- opts, null x || x == "a"] check cmd = mapM_ warning $ getVars cmd warning t = potentially $ do @@ -1057,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 diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index fa9084e..727572d 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -3169,7 +3169,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