Recognize wait -p as assigning a variable (fixes #2179)
This commit is contained in:
parent
c61fc7546e
commit
da7b28213e
|
@ -228,6 +228,39 @@ getOpts (gnu, arbitraryLongOpts) string longopts args = process args
|
||||||
|
|
||||||
listToArgs = map (\x -> ("", (x, x)))
|
listToArgs = map (\x -> ("", (x, x)))
|
||||||
|
|
||||||
|
|
||||||
|
-- Generic getOpts that doesn't rely on a format string, but may also be inaccurate.
|
||||||
|
-- This provides a best guess interpretation instead of failing when new options are added.
|
||||||
|
--
|
||||||
|
-- "--" is treated as end of arguments
|
||||||
|
-- "--anything[=foo]" is treated as a long option without argument
|
||||||
|
-- "-any" is treated as -a -n -y, with the next arg as an option to -y unless it starts with -
|
||||||
|
-- anything else is an argument
|
||||||
|
getGenericOpts :: [Token] -> [(String, (Token, Token))]
|
||||||
|
getGenericOpts = process
|
||||||
|
where
|
||||||
|
process (token:rest) =
|
||||||
|
case getLiteralStringDef "\0" token of
|
||||||
|
"--" -> map (\c -> ("", (c,c))) rest
|
||||||
|
'-':'-':word -> (takeWhile (`notElem` "\0=") word, (token, token)) : process rest
|
||||||
|
'-':optString ->
|
||||||
|
let opts = takeWhile (/= '\0') optString
|
||||||
|
in
|
||||||
|
case rest of
|
||||||
|
next:_ | "-" `isPrefixOf` getLiteralStringDef "\0" next ->
|
||||||
|
map (\c -> ([c], (token, token))) opts ++ process rest
|
||||||
|
next:remainder ->
|
||||||
|
case reverse opts of
|
||||||
|
last:initial ->
|
||||||
|
map (\c -> ([c], (token, token))) (reverse initial)
|
||||||
|
++ [([last], (token, next))]
|
||||||
|
++ process remainder
|
||||||
|
[] -> process remainder
|
||||||
|
[] -> map (\c -> ([c], (token, token))) opts
|
||||||
|
_ -> ("", (token, token)) : process rest
|
||||||
|
process [] = []
|
||||||
|
|
||||||
|
|
||||||
-- 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
|
||||||
|
|
|
@ -1968,6 +1968,7 @@ prop_checkSpacefulness41= verifyNotTree checkSpacefulness "exec $1 --flags"
|
||||||
prop_checkSpacefulness42= verifyNotTree checkSpacefulness "run $1 --flags"
|
prop_checkSpacefulness42= verifyNotTree checkSpacefulness "run $1 --flags"
|
||||||
prop_checkSpacefulness43= verifyNotTree checkSpacefulness "$foo=42"
|
prop_checkSpacefulness43= verifyNotTree checkSpacefulness "$foo=42"
|
||||||
prop_checkSpacefulness44= verifyTree checkSpacefulness "#!/bin/sh\nexport var=$value"
|
prop_checkSpacefulness44= verifyTree checkSpacefulness "#!/bin/sh\nexport var=$value"
|
||||||
|
prop_checkSpacefulness45= verifyNotTree checkSpacefulness "wait -zzx -p foo; echo $foo"
|
||||||
|
|
||||||
data SpaceStatus = SpaceSome | SpaceNone | SpaceEmpty deriving (Eq)
|
data SpaceStatus = SpaceSome | SpaceNone | SpaceEmpty deriving (Eq)
|
||||||
instance Semigroup SpaceStatus where
|
instance Semigroup SpaceStatus where
|
||||||
|
@ -2381,6 +2382,7 @@ prop_checkUnassignedReferences_minusNDefault = verifyNotTree checkUnassignedRefe
|
||||||
prop_checkUnassignedReferences_minusZDefault = verifyNotTree checkUnassignedReferences "if [ -z \"${x:-}\" ]; then echo \"\"; fi"
|
prop_checkUnassignedReferences_minusZDefault = verifyNotTree checkUnassignedReferences "if [ -z \"${x:-}\" ]; then echo \"\"; fi"
|
||||||
prop_checkUnassignedReferences50 = verifyNotTree checkUnassignedReferences "echo ${foo:+bar}"
|
prop_checkUnassignedReferences50 = verifyNotTree checkUnassignedReferences "echo ${foo:+bar}"
|
||||||
prop_checkUnassignedReferences51 = verifyNotTree checkUnassignedReferences "echo ${foo:+$foo}"
|
prop_checkUnassignedReferences51 = verifyNotTree checkUnassignedReferences "echo ${foo:+$foo}"
|
||||||
|
prop_checkUnassignedReferences52 = verifyNotTree checkUnassignedReferences "wait -p pid; echo $pid"
|
||||||
|
|
||||||
checkUnassignedReferences = checkUnassignedReferences' False
|
checkUnassignedReferences = checkUnassignedReferences' False
|
||||||
checkUnassignedReferences' includeGlobals params t = warnings
|
checkUnassignedReferences' includeGlobals params t = warnings
|
||||||
|
|
|
@ -617,6 +617,7 @@ getModifiedVariableCommand base@(T_SimpleCommand id cmdPrefix (T_NormalWord _ (T
|
||||||
return (base, base, "@", DataString $ SourceFrom params)
|
return (base, base, "@", DataString $ SourceFrom params)
|
||||||
|
|
||||||
"printf" -> maybeToList $ getPrintfVariable rest
|
"printf" -> maybeToList $ getPrintfVariable rest
|
||||||
|
"wait" -> maybeToList $ getWaitVariable rest
|
||||||
|
|
||||||
"mapfile" -> maybeToList $ getMapfileArray base rest
|
"mapfile" -> maybeToList $ getMapfileArray base rest
|
||||||
"readarray" -> maybeToList $ getMapfileArray base rest
|
"readarray" -> maybeToList $ getMapfileArray base rest
|
||||||
|
@ -674,15 +675,15 @@ getModifiedVariableCommand base@(T_SimpleCommand id cmdPrefix (T_NormalWord _ (T
|
||||||
_ -> return (t:fromMaybe [] (getSetParams rest))
|
_ -> return (t:fromMaybe [] (getSetParams rest))
|
||||||
getSetParams [] = Nothing
|
getSetParams [] = Nothing
|
||||||
|
|
||||||
getPrintfVariable list = f $ map (\x -> (x, getLiteralString x)) list
|
getPrintfVariable list = getFlagAssignedVariable "v" (SourceFrom list) $ getBsdOpts "v:" list
|
||||||
where
|
getWaitVariable list = getFlagAssignedVariable "p" SourceInteger $ return $ getGenericOpts list
|
||||||
f ((_, Just "-v") : (t, Just var) : _) = return (base, t, varName, varType $ SourceFrom list)
|
|
||||||
where
|
getFlagAssignedVariable str dataSource maybeFlags = do
|
||||||
(varName, varType) = case elemIndex '[' var of
|
flags <- maybeFlags
|
||||||
Just i -> (take i var, DataArray)
|
(_, (flag, value)) <- find ((== str) . fst) flags
|
||||||
Nothing -> (var, DataString)
|
variableName <- getLiteralStringExt (const $ return "!") value
|
||||||
f (_:rest) = f rest
|
let (baseName, index) = span (/= '[') variableName
|
||||||
f [] = fail "not found"
|
return (base, value, baseName, (if null index then DataString else DataArray) dataSource)
|
||||||
|
|
||||||
-- mapfile has some curious syntax allowing flags plus 0..n variable names
|
-- mapfile has some curious syntax allowing flags plus 0..n variable names
|
||||||
-- where only the first non-option one is used if any.
|
-- where only the first non-option one is used if any.
|
||||||
|
|
|
@ -138,18 +138,30 @@ prop_checkGetOptsS3 = checkGetOpts "-f -x" ["f", "x"] [] $ getOpts (True, True)
|
||||||
prop_checkGetOptsS4 = checkGetOpts "-f -x" ["f"] [] $ getOpts (True, True) "f:" []
|
prop_checkGetOptsS4 = checkGetOpts "-f -x" ["f"] [] $ getOpts (True, True) "f:" []
|
||||||
prop_checkGetOptsS5 = checkGetOpts "-fx" [] [] $ getOpts (True, True) "fx:" []
|
prop_checkGetOptsS5 = checkGetOpts "-fx" [] [] $ getOpts (True, True) "fx:" []
|
||||||
|
|
||||||
|
prop_checkGenericOptsS1 = checkGetOpts "-f x" ["f"] [] $ return . getGenericOpts
|
||||||
|
prop_checkGenericOptsS2 = checkGetOpts "-abc x" ["a", "b", "c"] [] $ return . getGenericOpts
|
||||||
|
prop_checkGenericOptsS3 = checkGetOpts "-abc -x" ["a", "b", "c", "x"] [] $ return . getGenericOpts
|
||||||
|
prop_checkGenericOptsS4 = checkGetOpts "-x" ["x"] [] $ return . getGenericOpts
|
||||||
|
|
||||||
-- Long options
|
-- Long options
|
||||||
prop_checkGetOptsL1 = checkGetOpts "--foo=bar baz" ["foo"] ["baz"] $ getOpts (True, False) "" [("foo", True)]
|
prop_checkGetOptsL1 = checkGetOpts "--foo=bar baz" ["foo"] ["baz"] $ getOpts (True, False) "" [("foo", True)]
|
||||||
prop_checkGetOptsL2 = checkGetOpts "--foo bar baz" ["foo"] ["baz"] $ getOpts (True, False) "" [("foo", True)]
|
prop_checkGetOptsL2 = checkGetOpts "--foo bar baz" ["foo"] ["baz"] $ getOpts (True, False) "" [("foo", True)]
|
||||||
prop_checkGetOptsL3 = checkGetOpts "--foo baz" ["foo"] ["baz"] $ getOpts (True, True) "" []
|
prop_checkGetOptsL3 = checkGetOpts "--foo baz" ["foo"] ["baz"] $ getOpts (True, True) "" []
|
||||||
prop_checkGetOptsL4 = checkGetOpts "--foo baz" [] [] $ getOpts (True, False) "" []
|
prop_checkGetOptsL4 = checkGetOpts "--foo baz" [] [] $ getOpts (True, False) "" []
|
||||||
|
|
||||||
|
prop_checkGenericOptsL1 = checkGetOpts "--foo=bar" ["foo"] [] $ return . getGenericOpts
|
||||||
|
prop_checkGenericOptsL2 = checkGetOpts "--foo bar" ["foo"] ["bar"] $ return . getGenericOpts
|
||||||
|
prop_checkGenericOptsL3 = checkGetOpts "-x --foo" ["x", "foo"] [] $ return . getGenericOpts
|
||||||
|
|
||||||
-- Know when to terminate
|
-- Know when to terminate
|
||||||
prop_checkGetOptsT1 = checkGetOpts "-a x -b" ["a", "b"] ["x"] $ getOpts (True, True) "ab" []
|
prop_checkGetOptsT1 = checkGetOpts "-a x -b" ["a", "b"] ["x"] $ getOpts (True, True) "ab" []
|
||||||
prop_checkGetOptsT2 = checkGetOpts "-a x -b" ["a"] ["x","-b"] $ getOpts (False, True) "ab" []
|
prop_checkGetOptsT2 = checkGetOpts "-a x -b" ["a"] ["x","-b"] $ getOpts (False, True) "ab" []
|
||||||
prop_checkGetOptsT3 = checkGetOpts "-a -- -b" ["a"] ["-b"] $ getOpts (True, True) "ab" []
|
prop_checkGetOptsT3 = checkGetOpts "-a -- -b" ["a"] ["-b"] $ getOpts (True, True) "ab" []
|
||||||
prop_checkGetOptsT4 = checkGetOpts "-a -- -b" ["a", "b"] [] $ getOpts (True, True) "a:b" []
|
prop_checkGetOptsT4 = checkGetOpts "-a -- -b" ["a", "b"] [] $ getOpts (True, True) "a:b" []
|
||||||
|
|
||||||
|
prop_checkGenericOptsT1 = checkGetOpts "-x -- -y" ["x"] ["-y"] $ return . getGenericOpts
|
||||||
|
prop_checkGenericOptsT2 = checkGetOpts "-xy --" ["x", "y"] [] $ return . getGenericOpts
|
||||||
|
|
||||||
|
|
||||||
buildCommandMap :: [CommandCheck] -> Map.Map CommandName (Token -> Analysis)
|
buildCommandMap :: [CommandCheck] -> Map.Map CommandName (Token -> Analysis)
|
||||||
buildCommandMap = foldl' addCheck Map.empty
|
buildCommandMap = foldl' addCheck Map.empty
|
||||||
|
|
Loading…
Reference in New Issue