mirror of
				https://github.com/koalaman/shellcheck.git
				synced 2025-11-01 07:14:25 +08:00 
			
		
		
		
	Added more robust a=cat foo | grep bar checker
This commit is contained in:
		| @@ -147,9 +147,16 @@ checkPipedAssignment _ = return () | ||||
|  | ||||
| prop_checkAssignAteCommand1 = verify checkAssignAteCommand "A=ls -l" | ||||
| prop_checkAssignAteCommand2 = verify checkAssignAteCommand "A=ls --sort=$foo" | ||||
| prop_checkAssignAteCommand3 = verifyNot checkAssignAteCommand "A=foo ls -l" | ||||
| checkAssignAteCommand (T_SimpleCommand id (t:[]) (w:_)) | "-" `isPrefixOf` (concat $ deadSimple w) = | ||||
|         warn id "To assign the output of a command, use var=$(cmd) ." | ||||
| prop_checkAssignAteCommand3 = verify checkAssignAteCommand "A=cat foo | grep bar" | ||||
| prop_checkAssignAteCommand4 = verifyNot checkAssignAteCommand "A=foo ls -l" | ||||
| prop_checkAssignAteCommand5 = verifyNot checkAssignAteCommand "PAGER=cat grep bar" | ||||
| checkAssignAteCommand (T_SimpleCommand id ((T_Assignment _ _ assignmentTerm):[]) (firstWord:_)) = | ||||
|     when ("-" `isPrefixOf` (concat $ deadSimple firstWord) ||  | ||||
|         (isCommonCommand (getLiteralString assignmentTerm) && not (isCommonCommand (getLiteralString firstWord)))) $ | ||||
|             warn id "To assign the output of a command, use var=$(cmd) ." | ||||
|   where | ||||
|     isCommonCommand (Just s) = s `elem` commonCommands | ||||
|     isCommonCommand _ = False | ||||
| checkAssignAteCommand _ = return () | ||||
|  | ||||
|  | ||||
|   | ||||
| @@ -17,7 +17,7 @@ | ||||
| -} | ||||
| {-# LANGUAGE NoMonomorphismRestriction #-} | ||||
|  | ||||
| module ShellCheck.Parser (Note(..), Severity(..), parseShell, ParseResult(..), ParseNote(..), notesFromMap, Metadata(..), sortNotes, getId) where | ||||
| module ShellCheck.Parser (Note(..), Severity(..), parseShell, ParseResult(..), ParseNote(..), notesFromMap, Metadata(..), sortNotes, commonCommands) where | ||||
|  | ||||
| import ShellCheck.AST | ||||
| import Text.Parsec | ||||
| @@ -287,7 +287,6 @@ readConditionContents single = do | ||||
|     readCondAnd = chainl1 readCondTerm readCondOrOp | ||||
|     readCondContents = readCondOr | ||||
|  | ||||
|     commonCommands = [ "admin", "alias", "ar", "asa", "at", "awk", "basename", "batch", "bc", "bg", "break", "c99", "cal", "cat", "cd", "cflow", "chgrp", "chmod", "chown", "cksum", "cmp", "colon", "comm", "command", "compress", "continue", "cp", "crontab", "csplit", "ctags", "cut", "cxref", "date", "dd", "delta", "df", "diff", "dirname", "dot", "du", "echo", "ed", "env", "eval", "ex", "exec", "exit", "expand", "export", "expr", "fc", "fg", "file", "find", "fold", "fort77", "fuser", "gencat", "get", "getconf", "getopts", "grep", "hash", "head", "iconv", "ipcrm", "ipcs", "jobs", "join", "kill", "lex", "link", "ln", "locale", "localedef", "logger", "logname", "lp", "ls", "m4", "mailx", "make", "man", "mesg", "mkdir", "mkfifo", "more", "mv", "newgrp", "nice", "nl", "nm", "nohup", "od", "paste", "patch", "pathchk", "pax", "pr", "printf", "prs", "ps", "pwd", "qalter", "qdel", "qhold", "qmove", "qmsg", "qrerun", "qrls", "qselect", "qsig", "qstat", "qsub", "read", "readonly", "renice", "return", "rm", "rmdel", "rmdir", "sact", "sccs", "sed", "set", "sh", "shift", "sleep", "sort", "split", "strings", "strip", "stty", "tabs", "tail", "talk", "tee", "test", "time", "times", "touch", "tput", "tr", "trap", "tsort", "tty", "type", "ulimit", "umask", "unalias", "uname", "uncompress", "unexpand", "unget", "uniq", "unlink", "unset", "uucp", "uudecode", "uuencode", "uustat", "uux", "val", "vi", "wait", "wc", "what", "who", "write", "xargs", "yacc", "zcat" ] | ||||
|  | ||||
|  | ||||
| prop_a1 = isOk readArithmeticContents " n++ + ++c" | ||||
| @@ -1150,6 +1149,8 @@ g_Lparen = tryToken "(" T_Lparen | ||||
| g_Rparen = tryToken ")" T_Rparen | ||||
| g_Bang = tryToken "!" T_Bang | ||||
|  | ||||
| commonCommands = [ "admin", "alias", "ar", "asa", "at", "awk", "basename", "batch", "bc", "bg", "break", "c99", "cal", "cat", "cd", "cflow", "chgrp", "chmod", "chown", "cksum", "cmp", "colon", "comm", "command", "compress", "continue", "cp", "crontab", "csplit", "ctags", "cut", "cxref", "date", "dd", "delta", "df", "diff", "dirname", "dot", "du", "echo", "ed", "env", "eval", "ex", "exec", "exit", "expand", "export", "expr", "fc", "fg", "file", "find", "fold", "fort77", "fuser", "gencat", "get", "getconf", "getopts", "grep", "hash", "head", "iconv", "ipcrm", "ipcs", "jobs", "join", "kill", "lex", "link", "ln", "locale", "localedef", "logger", "logname", "lp", "ls", "m4", "mailx", "make", "man", "mesg", "mkdir", "mkfifo", "more", "mv", "newgrp", "nice", "nl", "nm", "nohup", "od", "paste", "patch", "pathchk", "pax", "pr", "printf", "prs", "ps", "pwd", "qalter", "qdel", "qhold", "qmove", "qmsg", "qrerun", "qrls", "qselect", "qsig", "qstat", "qsub", "read", "readonly", "renice", "return", "rm", "rmdel", "rmdir", "sact", "sccs", "sed", "set", "sh", "shift", "sleep", "sort", "split", "strings", "strip", "stty", "tabs", "tail", "talk", "tee", "test", "time", "times", "touch", "tput", "tr", "trap", "tsort", "tty", "type", "ulimit", "umask", "unalias", "uname", "uncompress", "unexpand", "unget", "uniq", "unlink", "unset", "uucp", "uudecode", "uuencode", "uustat", "uux", "val", "vi", "wait", "wc", "what", "who", "write", "xargs", "yacc", "zcat" ] | ||||
|  | ||||
| g_Semi = do | ||||
|     notFollowedBy g_DSEMI | ||||
|     tryToken ";" T_Semi | ||||
|   | ||||
		Reference in New Issue
	
	Block a user