Warn about client side expansion in ssh strings/heredocs.
This commit is contained in:
parent
07b1fd6f44
commit
de1fa61560
|
@ -80,7 +80,7 @@ data Token =
|
||||||
| T_GREATAND Id
|
| T_GREATAND Id
|
||||||
| T_Glob Id String
|
| T_Glob Id String
|
||||||
| T_Greater Id
|
| T_Greater Id
|
||||||
| T_HereDoc Id Bool Bool String
|
| T_HereDoc Id Bool Bool String String
|
||||||
| T_HereString Id Token
|
| T_HereString Id Token
|
||||||
| T_If Id
|
| T_If Id
|
||||||
| T_IfExpression Id [([Token],[Token])] [Token]
|
| T_IfExpression Id [([Token],[Token])] [Token]
|
||||||
|
@ -272,7 +272,7 @@ getId t = case t of
|
||||||
T_DollarArithmetic id _ -> id
|
T_DollarArithmetic id _ -> id
|
||||||
T_BraceExpansion id _ -> id
|
T_BraceExpansion id _ -> id
|
||||||
T_IoFile id _ _ -> id
|
T_IoFile id _ _ -> id
|
||||||
T_HereDoc id _ _ _ -> id
|
T_HereDoc id _ _ _ _ -> id
|
||||||
T_HereString id _ -> id
|
T_HereString id _ -> id
|
||||||
T_FdRedirect id _ _ -> id
|
T_FdRedirect id _ _ -> id
|
||||||
T_Assignment id _ _ -> id
|
T_Assignment id _ _ -> id
|
||||||
|
|
|
@ -129,6 +129,8 @@ basicChecks = [
|
||||||
,checkSpuriousExpansion
|
,checkSpuriousExpansion
|
||||||
,checkUnusedEchoEscapes
|
,checkUnusedEchoEscapes
|
||||||
,checkDollarBrackets
|
,checkDollarBrackets
|
||||||
|
,checkSshHereDoc
|
||||||
|
,checkSshCommandString
|
||||||
]
|
]
|
||||||
treeChecks = [
|
treeChecks = [
|
||||||
checkUnquotedExpansions
|
checkUnquotedExpansions
|
||||||
|
@ -1287,6 +1289,38 @@ checkDollarBrackets (T_DollarBracket id _) =
|
||||||
style id "Use $((..)) instead of deprecated $[..]"
|
style id "Use $((..)) instead of deprecated $[..]"
|
||||||
checkDollarBrackets _ = return ()
|
checkDollarBrackets _ = return ()
|
||||||
|
|
||||||
|
prop_checkSshHereDoc1 = verify checkSshHereDoc "ssh host << foo\necho $PATH\nfoo"
|
||||||
|
prop_checkSshHereDoc2 = verifyNot checkSshHereDoc "ssh host << 'foo'\necho $PATH\nfoo"
|
||||||
|
checkSshHereDoc (T_Redirecting _ redirs cmd)
|
||||||
|
| cmd `isCommand` "ssh" =
|
||||||
|
mapM_ checkHereDoc redirs
|
||||||
|
where
|
||||||
|
hasVariables = mkRegex "[`$]"
|
||||||
|
checkHereDoc (T_FdRedirect _ _ (T_HereDoc id _ False token str))
|
||||||
|
| isJust $ matchRegex hasVariables str =
|
||||||
|
warn id $ "Quote '" ++ token ++ "' to make here document expansions happen on the server side rather than on the client."
|
||||||
|
checkHereDoc _ = return ()
|
||||||
|
checkSshHereDoc _ = return ()
|
||||||
|
|
||||||
|
-- This is hard to get right without properly parsing ssh args
|
||||||
|
prop_checkSshCmdStr1 = verify checkSshCommandString "ssh host \"echo $PS1\""
|
||||||
|
prop_checkSshCmdStr2 = verifyNot checkSshCommandString "ssh host \"ls foo\""
|
||||||
|
prop_checkSshCmdStr3 = verifyNot checkSshCommandString "ssh \"$host\""
|
||||||
|
checkSshCommandString = checkCommand "ssh" f
|
||||||
|
where
|
||||||
|
nonOptions args =
|
||||||
|
filter (\x -> not $ "-" `isPrefixOf` (concat $ deadSimple x)) args
|
||||||
|
f args =
|
||||||
|
case nonOptions args of
|
||||||
|
(hostport:r@(_:_)) -> checkArg $ last r
|
||||||
|
_ -> return ()
|
||||||
|
checkArg (T_NormalWord _ [T_DoubleQuoted id parts]) =
|
||||||
|
case filter (not . isConstant) parts of
|
||||||
|
[] -> return ()
|
||||||
|
(x:_) -> info (getId x) $
|
||||||
|
"Note that, unescaped, this expands on the client side."
|
||||||
|
checkArg _ = return ()
|
||||||
|
|
||||||
|
|
||||||
--- Subshell detection
|
--- Subshell detection
|
||||||
prop_subshellAssignmentCheck = verifyFull subshellAssignmentCheck "cat foo | while read bar; do a=$bar; done; echo \"$a\""
|
prop_subshellAssignmentCheck = verifyFull subshellAssignmentCheck "cat foo | while read bar; do a=$bar; done; echo \"$a\""
|
||||||
|
|
|
@ -989,7 +989,7 @@ readHereDoc = called "here document" $ do
|
||||||
spaces <- spacing
|
spaces <- spacing
|
||||||
verifyHereDoc dashed quoted spaces hereInfo
|
verifyHereDoc dashed quoted spaces hereInfo
|
||||||
token <- string endToken
|
token <- string endToken
|
||||||
return $ T_FdRedirect fid "" $ T_HereDoc hid dashed quoted hereInfo
|
return $ T_FdRedirect fid "" $ T_HereDoc hid dashed quoted endToken hereInfo
|
||||||
`attempting` (eof >> debugHereDoc tokenPosition endToken hereInfo)
|
`attempting` (eof >> debugHereDoc tokenPosition endToken hereInfo)
|
||||||
|
|
||||||
verifyHereDoc dashed quoted spacing hereInfo = do
|
verifyHereDoc dashed quoted spacing hereInfo = do
|
||||||
|
|
Loading…
Reference in New Issue