parent
ac3f0b3360
commit
505ff7832f
|
@ -1521,6 +1521,7 @@ prop_subshellAssignmentCheck15 = verifyNotTree subshellAssignmentCheck "#!/bin/k
|
||||||
prop_subshellAssignmentCheck16 = verifyNotTree subshellAssignmentCheck "(set -e); echo $@"
|
prop_subshellAssignmentCheck16 = verifyNotTree subshellAssignmentCheck "(set -e); echo $@"
|
||||||
prop_subshellAssignmentCheck17 = verifyNotTree subshellAssignmentCheck "foo=${ { bar=$(baz); } 2>&1; }; echo $foo $bar"
|
prop_subshellAssignmentCheck17 = verifyNotTree subshellAssignmentCheck "foo=${ { bar=$(baz); } 2>&1; }; echo $foo $bar"
|
||||||
prop_subshellAssignmentCheck18 = verifyTree subshellAssignmentCheck "( exec {n}>&2; ); echo $n"
|
prop_subshellAssignmentCheck18 = verifyTree subshellAssignmentCheck "( exec {n}>&2; ); echo $n"
|
||||||
|
prop_subshellAssignmentCheck19 = verifyNotTree subshellAssignmentCheck "#!/bin/bash\nshopt -s lastpipe; echo a | read -r b; echo \"$b\""
|
||||||
subshellAssignmentCheck params t =
|
subshellAssignmentCheck params t =
|
||||||
let flow = variableFlow params
|
let flow = variableFlow params
|
||||||
check = findSubshelled flow [("oops",[])] Map.empty
|
check = findSubshelled flow [("oops",[])] Map.empty
|
||||||
|
@ -2105,7 +2106,7 @@ checkLoopKeywordScope params t |
|
||||||
where
|
where
|
||||||
name = getCommandName t
|
name = getCommandName t
|
||||||
path = let p = getPath (parentMap params) t in filter relevant p
|
path = let p = getPath (parentMap params) t in filter relevant p
|
||||||
subshellType t = case leadType (shellType params) (parentMap params) t of
|
subshellType t' = case leadType (shellType params) (parentMap params) t' t of
|
||||||
NoneScope -> Nothing
|
NoneScope -> Nothing
|
||||||
SubshellScope str -> return str
|
SubshellScope str -> return str
|
||||||
relevant t = isLoop t || isFunction t || isJust (subshellType t)
|
relevant t = isLoop t || isFunction t || isJust (subshellType t)
|
||||||
|
@ -2167,7 +2168,7 @@ checkUnpassedInFunctions params root =
|
||||||
functions = execWriter $ doAnalysis (tell . maybeToList . findFunction) root
|
functions = execWriter $ doAnalysis (tell . maybeToList . findFunction) root
|
||||||
|
|
||||||
findFunction t@(T_Function id _ _ name body) =
|
findFunction t@(T_Function id _ _ name body) =
|
||||||
let flow = getVariableFlow (shellType params) (parentMap params) body
|
let flow = getVariableFlow (shellType params) (parentMap params) body root
|
||||||
in
|
in
|
||||||
if any (isPositionalReference t) flow && not (any isPositionalAssignment flow)
|
if any (isPositionalReference t) flow && not (any isPositionalAssignment flow)
|
||||||
then return t
|
then return t
|
||||||
|
|
|
@ -145,7 +145,7 @@ makeParameters spec =
|
||||||
shellTypeSpecified = isJust $ asShellType spec,
|
shellTypeSpecified = isJust $ asShellType spec,
|
||||||
parentMap = getParentTree root,
|
parentMap = getParentTree root,
|
||||||
variableFlow =
|
variableFlow =
|
||||||
getVariableFlow (shellType params) (parentMap params) root
|
getVariableFlow (shellType params) (parentMap params) root root
|
||||||
} in params
|
} in params
|
||||||
where root = asScript spec
|
where root = asScript spec
|
||||||
|
|
||||||
|
@ -337,18 +337,18 @@ tokenIsJustCommandOutput t = case t of
|
||||||
check _ = False
|
check _ = False
|
||||||
|
|
||||||
-- TODO: Replace this with a proper Control Flow Graph
|
-- TODO: Replace this with a proper Control Flow Graph
|
||||||
getVariableFlow shell parents t =
|
getVariableFlow shell parents t root =
|
||||||
let (_, stack) = runState (doStackAnalysis startScope endScope t) []
|
let (_, stack) = runState (doStackAnalysis startScope endScope t) []
|
||||||
in reverse stack
|
in reverse stack
|
||||||
where
|
where
|
||||||
startScope t =
|
startScope t =
|
||||||
let scopeType = leadType shell parents t
|
let scopeType = leadType shell parents t root
|
||||||
in do
|
in do
|
||||||
when (scopeType /= NoneScope) $ modify (StackScope scopeType:)
|
when (scopeType /= NoneScope) $ modify (StackScope scopeType:)
|
||||||
when (assignFirst t) $ setWritten t
|
when (assignFirst t) $ setWritten t
|
||||||
|
|
||||||
endScope t =
|
endScope t =
|
||||||
let scopeType = leadType shell parents t
|
let scopeType = leadType shell parents t root
|
||||||
in do
|
in do
|
||||||
setRead t
|
setRead t
|
||||||
unless (assignFirst t) $ setWritten t
|
unless (assignFirst t) $ setWritten t
|
||||||
|
@ -367,7 +367,7 @@ getVariableFlow shell parents t =
|
||||||
in mapM_ (\v -> modify (Assignment v:)) written
|
in mapM_ (\v -> modify (Assignment v:)) written
|
||||||
|
|
||||||
|
|
||||||
leadType shell parents t =
|
leadType shell parents t root =
|
||||||
case t of
|
case t of
|
||||||
T_DollarExpansion _ _ -> SubshellScope "$(..) expansion"
|
T_DollarExpansion _ _ -> SubshellScope "$(..) expansion"
|
||||||
T_Backticked _ _ -> SubshellScope "`..` expansion"
|
T_Backticked _ _ -> SubshellScope "`..` expansion"
|
||||||
|
@ -396,11 +396,19 @@ leadType shell parents t =
|
||||||
|
|
||||||
lastCreatesSubshell =
|
lastCreatesSubshell =
|
||||||
case shell of
|
case shell of
|
||||||
Bash -> True
|
Bash -> not hasShoptLastPipe
|
||||||
Dash -> True
|
Dash -> True
|
||||||
Sh -> True
|
Sh -> True
|
||||||
Ksh -> False
|
Ksh -> False
|
||||||
|
|
||||||
|
hasShoptLastPipe = isNothing $ doAnalysis (guard . not . isShoptLastPipe) root
|
||||||
|
isShoptLastPipe t =
|
||||||
|
case t of
|
||||||
|
T_SimpleCommand {} ->
|
||||||
|
t `isUnqualifiedCommand` "shopt" &&
|
||||||
|
("lastpipe" `elem` oversimplify t)
|
||||||
|
_ -> False
|
||||||
|
|
||||||
getModifiedVariables t =
|
getModifiedVariables t =
|
||||||
case t of
|
case t of
|
||||||
T_SimpleCommand _ vars [] ->
|
T_SimpleCommand _ vars [] ->
|
||||||
|
|
Loading…
Reference in New Issue