Support multidimensional KSH arrays and warn in Bash.

This commit is contained in:
Vidar Holen 2016-08-06 18:40:08 -07:00
parent 6a71ff6f46
commit 13a2070a32
4 changed files with 73 additions and 25 deletions

View file

@ -51,10 +51,10 @@ data Token =
| T_AndIf Id (Token) (Token) | T_AndIf Id (Token) (Token)
| T_Arithmetic Id Token | T_Arithmetic Id Token
| T_Array Id [Token] | T_Array Id [Token]
| T_IndexedElement Id Token Token | T_IndexedElement Id [Token] Token
-- Store the index as string, and parse as arithmetic or string later -- Store the index as string, and parse as arithmetic or string later
| T_UnparsedIndex Id SourcePos String | T_UnparsedIndex Id SourcePos String
| T_Assignment Id AssignmentMode String (Maybe Token) Token | T_Assignment Id AssignmentMode String [Token] Token
| T_Backgrounded Id Token | T_Backgrounded Id Token
| T_Backticked Id [Token] | T_Backticked Id [Token]
| T_Bang Id | T_Bang Id
@ -191,12 +191,15 @@ analyze f g i =
delve (T_IoFile id op file) = d2 op file $ T_IoFile id delve (T_IoFile id op file) = d2 op file $ T_IoFile id
delve (T_HereString id word) = d1 word $ T_HereString id delve (T_HereString id word) = d1 word $ T_HereString id
delve (T_FdRedirect id v t) = d1 t $ T_FdRedirect id v delve (T_FdRedirect id v t) = d1 t $ T_FdRedirect id v
delve (T_Assignment id mode var index value) = do delve (T_Assignment id mode var indices value) = do
a <- roundMaybe index a <- roundAll indices
b <- round value b <- round value
return $ T_Assignment id mode var a b return $ T_Assignment id mode var a b
delve (T_Array id t) = dl t $ T_Array id delve (T_Array id t) = dl t $ T_Array id
delve (T_IndexedElement id t1 t2) = d2 t1 t2 $ T_IndexedElement id delve (T_IndexedElement id indices t) = do
a <- roundAll indices
b <- round t
return $ T_IndexedElement id a b
delve (T_Redirecting id redirs cmd) = do delve (T_Redirecting id redirs cmd) = do
a <- roundAll redirs a <- roundAll redirs
b <- round cmd b <- round cmd

View file

@ -85,6 +85,7 @@ checksFor Bash = [
,checkEchoSed ,checkEchoSed
,checkForDecimals ,checkForDecimals
,checkLocalScope ,checkLocalScope
,checkMultiDimensionalArrays
] ]
runAnalytics :: AnalysisSpec -> [TokenComment] runAnalytics :: AnalysisSpec -> [TokenComment]
@ -943,7 +944,7 @@ checkArrayWithoutIndex params _ =
"Expanding an array without an index only gives the first element." "Expanding an array without an index only gives the first element."
readF _ _ _ = return [] readF _ _ _ = return []
writeF _ (T_Assignment id mode name Nothing _) _ (DataString _) = do writeF _ (T_Assignment id mode name [] _) _ (DataString _) = do
isArray <- gets (isJust . Map.lookup name) isArray <- gets (isJust . Map.lookup name)
return $ if not isArray then [] else return $ if not isArray then [] else
case mode of case mode of
@ -961,7 +962,7 @@ checkArrayWithoutIndex params _ =
isIndexed expr = isIndexed expr =
case expr of case expr of
T_Assignment _ _ _ (Just _) _ -> True T_Assignment _ _ _ (_:_) _ -> True
_ -> False _ -> False
prop_checkStderrRedirect = verify checkStderrRedirect "test 2>&1 > cow" prop_checkStderrRedirect = verify checkStderrRedirect "test 2>&1 > cow"
@ -2279,7 +2280,7 @@ checkPrefixAssignmentReference params t@(T_DollarBraced id value) =
case t of case t of
T_SimpleCommand _ vars (_:_) -> mapM_ checkVar vars T_SimpleCommand _ vars (_:_) -> mapM_ checkVar vars
otherwise -> check rest otherwise -> check rest
checkVar (T_Assignment aId mode aName Nothing value) | checkVar (T_Assignment aId mode aName [] value) |
aName == name && (aId `notElem` idPath) = do aName == name && (aId `notElem` idPath) = do
warn aId 2097 "This assignment is only seen by the forked process." warn aId 2097 "This assignment is only seen by the forked process."
warn id 2098 "This expansion will not see the mentioned assignment." warn id 2098 "This expansion will not see the mentioned assignment."
@ -2559,7 +2560,7 @@ prop_checkOverridingPath8 = verifyNot checkOverridingPath "PATH=$PATH:/stuff"
checkOverridingPath _ (T_SimpleCommand _ vars []) = checkOverridingPath _ (T_SimpleCommand _ vars []) =
mapM_ checkVar vars mapM_ checkVar vars
where where
checkVar (T_Assignment id Assign "PATH" Nothing word) = checkVar (T_Assignment id Assign "PATH" [] word) =
let string = concat $ oversimplify word let string = concat $ oversimplify word
in unless (any (`isInfixOf` string) ["/bin", "/sbin" ]) $ do in unless (any (`isInfixOf` string) ["/bin", "/sbin" ]) $ do
when ('/' `elem` string && ':' `notElem` string) $ notify id when ('/' `elem` string && ':' `notElem` string) $ notify id
@ -2574,7 +2575,7 @@ prop_checkTildeInPath3 = verifyNot checkTildeInPath "PATH=~/bin"
checkTildeInPath _ (T_SimpleCommand _ vars _) = checkTildeInPath _ (T_SimpleCommand _ vars _) =
mapM_ checkVar vars mapM_ checkVar vars
where where
checkVar (T_Assignment id Assign "PATH" Nothing (T_NormalWord _ parts)) = checkVar (T_Assignment id Assign "PATH" [] (T_NormalWord _ parts)) =
when (any (\x -> isQuoted x && hasTilde x) parts) $ when (any (\x -> isQuoted x && hasTilde x) parts) $
warn id 2147 "Literal tilde in PATH works poorly across programs." warn id 2147 "Literal tilde in PATH works poorly across programs."
checkVar _ = return () checkVar _ = return ()
@ -2635,7 +2636,7 @@ checkMultipleAppends params t =
prop_checkSuspiciousIFS1 = verify checkSuspiciousIFS "IFS=\"\\n\"" prop_checkSuspiciousIFS1 = verify checkSuspiciousIFS "IFS=\"\\n\""
prop_checkSuspiciousIFS2 = verifyNot checkSuspiciousIFS "IFS=$'\\t'" prop_checkSuspiciousIFS2 = verifyNot checkSuspiciousIFS "IFS=$'\\t'"
checkSuspiciousIFS params (T_Assignment id Assign "IFS" Nothing value) = checkSuspiciousIFS params (T_Assignment id Assign "IFS" [] value) =
potentially $ do potentially $ do
str <- getLiteralString value str <- getLiteralString value
return $ check str return $ check str
@ -2807,5 +2808,24 @@ checkTrailingBracket _ token =
"]" -> "[" "]" -> "["
x -> x x -> x
prop_checkMultiDimensionalArrays1 = verify checkMultiDimensionalArrays "foo[a][b]=3"
prop_checkMultiDimensionalArrays2 = verifyNot checkMultiDimensionalArrays "foo[a]=3"
prop_checkMultiDimensionalArrays3 = verify checkMultiDimensionalArrays "foo=( [a][b]=c )"
prop_checkMultiDimensionalArrays4 = verifyNot checkMultiDimensionalArrays "foo=( [a]=c )"
prop_checkMultiDimensionalArrays5 = verify checkMultiDimensionalArrays "echo ${foo[bar][baz]}"
prop_checkMultiDimensionalArrays6 = verifyNot checkMultiDimensionalArrays "echo ${foo[bar]}"
checkMultiDimensionalArrays _ token =
case token of
T_Assignment _ _ name (first:second:_) _ -> about second
T_IndexedElement _ (first:second:_) _ -> about second
T_DollarBraced {} ->
when (isMultiDim token) $ about token
_ -> return ()
where
about t = warn (getId t) 2180 "Bash does not support multidimensional arrays. Use 1D or associative arrays."
re = mkRegex "^\\[.*\\]\\[.*\\]" -- Fixme, this matches ${foo:- [][]} and such as well
isMultiDim t = getBracedModifier (bracedString t) `matches` re
return [] return []
runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |]) runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |])

View file

@ -573,6 +573,7 @@ prop_getBracedReference9 = getBracedReference "foo:-bar" == "foo"
prop_getBracedReference10= getBracedReference "foo: -1" == "foo" prop_getBracedReference10= getBracedReference "foo: -1" == "foo"
prop_getBracedReference11= getBracedReference "!os*" == "" prop_getBracedReference11= getBracedReference "!os*" == ""
prop_getBracedReference12= getBracedReference "!os?bar**" == "" prop_getBracedReference12= getBracedReference "!os?bar**" == ""
prop_getBracedReference13= getBracedReference "foo[bar]" == "foo"
getBracedReference s = fromMaybe s $ getBracedReference s = fromMaybe s $
nameExpansion s `mplus` takeName noPrefix `mplus` getSpecial noPrefix `mplus` getSpecial s nameExpansion s `mplus` takeName noPrefix `mplus` getSpecial noPrefix `mplus` getSpecial s
where where
@ -595,6 +596,20 @@ getBracedReference s = fromMaybe s $
return "" return ""
nameExpansion _ = Nothing nameExpansion _ = Nothing
prop_getBracedModifier1 = getBracedModifier "foo:bar:baz" == ":bar:baz"
prop_getBracedModifier2 = getBracedModifier "!var:-foo" == ":-foo"
prop_getBracedModifier3 = getBracedModifier "foo[bar]" == "[bar]"
getBracedModifier s = fromMaybe "" . listToMaybe $ do
let var = getBracedReference s
a <- dropModifier s
dropPrefix var a
where
dropPrefix [] t = return t
dropPrefix (a:b) (c:d) | a == c = dropPrefix b d
dropPrefix _ _ = []
dropModifier (c:rest) | c `elem` "#!" = [rest, c:rest]
dropModifier x = [x]
-- Useful generic functions -- Useful generic functions
potentially :: Monad m => Maybe (m ()) -> m () potentially :: Monad m => Maybe (m ()) -> m ()

View file

@ -181,6 +181,7 @@ getNextIdAt sourcepos = do
return newId return newId
where incId (Id n) = Id $ n+1 where incId (Id n) = Id $ n+1
getNextId :: Monad m => SCParser m Id
getNextId = do getNextId = do
pos <- getPosition pos <- getPosition
getNextIdAt pos getNextIdAt pos
@ -2335,7 +2336,7 @@ readAssignmentWord = try $ do
variable <- readVariableName variable <- readVariableName
optional (readNormalDollar >> parseNoteAt pos ErrorC optional (readNormalDollar >> parseNoteAt pos ErrorC
1067 "For indirection, use (associative) arrays or 'read \"var$n\" <<< \"value\"'") 1067 "For indirection, use (associative) arrays or 'read \"var$n\" <<< \"value\"'")
index <- optionMaybe readArrayIndex indices <- many readArrayIndex
hasLeftSpace <- liftM (not . null) spacing hasLeftSpace <- liftM (not . null) spacing
pos <- getPosition pos <- getPosition
op <- readAssignmentOp op <- readAssignmentOp
@ -2347,13 +2348,13 @@ readAssignmentWord = try $ do
parseNoteAt pos WarningC 1007 parseNoteAt pos WarningC 1007
"Remove space after = if trying to assign a value (for empty string, use var='' ... )." "Remove space after = if trying to assign a value (for empty string, use var='' ... )."
value <- readEmptyLiteral value <- readEmptyLiteral
return $ T_Assignment id op variable index value return $ T_Assignment id op variable indices value
else do else do
when (hasLeftSpace || hasRightSpace) $ when (hasLeftSpace || hasRightSpace) $
parseNoteAt pos ErrorC 1068 "Don't put spaces around the = in assignments." parseNoteAt pos ErrorC 1068 "Don't put spaces around the = in assignments."
value <- readArray <|> readNormalWord value <- readArray <|> readNormalWord
spacing spacing
return $ T_Assignment id op variable index value return $ T_Assignment id op variable indices value
where where
readAssignmentOp = do readAssignmentOp = do
pos <- getPosition pos <- getPosition
@ -2380,6 +2381,7 @@ readArrayIndex = do
char ']' char ']'
return $ T_UnparsedIndex id pos str return $ T_UnparsedIndex id pos str
readArray :: Monad m => SCParser m Token
readArray = called "array assignment" $ do readArray = called "array assignment" $ do
id <- getNextId id <- getNextId
char '(' char '('
@ -2392,7 +2394,7 @@ readArray = called "array assignment" $ do
readIndexed = do readIndexed = do
id <- getNextId id <- getNextId
index <- try $ do index <- try $ do
x <- readArrayIndex x <- many1 readArrayIndex
char '=' char '='
return x return x
value <- readNormalWord <|> nothing value <- readNormalWord <|> nothing
@ -2706,21 +2708,29 @@ reparseIndices root =
where where
associative = getAssociativeArrays root associative = getAssociativeArrays root
isAssociative s = s `elem` associative isAssociative s = s `elem` associative
f (T_Assignment id mode name (Just (T_UnparsedIndex _ pos src)) value) = do f (T_Assignment id mode name indices value) = do
new <- parsed name pos src newIndices <- mapM (fixAssignmentIndex name) indices
return $ T_Assignment id mode name (Just new) value newValue <- case value of
f (T_Assignment id mode name Nothing (T_Array id2 words)) = do (T_Array id2 words) -> do
newwords <- mapM (fix name) words newWords <- mapM (fixIndexElement name) words
return $ T_Assignment id mode name Nothing (T_Array id2 newwords) return $ T_Array id2 newWords
x -> return x
return $ T_Assignment id mode name newIndices newValue
f t = return t f t = return t
fix name word = fixIndexElement name word =
case word of case word of
T_IndexedElement id (T_UnparsedIndex _ pos src) value -> do T_IndexedElement id indices value -> do
new <- parsed name pos src new <- mapM (fixAssignmentIndex name) indices
return $ T_IndexedElement id new value return $ T_IndexedElement id new value
otherwise -> return word otherwise -> return word
fixAssignmentIndex name word =
case word of
T_UnparsedIndex id pos src -> do
parsed name pos src
otherwise -> return word
parsed name pos src = parsed name pos src =
if isAssociative name if isAssociative name
then subParse pos (called "associative array index" $ readIndexSpan) src then subParse pos (called "associative array index" $ readIndexSpan) src