Improve warnings for $ in (()). Also improves array subscripts.
This commit is contained in:
parent
f9c346cfd7
commit
2f3533fff6
|
@ -34,6 +34,7 @@ data CaseType = CaseBreak | CaseFallThrough | CaseContinue deriving (Show, Eq)
|
||||||
data Token =
|
data Token =
|
||||||
TA_Binary Id String Token Token
|
TA_Binary Id String Token Token
|
||||||
| TA_Expansion Id [Token]
|
| TA_Expansion Id [Token]
|
||||||
|
| TA_Index Id Token
|
||||||
| TA_Sequence Id [Token]
|
| TA_Sequence Id [Token]
|
||||||
| TA_Trinary Id Token Token Token
|
| TA_Trinary Id Token Token Token
|
||||||
| TA_Unary Id String Token
|
| TA_Unary Id String Token
|
||||||
|
@ -245,6 +246,7 @@ analyze f g i =
|
||||||
c <- round t3
|
c <- round t3
|
||||||
return $ TA_Trinary id a b c
|
return $ TA_Trinary id a b c
|
||||||
delve (TA_Expansion id t) = dl t $ TA_Expansion id
|
delve (TA_Expansion id t) = dl t $ TA_Expansion id
|
||||||
|
delve (TA_Index id t) = d1 t $ TA_Index id
|
||||||
delve (T_Annotation id anns t) = d1 t $ T_Annotation id anns
|
delve (T_Annotation id anns t) = d1 t $ T_Annotation id anns
|
||||||
delve t = return t
|
delve t = return t
|
||||||
|
|
||||||
|
@ -330,6 +332,7 @@ getId t = case t of
|
||||||
TA_Sequence id _ -> id
|
TA_Sequence id _ -> id
|
||||||
TA_Trinary id _ _ _ -> id
|
TA_Trinary id _ _ _ -> id
|
||||||
TA_Expansion id _ -> id
|
TA_Expansion id _ -> id
|
||||||
|
TA_Index id _ -> id
|
||||||
T_ProcSub id _ _ -> id
|
T_ProcSub id _ _ -> id
|
||||||
T_Glob id _ -> id
|
T_Glob id _ -> id
|
||||||
T_ForArithmetic id _ _ _ _ -> id
|
T_ForArithmetic id _ _ _ _ -> id
|
||||||
|
|
|
@ -1205,19 +1205,28 @@ prop_checkArithmeticDeref5 = verifyNot checkArithmeticDeref "(($1))"
|
||||||
prop_checkArithmeticDeref6 = verify checkArithmeticDeref "(( a[$i] ))"
|
prop_checkArithmeticDeref6 = verify checkArithmeticDeref "(( a[$i] ))"
|
||||||
prop_checkArithmeticDeref7 = verifyNot checkArithmeticDeref "(( 10#$n ))"
|
prop_checkArithmeticDeref7 = verifyNot checkArithmeticDeref "(( 10#$n ))"
|
||||||
prop_checkArithmeticDeref8 = verifyNot checkArithmeticDeref "let i=$i+1"
|
prop_checkArithmeticDeref8 = verifyNot checkArithmeticDeref "let i=$i+1"
|
||||||
|
prop_checkArithmeticDeref9 = verifyNot checkArithmeticDeref "(( a[foo] ))"
|
||||||
|
prop_checkArithmeticDeref10= verifyNot checkArithmeticDeref "(( a[\\$foo] ))"
|
||||||
|
prop_checkArithmeticDeref11= verifyNot checkArithmeticDeref "a[$foo]=wee"
|
||||||
|
prop_checkArithmeticDeref12= verify checkArithmeticDeref "for ((i=0; $i < 3; i)); do true; done"
|
||||||
checkArithmeticDeref params t@(TA_Expansion _ [T_DollarBraced id l]) =
|
checkArithmeticDeref params t@(TA_Expansion _ [T_DollarBraced id l]) =
|
||||||
unless ((isException $ bracedString l) || (not isNormal)) $
|
unless (isException $ bracedString l) getWarning
|
||||||
style id 2004 "$ on variables in (( )) is unnecessary."
|
|
||||||
where
|
where
|
||||||
isException [] = True
|
isException [] = True
|
||||||
isException s = any (`elem` "/.:#%?*@") s || isDigit (head s)
|
isException s = any (`elem` "/.:#%?*@") s || isDigit (head s)
|
||||||
isNormal = fromMaybe True $ msum $ map isNormalContext $ (parents params t)
|
getWarning = fromMaybe noWarning . msum . map warningFor $ parents params t
|
||||||
isNormalContext t =
|
warningFor t =
|
||||||
case t of
|
case t of
|
||||||
T_Arithmetic {} -> return True
|
T_Arithmetic {} -> return normalWarning
|
||||||
T_DollarArithmetic {} -> return True
|
T_DollarArithmetic {} -> return normalWarning
|
||||||
T_SimpleCommand {} -> return False
|
T_ForArithmetic {} -> return normalWarning
|
||||||
_ -> fail "Irrelevant"
|
TA_Index {} -> return indexWarning
|
||||||
|
T_SimpleCommand {} -> return noWarning
|
||||||
|
_ -> Nothing
|
||||||
|
|
||||||
|
normalWarning = style id 2004 "$/${} is unnecessary on arithmetic variables."
|
||||||
|
indexWarning = style id 2149 "Remove $/${} for numeric index, or escape it for string."
|
||||||
|
noWarning = return ()
|
||||||
checkArithmeticDeref _ _ = return ()
|
checkArithmeticDeref _ _ = return ()
|
||||||
|
|
||||||
prop_checkArithmeticBadOctal1 = verify checkArithmeticBadOctal "(( 0192 ))"
|
prop_checkArithmeticBadOctal1 = verify checkArithmeticBadOctal "(( 0192 ))"
|
||||||
|
|
|
@ -489,10 +489,10 @@ readArithmeticContents =
|
||||||
|
|
||||||
readArrayIndex = do
|
readArrayIndex = do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
start <- literal "["
|
char '['
|
||||||
middle <- readArithmeticContents
|
middle <- readArithmeticContents
|
||||||
end <- literal "]"
|
char ']'
|
||||||
return $ T_NormalWord id [start, middle, end]
|
return $ TA_Index id middle
|
||||||
|
|
||||||
literal s = do
|
literal s = do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
|
@ -596,7 +596,7 @@ readArithmeticContents =
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
op <- try $ string "++" <|> string "--"
|
op <- try $ string "++" <|> string "--"
|
||||||
spacing
|
spacing
|
||||||
return $ TA_Unary id ("|" ++ op) x
|
return $ TA_Unary id ('|':op) x
|
||||||
<|>
|
<|>
|
||||||
return x
|
return x
|
||||||
|
|
||||||
|
@ -1816,6 +1816,7 @@ prop_readAssignmentWord8 = isOk readAssignmentWord "a[4''$(cat foo)]=42"
|
||||||
prop_readAssignmentWord9 = isOk readAssignmentWord "IFS= "
|
prop_readAssignmentWord9 = isOk readAssignmentWord "IFS= "
|
||||||
prop_readAssignmentWord10= isWarning readAssignmentWord "foo$n=42"
|
prop_readAssignmentWord10= isWarning readAssignmentWord "foo$n=42"
|
||||||
prop_readAssignmentWord11= isOk readAssignmentWord "foo=([a]=b [c] [d]= [e f )"
|
prop_readAssignmentWord11= isOk readAssignmentWord "foo=([a]=b [c] [d]= [e f )"
|
||||||
|
prop_readAssignmentWord12= isOk readAssignmentWord "a[b <<= 3 + c]='thing'"
|
||||||
readAssignmentWord = try $ do
|
readAssignmentWord = try $ do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
pos <- getPosition
|
pos <- getPosition
|
||||||
|
@ -1851,14 +1852,10 @@ readAssignmentWord = try $ do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
return $ T_Literal id ""
|
return $ T_Literal id ""
|
||||||
|
|
||||||
-- This is only approximate. Fixme?
|
|
||||||
-- * Bash allows foo[' ' "" $(true) 2 ``]=var
|
|
||||||
-- * foo[bar] dereferences bar
|
|
||||||
readArrayIndex = do
|
readArrayIndex = do
|
||||||
char '['
|
char '['
|
||||||
optional space
|
optional space
|
||||||
x <- readNormalishWord "]"
|
x <- readArithmeticContents
|
||||||
optional space
|
|
||||||
char ']'
|
char ']'
|
||||||
return x
|
return x
|
||||||
|
|
||||||
|
|
Loading…
Reference in New Issue