mirror of
https://github.com/koalaman/shellcheck.git
synced 2025-08-07 22:38:50 +08:00
Added support for process substitution
This commit is contained in:
@@ -471,7 +471,7 @@ checkPossibleTermination pos [T_Literal _ x] =
|
||||
checkPossibleTermination _ _ = return ()
|
||||
|
||||
|
||||
readNormalWordPart = readSingleQuoted <|> readDoubleQuoted <|> readExtglob <|> readDollar <|> readBraced <|> readBackTicked <|> (readNormalLiteral)
|
||||
readNormalWordPart = readSingleQuoted <|> readDoubleQuoted <|> readExtglob <|> readDollar <|> readBraced <|> readBackTicked <|> readProcSub <|> readNormalLiteral
|
||||
readSpacePart = do
|
||||
id <- getNextId
|
||||
x <- many1 whitespace
|
||||
@@ -489,6 +489,20 @@ readDollarBracedLiteral = do
|
||||
vars <- (readBraceEscaped <|> (anyChar >>= \x -> return [x])) `reluctantlyTill1` bracedQuotable
|
||||
return $ T_Literal id $ concat vars
|
||||
|
||||
prop_readProcSub1 = isOk readProcSub "<(echo test | wc -l)"
|
||||
prop_readProcSub2 = isOk readProcSub "<( if true; then true; fi )"
|
||||
readProcSub = do
|
||||
id <- getNextId
|
||||
dir <- try $ do
|
||||
x <- oneOf "<>"
|
||||
char '('
|
||||
return [x]
|
||||
allspacing
|
||||
list <- readCompoundList
|
||||
allspacing
|
||||
char ')'
|
||||
return $ T_ProcSub id dir list
|
||||
|
||||
prop_readSingleQuoted = isOk readSingleQuoted "'foo bar'"
|
||||
prop_readSingleQuoted2 = isWarning readSingleQuoted "'foo bar\\'"
|
||||
readSingleQuoted = do
|
||||
@@ -774,7 +788,7 @@ debugHereDoc pos endToken doc =
|
||||
|
||||
|
||||
readFilename = readNormalWord
|
||||
readIoFileOp = choice [g_LESSAND, g_GREATAND, g_DGREAT, g_LESSGREAT, g_CLOBBER, tryToken "<" T_Less, tryToken ">" T_Greater ]
|
||||
readIoFileOp = choice [g_LESSAND, g_GREATAND, g_DGREAT, g_LESSGREAT, g_CLOBBER, redirToken '<' T_Less, redirToken '>' T_Greater ]
|
||||
|
||||
prop_readIoFile = isOk readIoFile ">> \"$(date +%YYmmDD)\""
|
||||
readIoFile = do
|
||||
@@ -1176,6 +1190,12 @@ tryToken s t = try $ do
|
||||
spacing
|
||||
return $ t id
|
||||
|
||||
redirToken c t = try $ do
|
||||
id <- getNextId
|
||||
char c
|
||||
notFollowedBy $ char '('
|
||||
return $ t id
|
||||
|
||||
tryWordToken s t = tryParseWordToken (string s) t `thenSkip` spacing
|
||||
tryParseWordToken parser t = try $ do
|
||||
id <- getNextId
|
||||
|
Reference in New Issue
Block a user