Improved assignment parsing: track indices and += vs =

This commit is contained in:
Vidar Holen 2013-10-06 14:44:43 -07:00
parent 710a28c572
commit b439f02b8e
3 changed files with 30 additions and 14 deletions

View File

@ -25,6 +25,7 @@ data Id = Id Int deriving (Show, Eq, Ord)
data Quoted = Quoted | Unquoted deriving (Show, Eq)
data Dashed = Dashed | Undashed deriving (Show, Eq)
data AssignmentMode = Assign | Append deriving (Show, Eq)
data Token =
TA_Base Id String Token
@ -45,7 +46,7 @@ data Token =
| T_AndIf Id (Token) (Token)
| T_Arithmetic Id Token
| T_Array Id [Token]
| T_Assignment Id String Token
| T_Assignment Id AssignmentMode String (Maybe Token) Token
| T_Backgrounded Id Token
| T_Backticked Id [Token]
| T_Bang Id
@ -137,6 +138,11 @@ analyze f g i t =
return . i $ newT
roundAll = mapM round
roundMaybe Nothing = return Nothing
roundMaybe (Just v) = do
s <- round v
return (Just s)
dl l v = do
x <- roundAll l
return $ v x
@ -162,7 +168,10 @@ analyze f g i t =
delve (T_IoFile id op file) = d2 op file $ T_IoFile 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_Assignment id v t) = d1 t $ T_Assignment id v
delve (T_Assignment id mode var index value) = do
a <- roundMaybe index
b <- round value
return $ T_Assignment id mode var a b
delve (T_Array id t) = dl t $ T_Array id
delve (T_Redirecting id redirs cmd) = do
a <- roundAll redirs
@ -279,7 +288,7 @@ getId t = case t of
T_HereDoc id _ _ _ _ -> id
T_HereString id _ -> id
T_FdRedirect id _ _ -> id
T_Assignment id _ _ -> id
T_Assignment id _ _ _ _ -> id
T_Array id _ -> id
T_Redirecting id _ _ -> id
T_SimpleCommand id _ _ -> id

View File

@ -285,7 +285,7 @@ prop_checkAssignAteCommand2 = verify checkAssignAteCommand "A=ls --sort=$foo"
prop_checkAssignAteCommand3 = verify checkAssignAteCommand "A=cat foo | grep bar"
prop_checkAssignAteCommand4 = verifyNot checkAssignAteCommand "A=foo ls -l"
prop_checkAssignAteCommand5 = verifyNot checkAssignAteCommand "PAGER=cat grep bar"
checkAssignAteCommand (T_SimpleCommand id ((T_Assignment _ _ assignmentTerm):[]) (firstWord:_)) =
checkAssignAteCommand (T_SimpleCommand id ((T_Assignment _ _ _ _ assignmentTerm):[]) (firstWord:_)) =
when ("-" `isPrefixOf` (concat $ deadSimple firstWord) ||
(isCommonCommand (getLiteralString assignmentTerm) && not (isCommonCommand (getLiteralString firstWord)))) $
warn id "To assign the output of a command, use var=$(cmd) ."
@ -880,7 +880,7 @@ inUnquotableContext tree t =
TA_Binary _ _ _ _ -> True
TA_Trinary _ _ _ _ -> True
TA_Expansion _ _ -> True
T_Assignment _ _ _ -> True
T_Assignment _ _ _ _ _ -> True
T_Redirecting _ _ _ ->
any (isCommand t) ["local", "declare", "typeset", "export"]
T_DoubleQuoted _ _ -> True
@ -1138,7 +1138,7 @@ prop_checkPS15 = verifyNot checkPS1Assignments "PS1='\\[\\033[1;35m\\]\\$ '"
prop_checkPS16 = verifyNot checkPS1Assignments "PS1='\\[\\e1m\\e[1m\\]\\$ '"
prop_checkPS17 = verifyNot checkPS1Assignments "PS1='e033x1B'"
prop_checkPS18 = verifyNot checkPS1Assignments "PS1='\\[\\e\\]'"
checkPS1Assignments (T_Assignment _ "PS1" word) = warnFor word
checkPS1Assignments (T_Assignment _ _ "PS1" _ word) = warnFor word
where
warnFor word =
let contents = concat $ deadSimple word in
@ -1386,7 +1386,7 @@ getModifiedVariables t =
case t of
T_SimpleCommand _ vars [] ->
concatMap (\x -> case x of
T_Assignment id name w ->
T_Assignment id _ name _ w ->
[(x, x, name, DataFrom [w])]
_ -> []
) vars
@ -1411,7 +1411,7 @@ getReferencedVariableCommand base@(T_SimpleCommand _ _ ((T_NormalWord _ ((T_Lite
"export" -> concatMap getReference rest
_ -> [(base,base, x)]
where
getReference t@(T_Assignment _ name value) = [(t, t, name)]
getReference t@(T_Assignment _ _ name _ value) = [(t, t, name)]
getReference t@(T_NormalWord _ [T_Literal _ name]) | not ("-" `isPrefixOf` name) = [(t, t, name)]
getReference _ = []
@ -1446,7 +1446,7 @@ getModifiedVariableCommand base@(T_SimpleCommand _ _ ((T_NormalWord _ ((T_Litera
[(base, t, s, DataExternal)]
getLiteral x = []
getModifierParam t@(T_Assignment _ name value) =
getModifierParam t@(T_Assignment _ _ name _ value) =
[(base, t, name, DataFrom [value])]
getModifierParam _ = []
@ -1464,6 +1464,7 @@ getReferencedVariables t =
case t of
T_DollarBraced id l -> map (\x -> (t, t, x)) $ [getBracedReference $ bracedString l]
TA_Variable id str -> [(t, t, str)]
T_Assignment id Append str _ _ -> [(t, t, str)]
x -> getReferencedVariableCommand x
getVariableFlow t =
@ -1692,6 +1693,7 @@ prop_checkUnused7 = verifyNotFull checkUnusedAssignments "var=2; $((var))"
prop_checkUnused8 = verifyFull checkUnusedAssignments "var=2; var=3;"
prop_checkUnused9 = verifyNotFull checkUnusedAssignments "read ''"
prop_checkUnused10= verifyNotFull checkUnusedAssignments "read -p 'test: '"
prop_checkUnused11= verifyNotFull checkUnusedAssignments "bar=5; export foo[$bar]=3"
checkUnusedAssignments t = snd $ runState (mapM_ checkAssignment flow) []
where
flow = getVariableFlow t

View File

@ -1143,7 +1143,7 @@ makeSimpleCommand id1 id2 prefix cmd suffix =
in
T_Redirecting id1 redirs $ T_SimpleCommand id2 assigns args
where
assignment (T_Assignment _ _ _) = True
assignment (T_Assignment _ _ _ _ _) = True
assignment _ = False
redirection (T_FdRedirect _ _ _) = True
redirection _ = False
@ -1538,35 +1538,40 @@ readAssignmentWord = try $ do
variable <- readVariableName
optional (readNormalDollar >> parseNoteAt pos ErrorC
"For indirection, use (associative) arrays or 'read \"var$n\" <<< \"value\"'")
optional readArrayIndex -- Throws away the index. Fixme?
index <- optionMaybe readArrayIndex
space <- spacing
pos <- getPosition
op <- string "+=" <|> string "=" -- analysis doesn't treat += as a reference. fixme?
op <- readAssignmentOp
space2 <- spacing
if space == "" && space2 /= ""
then do
when (variable /= "IFS") $
parseNoteAt pos InfoC $ "Note that 'var= value' (with space after equals sign) is similar to 'var=\"\"; value'."
value <- readEmptyLiteral
return $ T_Assignment id variable value
return $ T_Assignment id op variable index value
else do
when (space /= "" || space2 /= "") $
parseNoteAt pos ErrorC "Don't put spaces around the = in assignments."
value <- readArray <|> readNormalWord
spacing
return $ T_Assignment id variable value
return $ T_Assignment id op variable index value
where
readAssignmentOp =
(string "+=" >> return Append) <|> (string "=" >> return Assign)
readEmptyLiteral = do
id <- getNextId
return $ T_Literal id ""
-- This is only approximate. Fixme?
-- * Bash allows foo[' ' "" $(true) 2 ``]=var
-- * foo[bar] dereferences bar
readArrayIndex = do
char '['
optional space
x <- readNormalishWord "]"
optional space
char ']'
return x
readArray = called "array assignment" $ do
id <- getNextId