Refactor sudo checks into CommandChecks
This commit is contained in:
parent
8873a1732b
commit
ef6a5b97b9
|
@ -120,8 +120,6 @@ nodeChecks = [
|
||||||
,checkGlobbedRegex
|
,checkGlobbedRegex
|
||||||
,checkTestRedirects
|
,checkTestRedirects
|
||||||
,checkIndirectExpansion
|
,checkIndirectExpansion
|
||||||
,checkSudoRedirect
|
|
||||||
,checkSudoArgs
|
|
||||||
,checkPS1Assignments
|
,checkPS1Assignments
|
||||||
,checkBackticks
|
,checkBackticks
|
||||||
,checkInexplicablyUnquoted
|
,checkInexplicablyUnquoted
|
||||||
|
@ -1280,49 +1278,6 @@ checkTestRedirects _ (T_Redirecting id redirs cmd) | cmd `isCommand` "test" =
|
||||||
_ -> False
|
_ -> False
|
||||||
checkTestRedirects _ _ = return ()
|
checkTestRedirects _ _ = return ()
|
||||||
|
|
||||||
prop_checkSudoRedirect1 = verify checkSudoRedirect "sudo echo 3 > /proc/file"
|
|
||||||
prop_checkSudoRedirect2 = verify checkSudoRedirect "sudo cmd < input"
|
|
||||||
prop_checkSudoRedirect3 = verify checkSudoRedirect "sudo cmd >> file"
|
|
||||||
prop_checkSudoRedirect4 = verify checkSudoRedirect "sudo cmd &> file"
|
|
||||||
prop_checkSudoRedirect5 = verifyNot checkSudoRedirect "sudo cmd 2>&1"
|
|
||||||
prop_checkSudoRedirect6 = verifyNot checkSudoRedirect "sudo cmd 2> log"
|
|
||||||
prop_checkSudoRedirect7 = verifyNot checkSudoRedirect "sudo cmd > /dev/null 2>&1"
|
|
||||||
checkSudoRedirect _ (T_Redirecting _ redirs cmd) | cmd `isCommand` "sudo" =
|
|
||||||
mapM_ warnAbout redirs
|
|
||||||
where
|
|
||||||
warnAbout (T_FdRedirect _ s (T_IoFile id op file))
|
|
||||||
| (s == "" || s == "&") && not (special file) =
|
|
||||||
case op of
|
|
||||||
T_Less _ ->
|
|
||||||
info (getId op) 2024
|
|
||||||
"sudo doesn't affect redirects. Use sudo cat file | .."
|
|
||||||
T_Greater _ ->
|
|
||||||
warn (getId op) 2024
|
|
||||||
"sudo doesn't affect redirects. Use ..| sudo tee file"
|
|
||||||
T_DGREAT _ ->
|
|
||||||
warn (getId op) 2024
|
|
||||||
"sudo doesn't affect redirects. Use .. | sudo tee -a file"
|
|
||||||
_ -> return ()
|
|
||||||
warnAbout _ = return ()
|
|
||||||
special file = concat (oversimplify file) == "/dev/null"
|
|
||||||
checkSudoRedirect _ _ = return ()
|
|
||||||
|
|
||||||
prop_checkSudoArgs1 = verify checkSudoArgs "sudo cd /root"
|
|
||||||
prop_checkSudoArgs2 = verify checkSudoArgs "sudo export x=3"
|
|
||||||
prop_checkSudoArgs3 = verifyNot checkSudoArgs "sudo ls /usr/local/protected"
|
|
||||||
prop_checkSudoArgs4 = verifyNot checkSudoArgs "sudo ls && export x=3"
|
|
||||||
prop_checkSudoArgs5 = verifyNot checkSudoArgs "sudo echo ls"
|
|
||||||
checkSudoArgs _ t@(T_SimpleCommand _ _ (_:rest))
|
|
||||||
| t `isCommand` "sudo" = checkArgs args
|
|
||||||
where checkArgs (x:xs)
|
|
||||||
| x `elem` prohibitedArguments = warn (getId t) 2232 $ "Can't use sudo with " ++ x
|
|
||||||
| x `elem` commonCommands = return ()
|
|
||||||
| otherwise = checkArgs xs
|
|
||||||
checkArgs [] = return ()
|
|
||||||
args = map onlyLiteralString $ concat $ map getWordParts rest
|
|
||||||
prohibitedArguments = ["cd", "export"]
|
|
||||||
checkSudoArgs _ _ = return ()
|
|
||||||
|
|
||||||
prop_checkPS11 = verify checkPS1Assignments "PS1='\\033[1;35m\\$ '"
|
prop_checkPS11 = verify checkPS1Assignments "PS1='\\033[1;35m\\$ '"
|
||||||
prop_checkPS11a= verify checkPS1Assignments "export PS1='\\033[1;35m\\$ '"
|
prop_checkPS11a= verify checkPS1Assignments "export PS1='\\033[1;35m\\$ '"
|
||||||
prop_checkPSf2 = verify checkPS1Assignments "PS1='\\h \\e[0m\\$ '"
|
prop_checkPSf2 = verify checkPS1Assignments "PS1='\\h \\e[0m\\$ '"
|
||||||
|
|
|
@ -835,16 +835,18 @@ isQuotedAlternativeReference t =
|
||||||
where
|
where
|
||||||
re = mkRegex "(^|\\]):?\\+"
|
re = mkRegex "(^|\\]):?\\+"
|
||||||
|
|
||||||
-- getOpts "erd:u:" will parse a SimpleCommand like
|
-- getGnuOpts "erd:u:" will parse a SimpleCommand like
|
||||||
-- read -re -d : -u 3 bar
|
-- read -re -d : -u 3 bar
|
||||||
-- into
|
-- into
|
||||||
-- Just [("r", -re), ("e", -re), ("d", :), ("u", 3), ("", bar)]
|
-- Just [("r", -re), ("e", -re), ("d", :), ("u", 3), ("", bar)]
|
||||||
-- where flags with arguments map to arguments, while others map to themselves.
|
-- where flags with arguments map to arguments, while others map to themselves.
|
||||||
-- Any unrecognized flag will result in Nothing.
|
-- Any unrecognized flag will result in Nothing.
|
||||||
getOpts :: String -> Token -> Maybe [(String, Token)]
|
getGnuOpts = getOpts getAllFlags
|
||||||
getOpts string cmd = process flags
|
getBsdOpts = getOpts getLeadingFlags
|
||||||
|
getOpts :: (Token -> [(Token, String)]) -> String -> Token -> Maybe [(String, Token)]
|
||||||
|
getOpts flagTokenizer string cmd = process flags
|
||||||
where
|
where
|
||||||
flags = getAllFlags cmd
|
flags = flagTokenizer cmd
|
||||||
flagList (c:':':rest) = ([c], True) : flagList rest
|
flagList (c:':':rest) = ([c], True) : flagList rest
|
||||||
flagList (c:rest) = ([c], False) : flagList rest
|
flagList (c:rest) = ([c], False) : flagList rest
|
||||||
flagList [] = []
|
flagList [] = []
|
||||||
|
|
|
@ -90,6 +90,8 @@ commandChecks = [
|
||||||
,checkFindRedirections
|
,checkFindRedirections
|
||||||
,checkReadExpansions
|
,checkReadExpansions
|
||||||
,checkWhich
|
,checkWhich
|
||||||
|
,checkSudoRedirect
|
||||||
|
,checkSudoArgs
|
||||||
]
|
]
|
||||||
|
|
||||||
buildCommandMap :: [CommandCheck] -> Map.Map CommandName (Token -> Analysis)
|
buildCommandMap :: [CommandCheck] -> Map.Map CommandName (Token -> Analysis)
|
||||||
|
@ -608,7 +610,7 @@ prop_checkReadExpansions7 = verifyNot checkReadExpansions "read $1"
|
||||||
prop_checkReadExpansions8 = verifyNot checkReadExpansions "read ${var?}"
|
prop_checkReadExpansions8 = verifyNot checkReadExpansions "read ${var?}"
|
||||||
checkReadExpansions = CommandCheck (Exactly "read") check
|
checkReadExpansions = CommandCheck (Exactly "read") check
|
||||||
where
|
where
|
||||||
options = getOpts "sreu:n:N:i:p:a:"
|
options = getGnuOpts "sreu:n:N:i:p:a:"
|
||||||
getVars cmd = fromMaybe [] $ do
|
getVars cmd = fromMaybe [] $ do
|
||||||
opts <- options cmd
|
opts <- options cmd
|
||||||
return . map snd $ filter (\(x,_) -> x == "" || x == "a") opts
|
return . map snd $ filter (\(x,_) -> x == "" || x == "a") opts
|
||||||
|
@ -944,5 +946,55 @@ prop_checkWhich = verify checkWhich "which '.+'"
|
||||||
checkWhich = CommandCheck (Basename "which") $
|
checkWhich = CommandCheck (Basename "which") $
|
||||||
\t -> info (getId t) 2230 "which is non-standard. Use builtin 'command -v' instead."
|
\t -> info (getId t) 2230 "which is non-standard. Use builtin 'command -v' instead."
|
||||||
|
|
||||||
|
prop_checkSudoRedirect1 = verify checkSudoRedirect "sudo echo 3 > /proc/file"
|
||||||
|
prop_checkSudoRedirect2 = verify checkSudoRedirect "sudo cmd < input"
|
||||||
|
prop_checkSudoRedirect3 = verify checkSudoRedirect "sudo cmd >> file"
|
||||||
|
prop_checkSudoRedirect4 = verify checkSudoRedirect "sudo cmd &> file"
|
||||||
|
prop_checkSudoRedirect5 = verifyNot checkSudoRedirect "sudo cmd 2>&1"
|
||||||
|
prop_checkSudoRedirect6 = verifyNot checkSudoRedirect "sudo cmd 2> log"
|
||||||
|
prop_checkSudoRedirect7 = verifyNot checkSudoRedirect "sudo cmd > /dev/null 2>&1"
|
||||||
|
checkSudoRedirect = CommandCheck (Basename "sudo") f
|
||||||
|
where
|
||||||
|
f t = do
|
||||||
|
t_redir <- getClosestCommandM t
|
||||||
|
case t_redir of
|
||||||
|
Just (T_Redirecting _ redirs _) ->
|
||||||
|
mapM_ warnAbout redirs
|
||||||
|
warnAbout (T_FdRedirect _ s (T_IoFile id op file))
|
||||||
|
| (s == "" || s == "&") && not (special file) =
|
||||||
|
case op of
|
||||||
|
T_Less _ ->
|
||||||
|
info (getId op) 2024
|
||||||
|
"sudo doesn't affect redirects. Use sudo cat file | .."
|
||||||
|
T_Greater _ ->
|
||||||
|
warn (getId op) 2024
|
||||||
|
"sudo doesn't affect redirects. Use ..| sudo tee file"
|
||||||
|
T_DGREAT _ ->
|
||||||
|
warn (getId op) 2024
|
||||||
|
"sudo doesn't affect redirects. Use .. | sudo tee -a file"
|
||||||
|
_ -> return ()
|
||||||
|
warnAbout _ = return ()
|
||||||
|
special file = concat (oversimplify file) == "/dev/null"
|
||||||
|
|
||||||
|
prop_checkSudoArgs1 = verify checkSudoArgs "sudo cd /root"
|
||||||
|
prop_checkSudoArgs2 = verify checkSudoArgs "sudo export x=3"
|
||||||
|
prop_checkSudoArgs3 = verifyNot checkSudoArgs "sudo ls /usr/local/protected"
|
||||||
|
prop_checkSudoArgs4 = verifyNot checkSudoArgs "sudo ls && export x=3"
|
||||||
|
prop_checkSudoArgs5 = verifyNot checkSudoArgs "sudo echo ls"
|
||||||
|
prop_checkSudoArgs6 = verifyNot checkSudoArgs "sudo -n -u export ls"
|
||||||
|
prop_checkSudoArgs7 = verifyNot checkSudoArgs "sudo docker export foo"
|
||||||
|
checkSudoArgs = CommandCheck (Basename "sudo") f
|
||||||
|
where
|
||||||
|
f t = potentially $ do
|
||||||
|
opts <- parseOpts t
|
||||||
|
let nonFlags = map snd $ filter (\(flag, _) -> flag == "") opts
|
||||||
|
commandArg <- nonFlags !!! 0
|
||||||
|
command <- getLiteralString commandArg
|
||||||
|
guard $ command `elem` builtins
|
||||||
|
return $ warn (getId t) 2232 $ "Can't use sudo with builtins like " ++ command ++ ". Did you want sudo sh -c .. instead?"
|
||||||
|
builtins = [ "cd", "eval", "export", "history", "read", "source", "wait" ]
|
||||||
|
-- This mess is why ShellCheck prefers not to know.
|
||||||
|
parseOpts = getBsdOpts "vAknSbEHPa:g:h:p:u:c:T:r:"
|
||||||
|
|
||||||
return []
|
return []
|
||||||
runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |])
|
runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |])
|
||||||
|
|
Loading…
Reference in New Issue