Improve handling of command prefixes like exec/command (fixes #2008)

This commit is contained in:
Vidar Holen 2020-07-25 13:45:05 -07:00
parent 5b86777f9d
commit 5d753212fb
4 changed files with 81 additions and 53 deletions

View File

@ -28,6 +28,7 @@ import Data.Functor
import Data.Functor.Identity import Data.Functor.Identity
import Data.List import Data.List
import Data.Maybe import Data.Maybe
import qualified Data.Map as Map
-- Is this a type of loop? -- Is this a type of loop?
isLoop t = case t of isLoop t = case t of
@ -134,6 +135,33 @@ isUnquotedFlag token = fromMaybe False $ do
str <- getLeadingUnquotedString token str <- getLeadingUnquotedString token
return $ "-" `isPrefixOf` str return $ "-" `isPrefixOf` str
-- getGnuOpts "erd:u:" will parse a SimpleCommand like
-- read -re -d : -u 3 bar
-- into
-- Just [("r", -re), ("e", -re), ("d", :), ("u", 3), ("", bar)]
-- where flags with arguments map to arguments, while others map to themselves.
-- Any unrecognized flag will result in Nothing.
getGnuOpts str t = getOpts str $ getAllFlags t
getBsdOpts str t = getOpts str $ getLeadingFlags t
getOpts :: String -> [(Token, String)] -> Maybe [(String, Token)]
getOpts string flags = process flags
where
flagList (c:':':rest) = ([c], True) : flagList rest
flagList (c:rest) = ([c], False) : flagList rest
flagList [] = []
flagMap = Map.fromList $ ("", False) : flagList string
process [] = return []
process ((token1, flag):rest1) = do
takesArg <- Map.lookup flag flagMap
(token, rest) <- if takesArg
then case rest1 of
(token2, ""):rest2 -> return (token2, rest2)
_ -> fail "takesArg without valid arg"
else return (token1, rest1)
more <- process rest
return $ (flag, token) : more
-- Is this an expansion of multiple items of an array? -- Is this an expansion of multiple items of an array?
isArrayExpansion (T_DollarBraced _ _ l) = isArrayExpansion (T_DollarBraced _ _ l) =
let string = concat $ oversimplify l in let string = concat $ oversimplify l in
@ -297,7 +325,7 @@ getCommand t =
-- Maybe get the command name string of a token representing a command -- Maybe get the command name string of a token representing a command
getCommandName :: Token -> Maybe String getCommandName :: Token -> Maybe String
getCommandName = fst . getCommandNameAndToken getCommandName = fst . getCommandNameAndToken False
-- Maybe get the name+arguments of a command. -- Maybe get the name+arguments of a command.
getCommandArgv t = do getCommandArgv t = do
@ -307,18 +335,37 @@ getCommandArgv t = do
-- Get the command name token from a command, i.e. -- Get the command name token from a command, i.e.
-- the token representing 'ls' in 'ls -la 2> foo'. -- the token representing 'ls' in 'ls -la 2> foo'.
-- If it can't be determined, return the original token. -- If it can't be determined, return the original token.
getCommandTokenOrThis = snd . getCommandNameAndToken getCommandTokenOrThis = snd . getCommandNameAndToken False
getCommandNameAndToken :: Token -> (Maybe String, Token) -- Given a command, get the string and token that represents the command name.
getCommandNameAndToken t = fromMaybe (Nothing, t) $ do -- If direct, return the actual command (e.g. exec in 'exec ls')
(T_SimpleCommand _ _ (w:rest)) <- getCommand t -- If not, return the logical command (e.g. 'ls' in 'exec ls')
getCommandNameAndToken :: Bool -> Token -> (Maybe String, Token)
getCommandNameAndToken direct t = fromMaybe (Nothing, t) $ do
cmd@(T_SimpleCommand _ _ (w:rest)) <- getCommand t
s <- getLiteralString w s <- getLiteralString w
return $ case rest of return $ fromMaybe (Just s, w) $ do
(applet:_) | "busybox" `isSuffixOf` s || "builtin" == s -> guard $ not direct
(getLiteralString applet, applet) actual <- getEffectiveCommandToken s cmd rest
_ -> return (getLiteralString actual, actual)
(Just s, w) where
getEffectiveCommandToken str cmd args =
let
firstArg = do
arg <- listToMaybe args
guard . not $ isFlag arg
return arg
in
case str of
"busybox" -> firstArg
"builtin" -> firstArg
"command" -> firstArg
"exec" -> do
opts <- getBsdOpts "cla:" cmd
(_, t) <- listToMaybe $ filter (null . fst) opts
return t
_ -> fail ""
-- If a command substitution is a single command, get its name. -- If a command substitution is a single command, get its name.
-- $(date +%s) = Just "date" -- $(date +%s) = Just "date"
@ -335,8 +382,8 @@ getCommandNameFromExpansion t =
-- Get the basename of a token representing a command -- Get the basename of a token representing a command
getCommandBasename = fmap basename . getCommandName getCommandBasename = fmap basename . getCommandName
where
basename = reverse . takeWhile (/= '/') . reverse basename = reverse . takeWhile (/= '/') . reverse
isAssignment t = isAssignment t =
case t of case t of

View File

@ -942,8 +942,10 @@ prop_checkSingleQuotedVariables18= verifyNot checkSingleQuotedVariables "echo '`
prop_checkSingleQuotedVariables19= verifyNot checkSingleQuotedVariables "echo '```'" prop_checkSingleQuotedVariables19= verifyNot checkSingleQuotedVariables "echo '```'"
prop_checkSingleQuotedVariables20= verifyNot checkSingleQuotedVariables "mumps -run %XCMD 'W $O(^GLOBAL(5))'" prop_checkSingleQuotedVariables20= verifyNot checkSingleQuotedVariables "mumps -run %XCMD 'W $O(^GLOBAL(5))'"
prop_checkSingleQuotedVariables21= verifyNot checkSingleQuotedVariables "mumps -run LOOP%XCMD --xec 'W $O(^GLOBAL(6))'" prop_checkSingleQuotedVariables21= verifyNot checkSingleQuotedVariables "mumps -run LOOP%XCMD --xec 'W $O(^GLOBAL(6))'"
prop_checkSingleQuotedVariables22= verifyNot checkSingleQuotedVariables "jq '$__loc__'"
prop_checkSingleQuotedVariables23= verifyNot checkSingleQuotedVariables "command jq '$__loc__'"
prop_checkSingleQuotedVariables24= verifyNot checkSingleQuotedVariables "exec jq '$__loc__'"
prop_checkSingleQuotedVariables25= verifyNot checkSingleQuotedVariables "exec -c -a foo jq '$__loc__'"
checkSingleQuotedVariables params t@(T_SingleQuoted id s) = checkSingleQuotedVariables params t@(T_SingleQuoted id s) =
@ -1677,13 +1679,10 @@ checkSpuriousExec _ = doLists
doList tail True doList tail True
doList' _ _ = return () doList' _ _ = return ()
commentIfExec (T_Pipeline id _ list) = commentIfExec (T_Pipeline id _ [c]) = commentIfExec c
mapM_ commentIfExec $ take 1 list commentIfExec (T_Redirecting _ _ (T_SimpleCommand id _ (cmd:additionalArg:_))) |
commentIfExec (T_Redirecting _ _ f@( getLiteralString cmd == Just "exec" =
T_SimpleCommand id _ (cmd:arg:_))) warn id 2093 "Remove \"exec \" if script should continue after this command."
| f `isUnqualifiedCommand` "exec" =
warn id 2093
"Remove \"exec \" if script should continue after this command."
commentIfExec _ = return () commentIfExec _ = return ()
@ -2056,18 +2055,27 @@ prop_checkFunctionsUsedExternally6 =
verifyNotTree checkFunctionsUsedExternally "foo() { :; }; ssh host echo foo" verifyNotTree checkFunctionsUsedExternally "foo() { :; }; ssh host echo foo"
prop_checkFunctionsUsedExternally7 = prop_checkFunctionsUsedExternally7 =
verifyNotTree checkFunctionsUsedExternally "install() { :; }; sudo apt-get install foo" verifyNotTree checkFunctionsUsedExternally "install() { :; }; sudo apt-get install foo"
prop_checkFunctionsUsedExternally8 =
verifyTree checkFunctionsUsedExternally "foo() { :; }; command sudo foo"
prop_checkFunctionsUsedExternally9 =
verifyTree checkFunctionsUsedExternally "foo() { :; }; exec -c sudo foo"
checkFunctionsUsedExternally params t = checkFunctionsUsedExternally params t =
runNodeAnalysis checkCommand params t runNodeAnalysis checkCommand params t
where where
checkCommand _ t@(T_SimpleCommand _ _ (cmd:args)) = checkCommand _ t@(T_SimpleCommand _ _ argv) =
case getCommandBasename t of case getCommandNameAndToken False t of
Just name -> do (Just str, t) -> do
let name = basename str
let args = skipOver t argv
let argStrings = map (\x -> (fromMaybe "" $ getLiteralString x, x)) args let argStrings = map (\x -> (fromMaybe "" $ getLiteralString x, x)) args
let candidates = getPotentialCommands name argStrings let candidates = getPotentialCommands name argStrings
mapM_ (checkArg name) candidates mapM_ (checkArg name) candidates
_ -> return () _ -> return ()
checkCommand _ _ = return () checkCommand _ _ = return ()
skipOver t list = drop 1 $ dropWhile (\c -> getId c /= id) $ list
where id = getId t
-- Try to pick out the argument[s] that may be commands -- Try to pick out the argument[s] that may be commands
getPotentialCommands name argAndString = getPotentialCommands name argAndString =
case name of case name of

View File

@ -901,33 +901,6 @@ isQuotedAlternativeReference t =
where where
re = mkRegex "(^|\\]):?\\+" re = mkRegex "(^|\\]):?\\+"
-- getGnuOpts "erd:u:" will parse a SimpleCommand like
-- read -re -d : -u 3 bar
-- into
-- Just [("r", -re), ("e", -re), ("d", :), ("u", 3), ("", bar)]
-- where flags with arguments map to arguments, while others map to themselves.
-- Any unrecognized flag will result in Nothing.
getGnuOpts str t = getOpts str $ getAllFlags t
getBsdOpts str t = getOpts str $ getLeadingFlags t
getOpts :: String -> [(Token, String)] -> Maybe [(String, Token)]
getOpts string flags = process flags
where
flagList (c:':':rest) = ([c], True) : flagList rest
flagList (c:rest) = ([c], False) : flagList rest
flagList [] = []
flagMap = Map.fromList $ ("", False) : flagList string
process [] = return []
process ((token1, flag):rest1) = do
takesArg <- Map.lookup flag flagMap
(token, rest) <- if takesArg
then case rest1 of
(token2, ""):rest2 -> return (token2, rest2)
_ -> fail "takesArg without valid arg"
else return (token1, rest1)
more <- process rest
return $ (flag, token) : more
supportsArrays Bash = True supportsArrays Bash = True
supportsArrays Ksh = True supportsArrays Ksh = True
supportsArrays _ = False supportsArrays _ = False

View File

@ -280,7 +280,7 @@ checkBashisms = ForShell [Sh, Dash] $ \t -> do
flagRegex = mkRegex "^-[eEsn]+$" flagRegex = mkRegex "^-[eEsn]+$"
bashism t@(T_SimpleCommand _ _ (cmd:arg:_)) bashism t@(T_SimpleCommand _ _ (cmd:arg:_))
| t `isCommand` "exec" && "-" `isPrefixOf` concat (oversimplify arg) = | getLiteralString cmd == Just "exec" && "-" `isPrefixOf` concat (oversimplify arg) =
warnMsg (getId arg) "exec flags are" warnMsg (getId arg) "exec flags are"
bashism t@(T_SimpleCommand id _ _) bashism t@(T_SimpleCommand id _ _)
| t `isCommand` "let" = warnMsg id "'let' is" | t `isCommand` "let" = warnMsg id "'let' is"