diff --git a/src/ShellCheck/ASTLib.hs b/src/ShellCheck/ASTLib.hs index 2e08f4d..ab28959 100644 --- a/src/ShellCheck/ASTLib.hs +++ b/src/ShellCheck/ASTLib.hs @@ -25,6 +25,7 @@ import Control.Monad.Writer import Control.Monad import Data.Char import Data.Functor +import Data.Functor.Identity import Data.List import Data.Maybe @@ -175,9 +176,13 @@ willConcatInAssignment token = getLiteralString :: Token -> Maybe String getLiteralString = getLiteralStringExt (const Nothing) +-- Definitely get a literal string, with a given default for all non-literals +getLiteralStringDef :: String -> Token -> String +getLiteralStringDef x = runIdentity . getLiteralStringExt (const $ return x) + -- Definitely get a literal string, skipping over all non-literals onlyLiteralString :: Token -> String -onlyLiteralString = fromJust . getLiteralStringExt (const $ return "") +onlyLiteralString = getLiteralStringDef "" -- Maybe get a literal string, but only if it's an unquoted argument. getUnquotedLiteral (T_NormalWord _ list) = @@ -216,7 +221,7 @@ getGlobOrLiteralString = getLiteralStringExt f -- Maybe get the literal value of a token, using a custom function -- to map unrecognized Tokens into strings. -getLiteralStringExt :: (Token -> Maybe String) -> Token -> Maybe String +getLiteralStringExt :: Monad m => (Token -> m String) -> Token -> m String getLiteralStringExt more = g where allInList = fmap concat . mapM g diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index d62d61d..c65645d 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -1057,9 +1057,7 @@ checkNumberComparisons params (TC_Binary id typ op lhs rhs) = do checkStrings = mapM_ stringError . find isNonNum - isNonNum t = fromMaybe False $ do - s <- getLiteralStringExt (const $ return "") t - return . not . all numChar $ s + isNonNum t = not . all numChar $ onlyLiteralString t numChar x = isDigit x || x `elem` "+-. " stringError t = err (getId t) 2170 $ @@ -2578,7 +2576,7 @@ checkTildeInPath _ (T_SimpleCommand _ vars _) = warn id 2147 "Literal tilde in PATH works poorly across programs." checkVar _ = return () - hasTilde t = fromMaybe False (liftM2 elem (return '~') (getLiteralStringExt (const $ return "") t)) + hasTilde t = '~' `elem` onlyLiteralString t isQuoted T_DoubleQuoted {} = True isQuoted T_SingleQuoted {} = True isQuoted _ = False diff --git a/src/ShellCheck/AnalyzerLib.hs b/src/ShellCheck/AnalyzerLib.hs index 364722b..dbf59a0 100644 --- a/src/ShellCheck/AnalyzerLib.hs +++ b/src/ShellCheck/AnalyzerLib.hs @@ -801,7 +801,7 @@ isVariableName (x:r) = isVariableStartChar x && all isVariableChar r isVariableName _ = False getVariablesFromLiteralToken token = - getVariablesFromLiteral (fromJust $ getLiteralStringExt (const $ return " ") token) + getVariablesFromLiteral (getLiteralStringDef " " token) -- Try to get referenced variables from a literal string like "$foo" -- Ignores tons of cases like arithmetic evaluation and array indices. diff --git a/src/ShellCheck/Checks/Commands.hs b/src/ShellCheck/Checks/Commands.hs index 3407030..3beca25 100644 --- a/src/ShellCheck/Checks/Commands.hs +++ b/src/ShellCheck/Checks/Commands.hs @@ -34,6 +34,7 @@ import ShellCheck.Regex import Control.Monad import Control.Monad.RWS import Data.Char +import Data.Functor.Identity import Data.List import Data.Maybe import qualified Data.Map.Strict as Map @@ -248,13 +249,12 @@ prop_checkGrepRe23= verifyNot checkGrepRe "grep '.*' file" checkGrepRe = CommandCheck (Basename "grep") check where check cmd = f cmd (arguments cmd) -- --regex=*(extglob) doesn't work. Fixme? - skippable (Just s) = not ("--regex=" `isPrefixOf` s) && "-" `isPrefixOf` s - skippable _ = False + skippable s = not ("--regex=" `isPrefixOf` s) && "-" `isPrefixOf` s f _ [] = return () f cmd (x:r) = - let str = getLiteralStringExt (const $ return "_") x + let str = getLiteralStringDef "_" x in - if str `elem` [Just "--", Just "-e", Just "--regex"] + if str `elem` ["--", "-e", "--regex"] then checkRE cmd r -- Regex is *after* this else if skippable str @@ -348,7 +348,7 @@ returnOrExit multi invalid = (f . arguments) 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 + literal token = runIdentity $ getLiteralStringExt lit token lit (T_DollarBraced {}) = return "0" lit (T_DollarArithmetic {}) = return "0" lit (T_DollarExpansion {}) = return "0" @@ -365,7 +365,7 @@ checkFindExecWithSingleArgument = CommandCheck (Basename "find") (f . arguments) check (exec:arg:term:_) = do execS <- getLiteralString exec termS <- getLiteralString term - cmdS <- getLiteralStringExt (const $ return " ") arg + let cmdS = getLiteralStringDef " " arg guard $ execS `elem` ["-exec", "-execdir"] && termS `elem` [";", "+"] guard $ cmdS `matches` commandRegex @@ -735,7 +735,7 @@ checkAliasesUsesArgs = CommandCheck (Exactly "alias") (f . arguments) re = mkRegex "\\$\\{?[0-9*@]" f = mapM_ checkArg checkArg arg = - let string = fromJust $ getLiteralStringExt (const $ return "_") arg in + let string = getLiteralStringDef "_" arg in when ('=' `elem` string && string `matches` re) $ err (getId arg) 2142 "Aliases can't use positional parameters. Use a function." @@ -781,7 +781,7 @@ checkFindWithoutPath = CommandCheck (Basename "find") f -- path. We assume that all the pre-path flags are single characters from a -- list of GNU and macOS flags. hasPath (first:rest) = - let flag = fromJust $ getLiteralStringExt (const $ return "___") first in + let flag = getLiteralStringDef "___" first in not ("-" `isPrefixOf` flag) || isLeadingFlag flag && hasPath rest hasPath [] = False isLeadingFlag flag = length flag <= 2 || all (`elem` leadingFlagChars) flag diff --git a/src/ShellCheck/Checks/ShellSupport.hs b/src/ShellCheck/Checks/ShellSupport.hs index 83d7887..49d3212 100644 --- a/src/ShellCheck/Checks/ShellSupport.hs +++ b/src/ShellCheck/Checks/ShellSupport.hs @@ -30,6 +30,7 @@ import ShellCheck.Regex import Control.Monad import Control.Monad.RWS import Data.Char +import Data.Functor.Identity import Data.List import Data.Maybe import qualified Data.Map as Map @@ -487,7 +488,7 @@ checkBraceExpansionVars = ForShell [Bash] f T_DollarExpansion {} -> return "$" T_DollarArithmetic {} -> return "$" _ -> return "-" - toString t = fromJust $ getLiteralStringExt literalExt t + toString t = runIdentity $ getLiteralStringExt literalExt t isEvaled t = do cmd <- getClosestCommandM t return $ maybe False (`isUnqualifiedCommand` "eval") cmd