diff --git a/ShellCheck/Analytics.hs b/ShellCheck/Analytics.hs index bbb0aff..9613548 100644 --- a/ShellCheck/Analytics.hs +++ b/ShellCheck/Analytics.hs @@ -1254,6 +1254,7 @@ prop_subshellAssignmentCheck3 = verifyFull subshellAssignmentCheck "( A=foo; prop_subshellAssignmentCheck4 = verifyNotFull subshellAssignmentCheck "( A=foo; rm $A; )" prop_subshellAssignmentCheck5 = verifyFull subshellAssignmentCheck "cat foo | while read cow; do true; done; echo $cow;" prop_subshellAssignmentCheck6 = verifyFull subshellAssignmentCheck "( export lol=$(ls); ); echo $lol;" +prop_subshellAssignmentCheck6a= verifyFull subshellAssignmentCheck "( typeset -a lol=a; ); echo $lol;" prop_subshellAssignmentCheck7 = verifyFull subshellAssignmentCheck "cmd | while read foo; do (( n++ )); done; echo \"$n lines\"" prop_subshellAssignmentCheck8 = verifyFull subshellAssignmentCheck "n=3 & echo $((n++))" prop_subshellAssignmentCheck9 = verifyFull subshellAssignmentCheck "read n & n=foo$n" @@ -1316,8 +1317,12 @@ getModifiedVariables t = getModifiedVariableCommand base@(T_SimpleCommand _ _ ((T_NormalWord _ ((T_Literal _ x):_)):rest)) = case x of "read" -> concatMap getLiteral rest - "export" -> concatMap exportParamToLiteral rest "let" -> concatMap letParamToLiteral rest + + "export" -> concatMap getModifierParam rest + "declare" -> concatMap getModifierParam rest + "typeset" -> concatMap getModifierParam rest + _ -> [] where stripEquals s = let rest = dropWhile (/= '=') s in @@ -1333,12 +1338,11 @@ getModifiedVariableCommand base@(T_SimpleCommand _ _ ((T_NormalWord _ ((T_Litera getLiteral t@(T_NormalWord _ [T_DoubleQuoted _ [T_Literal id s]]) = [(base, t, s, DataExternal)] getLiteral x = [] - exportParamToLiteral t@(T_NormalWord _ ((T_Literal _ s):_)) = - if '=' `elem` s - then [(base, t, prefix, DataFrom [stripEqualsFrom t])] - else [] - where prefix = takeWhile (/= '=') s - exportParamToLiteral _ = [] + + getModifierParam t@(T_Assignment _ name value) = + [(base, t, name, DataFrom [value])] + getModifierParam _ = [] + letParamToLiteral token = if var == "" then [] diff --git a/ShellCheck/Parser.hs b/ShellCheck/Parser.hs index 7577617..d565bde 100644 --- a/ShellCheck/Parser.hs +++ b/ShellCheck/Parser.hs @@ -689,7 +689,7 @@ readBackTicked = called "backtick expansion" $ do unEscape ('\\':x:rest) | x `elem` "\"$`\\" = x : unEscape rest unEscape ('\\':'\n':rest) = unEscape rest unEscape (c:rest) = c : unEscape rest - + prop_readDoubleQuoted = isOk readDoubleQuoted "\"Hello $FOO\"" readDoubleQuoted = called "double quoted string" $ do @@ -1071,24 +1071,46 @@ readSeparator = readNewlineList return '\n' -makeSimpleCommand id1 id2 tokens = - let (assignment, rest) = partition (\x -> case x of T_Assignment _ _ _ -> True; _ -> False) tokens - in let (redirections, rest2) = partition (\x -> case x of T_FdRedirect _ _ _ -> True; _ -> False) rest - in T_Redirecting id1 redirections $ T_SimpleCommand id2 assignment rest2 +makeSimpleCommand id1 id2 prefix cmd suffix = + let + (preAssigned, preRest) = partition assignment prefix + (preRedirected, preRest2) = partition redirection preRest + (postRedirected, postRest) = partition redirection suffix + + redirs = preRedirected ++ postRedirected + assigns = preAssigned + args = cmd ++ preRest2 ++ postRest + in + T_Redirecting id1 redirs $ T_SimpleCommand id2 assigns args + where + assignment (T_Assignment _ _ _) = True + assignment _ = False + redirection (T_FdRedirect _ _ _) = True + redirection _ = False + prop_readSimpleCommand = isOk readSimpleCommand "echo test > file" prop_readSimpleCommand2 = isOk readSimpleCommand "cmd &> file" +prop_readSimpleCommand3 = isOk readSimpleCommand "export foo=(bar baz)" +prop_readSimpleCommand4 = isOk readSimpleCommand "typeset -a foo=(lol)" readSimpleCommand = called "simple command" $ do id1 <- getNextId id2 <- getNextId prefix <- option [] readCmdPrefix - cmd <- option [] $ do { f <- readCmdName; return [f]; } - when (null prefix && null cmd) $ fail "No command" - if null cmd - then return $ makeSimpleCommand id1 id2 prefix - else do - suffix <- option [] readCmdSuffix - return $ makeSimpleCommand id1 id2 (prefix ++ cmd ++ suffix) + cmd <- option Nothing $ do { f <- readCmdName; return $ Just f; } + when (null prefix && isNothing cmd) $ fail "No command" + case cmd of + Nothing -> return $ makeSimpleCommand id1 id2 prefix [] [] + Just cmd -> do + suffix <- option [] $ + if isModifierCommand cmd + then readModifierSuffix + else readCmdSuffix + return $ makeSimpleCommand id1 id2 prefix [cmd] suffix + where + isModifierCommand (T_NormalWord _ [T_Literal _ s]) = + s `elem` ["declare", "export", "local", "typeset"] + isModifierCommand _ = False prop_readPipeline = isOk readPipeline "! cat /etc/issue | grep -i ubuntu" prop_readPipeline2 = isWarning readPipeline "!cat /etc/issue | grep -i ubuntu" @@ -1433,6 +1455,7 @@ readCompoundList = readTerm readCmdPrefix = many1 (readIoRedirect <|> readAssignmentWord) readCmdSuffix = many1 (readIoRedirect <|> readCmdWord) +readModifierSuffix = many1 (readIoRedirect <|> readAssignmentWord <|> readCmdWord) prop_readAssignmentWord = isOk readAssignmentWord "a=42" prop_readAssignmentWord2 = isOk readAssignmentWord "b=(1 2 3)"