Avoid rescanning tree for lastpipe on every node.

This commit is contained in:
Vidar Holen 2017-05-28 16:04:42 -07:00
parent 505ff7832f
commit 6f4e06d83c
2 changed files with 51 additions and 36 deletions

View File

@ -2106,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' t of subshellType t = case leadType params 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)
@ -2168,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 root let flow = getVariableFlow params body
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
@ -2471,7 +2471,9 @@ prop_checkUncheckedCd6 = verifyNotTree checkUncheckedCd "cd .."
prop_checkUncheckedCd7 = verifyNotTree checkUncheckedCd "#!/bin/bash -e\ncd foo\nrm bar" prop_checkUncheckedCd7 = verifyNotTree checkUncheckedCd "#!/bin/bash -e\ncd foo\nrm bar"
prop_checkUncheckedCd8 = verifyNotTree checkUncheckedCd "set -o errexit; cd foo; rm bar" prop_checkUncheckedCd8 = verifyNotTree checkUncheckedCd "set -o errexit; cd foo; rm bar"
checkUncheckedCd params root = checkUncheckedCd params root =
if hasSetE then [] else execWriter $ doAnalysis checkElement root if hasSetE params
then []
else execWriter $ doAnalysis checkElement root
where where
checkElement t@T_SimpleCommand {} = checkElement t@T_SimpleCommand {} =
when(t `isUnqualifiedCommand` "cd" when(t `isUnqualifiedCommand` "cd"
@ -2480,15 +2482,6 @@ checkUncheckedCd params root =
warn (getId t) 2164 "Use 'cd ... || exit' or 'cd ... || return' in case cd fails." warn (getId t) 2164 "Use 'cd ... || exit' or 'cd ... || return' in case cd fails."
checkElement _ = return () checkElement _ = return ()
isCdDotDot t = oversimplify t == ["cd", ".."] isCdDotDot t = oversimplify t == ["cd", ".."]
hasSetE = isNothing $ doAnalysis (guard . not . isSetE) root
isSetE t =
case t of
T_Script _ str _ -> str `matches` re
T_SimpleCommand {} ->
t `isUnqualifiedCommand` "set" &&
("errexit" `elem` oversimplify t || "e" `elem` map snd (getAllFlags t))
_ -> False
re = mkRegex "[[:space:]]-[^-]*e"
prop_checkLoopVariableReassignment1 = verify checkLoopVariableReassignment "for i in *; do for i in *.bar; do true; done; done" prop_checkLoopVariableReassignment1 = verify checkLoopVariableReassignment "for i in *; do for i in *.bar; do true; done; done"
prop_checkLoopVariableReassignment2 = verify checkLoopVariableReassignment "for i in *; do for((i=0; i<3; i++)); do true; done; done" prop_checkLoopVariableReassignment2 = verify checkLoopVariableReassignment "for i in *; do for((i=0; i<3; i++)); do true; done; done"

View File

@ -72,6 +72,8 @@ composeAnalyzers :: (a -> Analysis) -> (a -> Analysis) -> a -> Analysis
composeAnalyzers f g x = f x >> g x composeAnalyzers f g x = f x >> g x
data Parameters = Parameters { data Parameters = Parameters {
hasLastpipe :: Bool, -- Whether this script has the 'lastpipe' option set/default.
hasSetE :: Bool, -- Whether this script has 'set -e' anywhere.
variableFlow :: [StackData], -- A linear (bad) analysis of data flow variableFlow :: [StackData], -- A linear (bad) analysis of data flow
parentMap :: Map.Map Id Token, -- A map from Id to parent Token parentMap :: Map.Map Id Token, -- A map from Id to parent Token
shellType :: Shell, -- The shell type, such as Bash or Ksh shellType :: Shell, -- The shell type, such as Bash or Ksh
@ -142,13 +144,48 @@ makeParameters spec =
let params = Parameters { let params = Parameters {
rootNode = root, rootNode = root,
shellType = fromMaybe (determineShell root) $ asShellType spec, shellType = fromMaybe (determineShell root) $ asShellType spec,
hasSetE = containsSetE root,
hasLastpipe =
case shellType params of
Bash -> containsLastpipe root
Dash -> False
Sh -> False
Ksh -> True,
shellTypeSpecified = isJust $ asShellType spec, shellTypeSpecified = isJust $ asShellType spec,
parentMap = getParentTree root, parentMap = getParentTree root,
variableFlow = variableFlow = getVariableFlow params root
getVariableFlow (shellType params) (parentMap params) root root
} in params } in params
where root = asScript spec where root = asScript spec
-- Does this script mention 'set -e' anywhere?
-- Used as a hack to disable certain warnings.
containsSetE root = isNothing $ doAnalysis (guard . not . isSetE) root
where
isSetE t =
case t of
T_Script _ str _ -> str `matches` re
T_SimpleCommand {} ->
t `isUnqualifiedCommand` "set" &&
("errexit" `elem` oversimplify t ||
"e" `elem` map snd (getAllFlags t))
_ -> False
re = mkRegex "[[:space:]]-[^-]*e"
-- Does this script mention 'shopt -s lastpipe' anywhere?
-- Also used as a hack.
containsLastpipe root =
isNothing $ doAnalysis (guard . not . isShoptLastPipe) root
where
isShoptLastPipe t =
case t of
T_SimpleCommand {} ->
t `isUnqualifiedCommand` "shopt" &&
("lastpipe" `elem` oversimplify t)
_ -> False
prop_determineShell0 = determineShell (fromJust $ pScript "#!/bin/sh") == Sh prop_determineShell0 = determineShell (fromJust $ pScript "#!/bin/sh") == Sh
prop_determineShell1 = determineShell (fromJust $ pScript "#!/usr/bin/env ksh") == Ksh prop_determineShell1 = determineShell (fromJust $ pScript "#!/usr/bin/env ksh") == Ksh
prop_determineShell2 = determineShell (fromJust $ pScript "") == Bash prop_determineShell2 = determineShell (fromJust $ pScript "") == Bash
@ -337,18 +374,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 root = getVariableFlow params t =
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 root let scopeType = leadType params t
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 root let scopeType = leadType params t
in do in do
setRead t setRead t
unless (assignFirst t) $ setWritten t unless (assignFirst t) $ setWritten t
@ -359,7 +396,7 @@ getVariableFlow shell parents t root =
assignFirst _ = False assignFirst _ = False
setRead t = setRead t =
let read = getReferencedVariables parents t let read = getReferencedVariables (parentMap params) t
in mapM_ (\v -> modify (Reference v:)) read in mapM_ (\v -> modify (Reference v:)) read
setWritten t = setWritten t =
@ -367,7 +404,7 @@ getVariableFlow shell parents t root =
in mapM_ (\v -> modify (Assignment v:)) written in mapM_ (\v -> modify (Assignment v:)) written
leadType shell parents t root = leadType params t =
case t of case t of
T_DollarExpansion _ _ -> SubshellScope "$(..) expansion" T_DollarExpansion _ _ -> SubshellScope "$(..) expansion"
T_Backticked _ _ -> SubshellScope "`..` expansion" T_Backticked _ _ -> SubshellScope "`..` expansion"
@ -381,7 +418,7 @@ leadType shell parents t root =
_ -> NoneScope _ -> NoneScope
where where
parentPipeline = do parentPipeline = do
parent <- Map.lookup (getId t) parents parent <- Map.lookup (getId t) (parentMap params)
case parent of case parent of
T_Pipeline {} -> return parent T_Pipeline {} -> return parent
_ -> Nothing _ -> Nothing
@ -390,25 +427,10 @@ leadType shell parents t root =
(T_Pipeline _ _ list) <- parentPipeline (T_Pipeline _ _ list) <- parentPipeline
if length list <= 1 if length list <= 1
then return False then return False
else if lastCreatesSubshell else if not $ hasLastpipe params
then return True then return True
else return . not $ (getId . head $ reverse list) == getId t else return . not $ (getId . head $ reverse list) == getId t
lastCreatesSubshell =
case shell of
Bash -> not hasShoptLastPipe
Dash -> True
Sh -> True
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 [] ->