diff --git a/ShellCheck/AST.hs b/ShellCheck/AST.hs index de2e509..f911f41 100644 --- a/ShellCheck/AST.hs +++ b/ShellCheck/AST.hs @@ -124,6 +124,7 @@ data Token = | T_Annotation Id [Annotation] Token | T_Pipe Id String | T_CoProc Id (Maybe String) Token + | T_CoProcBody Id Token deriving (Show) data Annotation = DisableComment Integer deriving (Show, Eq) @@ -250,6 +251,7 @@ analyze f g i = delve (TA_Index id t) = d1 t $ TA_Index id delve (T_Annotation id anns t) = d1 t $ T_Annotation id anns delve (T_CoProc id var body) = d1 body $ T_CoProc id var + delve (T_CoProcBody id t) = d1 t $ T_CoProcBody id delve t = return t getId t = case t of @@ -344,6 +346,7 @@ getId t = case t of T_Annotation id _ _ -> id T_Pipe id _ -> id T_CoProc id _ _ -> id + T_CoProcBody id _ -> id blank :: Monad m => Token -> m () blank = const $ return () diff --git a/ShellCheck/Analytics.hs b/ShellCheck/Analytics.hs index 5ca2b18..17af0a5 100644 --- a/ShellCheck/Analytics.hs +++ b/ShellCheck/Analytics.hs @@ -919,6 +919,8 @@ checkArrayAsString _ _ = return () prop_checkArrayWithoutIndex1 = verifyTree checkArrayWithoutIndex "foo=(a b); echo $foo" prop_checkArrayWithoutIndex2 = verifyNotTree checkArrayWithoutIndex "foo='bar baz'; foo=($foo); echo ${foo[0]}" +prop_checkArrayWithoutIndex3 = verifyTree checkArrayWithoutIndex "coproc foo while true; do echo cow; done; echo $foo" +prop_checkArrayWithoutIndex4 = verifyTree checkArrayWithoutIndex "coproc tail -f log; echo $COPROC" checkArrayWithoutIndex params _ = concat $ doVariableFlowAnalysis readF writeF Map.empty (variableFlow params) where @@ -934,6 +936,9 @@ checkArrayWithoutIndex params _ = writeF _ t name (DataFrom [T_Array {}]) = do modify (Map.insert name t) return [] + writeF _ t name DataExternalArray = do + modify (Map.insert name t) + return [] writeF _ _ name _ = do modify (Map.delete name) return [] @@ -1963,7 +1968,7 @@ data StackData = | Assignment (Token, Token, String, DataSource) | Reference (Token, Token, String) deriving (Show, Eq) -data DataSource = DataFrom [Token] | DataExternal +data DataSource = DataFrom [Token] | DataExternalValue | DataExternalArray deriving (Show, Eq) data VariableState = Dead Token String | Alive deriving (Show, Eq) @@ -1974,7 +1979,7 @@ leadType shell parents t = T_Backticked _ _ -> SubshellScope "`..` expansion" T_Backgrounded _ _ -> SubshellScope "backgrounding &" T_Subshell _ _ -> SubshellScope "(..) group" - T_CoProc _ _ _ -> SubshellScope "coproc" + T_CoProcBody _ _ -> SubshellScope "coproc" T_Redirecting {} -> if fromMaybe False causesSubshell then SubshellScope "pipeline" @@ -2024,6 +2029,9 @@ getModifiedVariables t = name <- getLiteralString lhs return (t, t, name, DataFrom [rhs]) + t@(T_CoProc _ name _) -> + [(t, t, fromMaybe "COPROC" name, DataExternalArray)] + --Points to 'for' rather than variable T_ForIn id _ strs words _ -> map (\str -> (t, t, str, DataFrom words)) strs T_SelectIn id str words _ -> [(t, t, str, DataFrom words)] @@ -2075,7 +2083,7 @@ getModifiedVariableCommand base@(T_SimpleCommand _ _ (T_NormalWord _ (T_Literal getLiteral t = do s <- getLiteralString t when ("-" `isPrefixOf` s) $ fail "argument" - return (base, t, s, DataExternal) + return (base, t, s, DataExternalValue) getModifierParam t@(T_Assignment _ _ name _ value) = [(base, t, name, DataFrom [value])] @@ -2251,7 +2259,7 @@ checkSpacefulness params t = where warning = "Double quote to prevent globbing and word splitting." - writeF _ _ name DataExternal = do + writeF _ _ name DataExternalValue = do setSpaces name True return [] @@ -2261,6 +2269,8 @@ checkSpacefulness params t = (isSpacefulWord (\x -> Map.findWithDefault True x map) vals) return [] + writeF _ _ _ _ = return [] + parents = parentMap params isCounting (T_DollarBraced id token) = diff --git a/ShellCheck/Data.hs b/ShellCheck/Data.hs index 781d277..7d79bca 100644 --- a/ShellCheck/Data.hs +++ b/ShellCheck/Data.hs @@ -27,7 +27,7 @@ internalVariables = [ "LC_MESSAGES", "LC_NUMERIC", "LINES", "MAIL", "MAILCHECK", "MAILPATH", "OPTERR", "PATH", "POSIXLY_CORRECT", "PROMPT_COMMAND", "PROMPT_DIRTRIM", "PS1", "PS2", "PS3", "PS4", "SHELL", "TIMEFORMAT", - "TMOUT", "TMPDIR", "auto_resume", "histchars", + "TMOUT", "TMPDIR", "auto_resume", "histchars", "COPROC", -- Zsh "ARGV0", "BAUD", "cdpath", "COLUMNS", "CORRECT_IGNORE", diff --git a/ShellCheck/Parser.hs b/ShellCheck/Parser.hs index 230ea0d..ce20784 100644 --- a/ShellCheck/Parser.hs +++ b/ShellCheck/Parser.hs @@ -1814,11 +1814,15 @@ readCoProc = called "coproc" $ do readCompoundCoProc id = do var <- optionMaybe $ readVariableName `thenSkip` whitespace - body <- readCompoundCommand + body <- readBody readCompoundCommand return $ T_CoProc id var body readSimpleCoProc id = do - body <- readSimpleCommand + body <- readBody readSimpleCommand return $ T_CoProc id Nothing body + readBody parser = do + id <- getNextId + body <- parser + return $ T_CoProcBody id body readPattern = (readNormalWord `thenSkip` spacing) `sepBy1` (char '|' `thenSkip` spacing)