diff --git a/src/ShellCheck/ASTLib.hs b/src/ShellCheck/ASTLib.hs index 7b5efdd..20e5be4 100644 --- a/src/ShellCheck/ASTLib.hs +++ b/src/ShellCheck/ASTLib.hs @@ -59,10 +59,28 @@ willSplit x = T_NormalWord _ l -> any willSplit l _ -> False -isGlob T_Extglob {} = True -isGlob T_Glob {} = True -isGlob (T_NormalWord _ l) = any isGlob l -isGlob _ = False +isGlob t = case t of + T_Extglob {} -> True + T_Glob {} -> True + T_NormalWord _ l -> any isGlob l || hasSplitRange l + _ -> False + where + -- foo[x${var}y] gets parsed as foo,[,x,$var,y], + -- so check if there's such an interval + hasSplitRange l = + let afterBracket = dropWhile (not . isHalfOpenRange) l + in any isClosingRange afterBracket + + isHalfOpenRange t = + case t of + T_Literal _ "[" -> True + _ -> False + + isClosingRange t = + case t of + T_Literal _ str -> ']' `elem` str + _ -> False + -- Is this shell word a constant? isConstant token = diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index 8e0589c..f35fc0d 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -2311,6 +2311,8 @@ prop_checkUnused45= verifyTree checkUnusedAssignments "readonly foo=bar" prop_checkUnused46= verifyTree checkUnusedAssignments "readonly foo=(bar)" prop_checkUnused47= verifyNotTree checkUnusedAssignments "a=1; alias hello='echo $a'" prop_checkUnused48= verifyNotTree checkUnusedAssignments "_a=1" +prop_checkUnused49= verifyNotTree checkUnusedAssignments "declare -A array; key=a; [[ -v array[$key] ]]" + checkUnusedAssignments params t = execWriter (mapM_ warnFor unused) where flow = variableFlow params diff --git a/src/ShellCheck/AnalyzerLib.hs b/src/ShellCheck/AnalyzerLib.hs index 662eff5..5b389d7 100644 --- a/src/ShellCheck/AnalyzerLib.hs +++ b/src/ShellCheck/AnalyzerLib.hs @@ -497,14 +497,8 @@ getModifiedVariables t = -- Count [[ -v foo ]] as an "assignment". -- This is to prevent [ -v foo ] being unassigned or unused. - TC_Unary id _ "-v" token -> do - str <- fmap (takeWhile (/= '[')) $ -- Quoted index - flip getLiteralStringExt token $ \x -> - case x of - T_Glob _ s -> return s -- Unquoted index - _ -> [] - - guard . not . null $ str + TC_Unary id _ "-v" token -> maybeToList $ do + str <- getVariableForTestDashV token return (t, token, str, DataString SourceChecked) TC_Unary _ _ "-n" token -> markAsChecked t token @@ -724,6 +718,20 @@ getIndexReferences s = fromMaybe [] $ do where re = mkRegex "(\\[.*\\])" +-- Given a NormalWord like foo or foo[$bar], get foo. +-- Primarily used to get references for [[ -v foo[bar] ]] +getVariableForTestDashV :: Token -> Maybe String +getVariableForTestDashV t = do + str <- takeWhile ('[' /=) <$> getLiteralStringExt toStr t + guard $ isVariableName str + return str + where + -- foo[bar] gets parsed with [bar] as a glob, so undo that + toStr (T_Glob _ s) = return s + -- Turn foo[$x] into foo[\0] so that we can get the constant array name + -- in a non-constant expression (while filtering out foo$x[$y]) + toStr _ = return "\0" + prop_getOffsetReferences1 = getOffsetReferences ":bar" == ["bar"] prop_getOffsetReferences2 = getOffsetReferences ":bar:baz" == ["bar", "baz"] prop_getOffsetReferences3 = getOffsetReferences "[foo]:bar" == ["bar"] @@ -782,9 +790,8 @@ getReferencedVariables parents t = T_Glob _ s -> return s -- Also when parsed as globs _ -> [] - getIfReference context token = do - str@(h:_) <- getLiteralStringExt literalizer token - when (isDigit h) $ fail "is a number" + getIfReference context token = maybeToList $ do + str <- getVariableForTestDashV token return (context, token, getBracedReference str) isArithmeticAssignment t = case getPath parents t of diff --git a/src/ShellCheck/Checks/Commands.hs b/src/ShellCheck/Checks/Commands.hs index 76ac9a7..d0ada73 100644 --- a/src/ShellCheck/Checks/Commands.hs +++ b/src/ShellCheck/Checks/Commands.hs @@ -845,6 +845,9 @@ checkAliasesExpandEarly = CommandCheck (Exactly "alias") (f . arguments) prop_checkUnsetGlobs1 = verify checkUnsetGlobs "unset foo[1]" prop_checkUnsetGlobs2 = verifyNot checkUnsetGlobs "unset foo" +prop_checkUnsetGlobs3 = verify checkUnsetGlobs "unset foo[$i]" +prop_checkUnsetGlobs4 = verify checkUnsetGlobs "unset foo[x${i}y]" +prop_checkUnsetGlobs5 = verifyNot checkUnsetGlobs "unset foo][" checkUnsetGlobs = CommandCheck (Exactly "unset") (mapM_ check . arguments) where check arg = diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index e559f62..45434a8 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -1372,6 +1372,8 @@ prop_readGlob5 = isOk readGlob "[^[:alpha:]1-9]" prop_readGlob6 = isOk readGlob "[\\|]" prop_readGlob7 = isOk readGlob "[^[]" prop_readGlob8 = isOk readGlob "[*?]" +prop_readGlob9 = isOk readGlob "[!]^]" +prop_readGlob10 = isOk readGlob "[]]" readGlob = readExtglob <|> readSimple <|> readClass <|> readGlobbyLiteral where readSimple = do @@ -1379,22 +1381,25 @@ readGlob = readExtglob <|> readSimple <|> readClass <|> readGlobbyLiteral c <- oneOf "*?" id <- endSpan start return $ T_Glob id [c] - -- Doesn't handle weird things like [^]a] and [$foo]. fixme? readClass = try $ do start <- startSpan char '[' - s <- many1 (predefined <|> readNormalLiteralPart "]" <|> globchars) + negation <- charToString (oneOf "!^") <|> return "" + leadingBracket <- charToString (oneOf "]") <|> return "" + s <- many (predefined <|> readNormalLiteralPart "]" <|> globchars) + guard $ not (null leadingBracket) || not (null s) char ']' id <- endSpan start - return $ T_Glob id $ "[" ++ concat s ++ "]" + return $ T_Glob id $ "[" ++ concat (negation:leadingBracket:s) ++ "]" where - globchars = fmap return . oneOf $ "!$[" ++ extglobStartChars + globchars = charToString $ oneOf $ "![" ++ extglobStartChars predefined = do try $ string "[:" s <- many1 letter string ":]" return $ "[:" ++ s ++ ":]" + charToString = fmap return readGlobbyLiteral = do start <- startSpan c <- extglobStart <|> char '['