Fixed incorrect n=1 & n=foo$n and same for $((n++))
This commit is contained in:
parent
5d26f627cf
commit
ad9db04856
|
@ -35,6 +35,8 @@ basicChecks = [
|
||||||
,checkNumberComparisons
|
,checkNumberComparisons
|
||||||
,checkNoaryWasBinary
|
,checkNoaryWasBinary
|
||||||
,checkBraceExpansionVars
|
,checkBraceExpansionVars
|
||||||
|
,checkForDecimals
|
||||||
|
,checkDivBeforeMult
|
||||||
]
|
]
|
||||||
|
|
||||||
modifyMap = modify
|
modifyMap = modify
|
||||||
|
@ -239,6 +241,17 @@ checkBraceExpansionVars (T_BraceExpansion id s) | '$' `elem` s =
|
||||||
addNoteFor id $ Note WarningC $ "You can't use variables in brace expansions."
|
addNoteFor id $ Note WarningC $ "You can't use variables in brace expansions."
|
||||||
checkBraceExpansionVars _ = return ()
|
checkBraceExpansionVars _ = return ()
|
||||||
|
|
||||||
|
prop_checkForDecimals = verify checkForDecimals "((3.14*c))"
|
||||||
|
checkForDecimals (TA_Literal id s) | any (== '.') s = do
|
||||||
|
addNoteFor id $ Note ErrorC $ "(( )) doesn't support decimals. Use bc or awk."
|
||||||
|
checkForDecimals _ = return ()
|
||||||
|
|
||||||
|
prop_checkDivBeforeMult = verify checkDivBeforeMult "echo $((c/n*100))"
|
||||||
|
prop_checkDivBeforeMult2 = verifyNot checkDivBeforeMult "echo $((c*100/n))"
|
||||||
|
checkDivBeforeMult (TA_Binary _ "*" (TA_Binary id "/" _ _) _) = do
|
||||||
|
addNoteFor id $ Note InfoC $ "Increase precision by replacing a/b*c with a*c/b"
|
||||||
|
checkDivBeforeMult _ = return ()
|
||||||
|
|
||||||
allModifiedVariables t = snd $ runState (doAnalysis (\x -> modify $ (++) (getModifiedVariables x)) t) []
|
allModifiedVariables t = snd $ runState (doAnalysis (\x -> modify $ (++) (getModifiedVariables x)) t) []
|
||||||
|
|
||||||
--- Subshell detection
|
--- Subshell detection
|
||||||
|
@ -249,6 +262,10 @@ prop_subshellAssignmentCheck3 = verifyFull subshellAssignmentCheck "( A=foo;
|
||||||
prop_subshellAssignmentCheck4 = verifyNotFull subshellAssignmentCheck "( A=foo; rm $A; )"
|
prop_subshellAssignmentCheck4 = verifyNotFull subshellAssignmentCheck "( A=foo; rm $A; )"
|
||||||
prop_subshellAssignmentCheck5 = verifyFull subshellAssignmentCheck "cat foo | while read cow; do true; done; echo $cow;"
|
prop_subshellAssignmentCheck5 = verifyFull subshellAssignmentCheck "cat foo | while read cow; do true; done; echo $cow;"
|
||||||
prop_subshellAssignmentCheck6 = verifyFull subshellAssignmentCheck "( export lol=$(ls); ); echo $lol;"
|
prop_subshellAssignmentCheck6 = verifyFull subshellAssignmentCheck "( export lol=$(ls); ); echo $lol;"
|
||||||
|
prop_subshellAssignmentCheck7 = verifyFull subshellAssignmentCheck "cmd | while read foo; do (( n++ )); done; echo \"$n lines\""
|
||||||
|
prop_subshellAssignmentCheck8 = verifyFull subshellAssignmentCheck "n=3 & echo $((n++))"
|
||||||
|
prop_subshellAssignmentCheck9 = verifyFull subshellAssignmentCheck "read n & n=foo$n"
|
||||||
|
prop_subshellAssignmentCheck10 = verifyFull subshellAssignmentCheck "(( n <<= 3 )) & (( n |= 4 )) &"
|
||||||
subshellAssignmentCheck t map =
|
subshellAssignmentCheck t map =
|
||||||
let flow = getVariableFlow t
|
let flow = getVariableFlow t
|
||||||
check = findSubshelled flow [("oops",[])] Map.empty
|
check = findSubshelled flow [("oops",[])] Map.empty
|
||||||
|
@ -279,6 +296,12 @@ getModifiedVariables t =
|
||||||
c@(T_SimpleCommand _ _ _) ->
|
c@(T_SimpleCommand _ _ _) ->
|
||||||
getModifiedVariableCommand c
|
getModifiedVariableCommand c
|
||||||
|
|
||||||
|
TA_Unary _ "++|" (TA_Variable id name) -> [(id, name)]
|
||||||
|
TA_Unary _ "|++" (TA_Variable id name) -> [(id, name)]
|
||||||
|
TA_Binary _ op (TA_Variable id name) _ -> if any (==op) ["=", "*=", "/=", "%=", "+=", "-=", "<<=", ">>=", "&=", "^=", "|="]
|
||||||
|
then [(id,name)]
|
||||||
|
else []
|
||||||
|
|
||||||
--Points to 'for' rather than variable
|
--Points to 'for' rather than variable
|
||||||
T_ForIn id str _ _ -> [(id, str)]
|
T_ForIn id str _ _ -> [(id, str)]
|
||||||
_ -> []
|
_ -> []
|
||||||
|
@ -305,23 +328,23 @@ getBracedReference s = takeWhile (\x -> not $ x `elem` ":[#%/^,") $ dropWhile (=
|
||||||
getReferencedVariables t =
|
getReferencedVariables t =
|
||||||
case t of
|
case t of
|
||||||
T_DollarBraced id str -> map (\x -> (id, x)) $ [getBracedReference str]
|
T_DollarBraced id str -> map (\x -> (id, x)) $ [getBracedReference str]
|
||||||
T_Arithmetic _ _ -> [] -- TODO
|
TA_Variable id str -> [(id,str)]
|
||||||
_ -> []
|
x -> []
|
||||||
|
|
||||||
|
|
||||||
startScope t =
|
startScope t =
|
||||||
let scopeType = leadType t
|
let scopeType = leadType t
|
||||||
written = getModifiedVariables t
|
|
||||||
read = getReferencedVariables t
|
|
||||||
in do
|
in do
|
||||||
when (scopeType /= NoneScope) $ modify ((StackScope scopeType):)
|
when (scopeType /= NoneScope) $ modify ((StackScope scopeType):)
|
||||||
mapM_ (\v -> modify ((Assignment v):)) written
|
|
||||||
mapM_ (\v -> modify ((Reference v):)) read
|
|
||||||
|
|
||||||
endScope t =
|
endScope t =
|
||||||
let scopeType = leadType t
|
let scopeType = leadType t
|
||||||
|
written = getModifiedVariables t
|
||||||
|
read = getReferencedVariables t
|
||||||
in do
|
in do
|
||||||
when (scopeType /= NoneScope) $ modify ((StackScopeEnd):)
|
when (scopeType /= NoneScope) $ modify ((StackScopeEnd):)
|
||||||
|
mapM_ (\v -> modify ((Reference v):)) read
|
||||||
|
mapM_ (\v -> modify ((Assignment v):)) written
|
||||||
|
|
||||||
getVariableFlow t =
|
getVariableFlow t =
|
||||||
let (_, stack) = runState (doStackAnalysis startScope endScope t) []
|
let (_, stack) = runState (doStackAnalysis startScope endScope t) []
|
||||||
|
|
|
@ -459,6 +459,7 @@ analyze f g i t =
|
||||||
delve (T_NormalWord id list) = dl list $ T_NormalWord id
|
delve (T_NormalWord id list) = dl list $ T_NormalWord id
|
||||||
delve (T_DoubleQuoted id list) = dl list $ T_DoubleQuoted id
|
delve (T_DoubleQuoted id list) = dl list $ T_DoubleQuoted id
|
||||||
delve (T_DollarExpansion id list) = dl list $ T_DollarExpansion id
|
delve (T_DollarExpansion id list) = dl list $ T_DollarExpansion id
|
||||||
|
delve (T_DollarArithmetic id c) = d1 c $ T_DollarArithmetic id
|
||||||
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
|
||||||
|
@ -475,6 +476,7 @@ analyze f g i t =
|
||||||
delve (T_OrIf id t u) = d2 t u $ T_OrIf id
|
delve (T_OrIf id t u) = d2 t u $ T_OrIf id
|
||||||
delve (T_Backgrounded id l) = d1 l $ T_Backgrounded id
|
delve (T_Backgrounded id l) = d1 l $ T_Backgrounded id
|
||||||
delve (T_Subshell id l) = dl l $ T_Subshell id
|
delve (T_Subshell id l) = dl l $ T_Subshell id
|
||||||
|
delve (T_Arithmetic id c) = d1 c $ T_Arithmetic id
|
||||||
delve (T_IfExpression id conditions elses) = do
|
delve (T_IfExpression id conditions elses) = do
|
||||||
newConds <- mapM (\(c, t) -> do
|
newConds <- mapM (\(c, t) -> do
|
||||||
x <- mapM round c
|
x <- mapM round c
|
||||||
|
@ -518,7 +520,6 @@ analyze f g i t =
|
||||||
delve (TA_Expansion id t) = d1 t $ TA_Expansion id
|
delve (TA_Expansion id t) = d1 t $ TA_Expansion id
|
||||||
delve t = return t
|
delve t = return t
|
||||||
|
|
||||||
|
|
||||||
blank = const $ return ()
|
blank = const $ return ()
|
||||||
doAnalysis f t = analyze f blank id t
|
doAnalysis f t = analyze f blank id t
|
||||||
doStackAnalysis startToken endToken t = analyze startToken endToken id t
|
doStackAnalysis startToken endToken t = analyze startToken endToken id t
|
||||||
|
@ -1279,3 +1280,4 @@ parseShell filename contents = do
|
||||||
(Right (script, map, notes), parsenotes) -> ParseResult (Just (script, map)) (nub $ sortNotes $ notes ++ parsenotes)
|
(Right (script, map, notes), parsenotes) -> ParseResult (Just (script, map)) (nub $ sortNotes $ notes ++ parsenotes)
|
||||||
(Left err, p) -> ParseResult Nothing (nub $ sortNotes $ p ++ ([makeErrorFor err]))
|
(Left err, p) -> ParseResult Nothing (nub $ sortNotes $ p ++ ([makeErrorFor err]))
|
||||||
|
|
||||||
|
lt x = trace (show x) x
|
||||||
|
|
|
@ -19,7 +19,6 @@ shellCheck script =
|
||||||
|
|
||||||
data ShellCheckComment = ShellCheckComment { scLine :: Int, scColumn :: Int, scSeverity :: String, scMessage :: String }
|
data ShellCheckComment = ShellCheckComment { scLine :: Int, scColumn :: Int, scSeverity :: String, scMessage :: String }
|
||||||
|
|
||||||
|
|
||||||
instance Show ShellCheckComment where
|
instance Show ShellCheckComment where
|
||||||
show c = concat ["(", show $ scLine c, ",", show $ scColumn c, ") ", scSeverity c, ": ", scMessage c]
|
show c = concat ["(", show $ scLine c, ",", show $ scColumn c, ") ", scSeverity c, ": ", scMessage c]
|
||||||
|
|
||||||
|
|
|
@ -0,0 +1,3 @@
|
||||||
|
n=0;
|
||||||
|
mycmd | while read foo; do rm "$foo"; ((n++)); done
|
||||||
|
echo "Deleted $n files"
|
Loading…
Reference in New Issue