Improve parsing of fd close/duplicate redirections.

This commit is contained in:
Vidar Holen 2016-10-21 11:31:58 -07:00
parent 88c56ecd53
commit 619b6c42f3
3 changed files with 28 additions and 22 deletions

View file

@ -99,6 +99,7 @@ data Token =
| T_IfExpression Id [([Token],[Token])] [Token] | T_IfExpression Id [([Token],[Token])] [Token]
| T_In Id | T_In Id
| T_IoFile Id Token Token | T_IoFile Id Token Token
| T_IoDuplicate Id Token String
| T_LESSAND Id | T_LESSAND Id
| T_LESSGREAT Id | T_LESSGREAT Id
| T_Lbrace Id | T_Lbrace Id
@ -189,6 +190,7 @@ analyze f g i =
delve (T_DollarArithmetic id c) = d1 c $ T_DollarArithmetic id delve (T_DollarArithmetic id c) = d1 c $ T_DollarArithmetic id
delve (T_DollarBracket id c) = d1 c $ T_DollarBracket id delve (T_DollarBracket id c) = d1 c $ T_DollarBracket id
delve (T_IoFile id op file) = d2 op file $ T_IoFile id delve (T_IoFile id op file) = d2 op file $ T_IoFile id
delve (T_IoDuplicate id op num) = d1 op $ \x -> T_IoDuplicate id x num
delve (T_HereString id word) = d1 word $ T_HereString id delve (T_HereString id word) = d1 word $ T_HereString id
delve (T_FdRedirect id v t) = d1 t $ T_FdRedirect id v delve (T_FdRedirect id v t) = d1 t $ T_FdRedirect id v
delve (T_Assignment id mode var indices value) = do delve (T_Assignment id mode var indices value) = do
@ -318,6 +320,7 @@ getId t = case t of
T_BraceExpansion id _ -> id T_BraceExpansion id _ -> id
T_DollarBraceCommandExpansion id _ -> id T_DollarBraceCommandExpansion id _ -> id
T_IoFile id _ _ -> id T_IoFile id _ _ -> id
T_IoDuplicate id _ _ -> id
T_HereDoc id _ _ _ _ -> id T_HereDoc id _ _ _ _ -> id
T_HereString id _ -> id T_HereString id _ -> id
T_FdRedirect id _ _ -> id T_FdRedirect id _ _ -> id

View file

@ -509,6 +509,7 @@ prop_checkBashisms48= verifyNot checkBashisms "#!/bin/dash\necho $LINENO"
prop_checkBashisms49= verify checkBashisms "#!/bin/dash\necho $MACHTYPE" prop_checkBashisms49= verify checkBashisms "#!/bin/dash\necho $MACHTYPE"
prop_checkBashisms50= verify checkBashisms "#!/bin/sh\ncmd >& file" prop_checkBashisms50= verify checkBashisms "#!/bin/sh\ncmd >& file"
prop_checkBashisms51= verifyNot checkBashisms "#!/bin/sh\ncmd 2>&1" prop_checkBashisms51= verifyNot checkBashisms "#!/bin/sh\ncmd 2>&1"
prop_checkBashisms52= verifyNot checkBashisms "#!/bin/sh\ncmd >&2"
checkBashisms params = bashism checkBashisms params = bashism
where where
isDash = shellType params == Dash isDash = shellType params == Dash
@ -983,7 +984,7 @@ prop_checkStderrRedirect4 = verifyNot checkStderrRedirect "errors=$(test 2>&1 >
prop_checkStderrRedirect5 = verifyNot checkStderrRedirect "read < <(test 2>&1 > file)" prop_checkStderrRedirect5 = verifyNot checkStderrRedirect "read < <(test 2>&1 > file)"
prop_checkStderrRedirect6 = verify checkStderrRedirect "foo | bar 2>&1 > /dev/null" prop_checkStderrRedirect6 = verify checkStderrRedirect "foo | bar 2>&1 > /dev/null"
checkStderrRedirect params redir@(T_Redirecting _ [ checkStderrRedirect params redir@(T_Redirecting _ [
T_FdRedirect id "2" (T_IoFile _ (T_GREATAND _) (T_NormalWord _ [T_Literal _ "1"])), T_FdRedirect id "2" (T_IoDuplicate _ (T_GREATAND _) "1"),
T_FdRedirect _ _ (T_IoFile _ op _) T_FdRedirect _ _ (T_IoFile _ op _)
] _) = case op of ] _) = case op of
T_Greater _ -> error T_Greater _ -> error

View file

@ -1547,7 +1547,7 @@ readHereDoc = called "here document" $ do
-- add empty tokens for now, read the rest in readPendingHereDocs -- add empty tokens for now, read the rest in readPendingHereDocs
let doc = T_HereDoc hid dashed quoted endToken [] let doc = T_HereDoc hid dashed quoted endToken []
addPendingHereDoc doc addPendingHereDoc doc
return $ T_FdRedirect fid "" doc return doc
where where
stripLiteral (T_Literal _ x) = x stripLiteral (T_Literal _ x) = x
stripLiteral (T_SingleQuoted _ x) = x stripLiteral (T_SingleQuoted _ x) = x
@ -1618,7 +1618,13 @@ readPendingHereDocs = do
readFilename = readNormalWord readFilename = readNormalWord
readIoFileOp = choice [g_LESSAND, g_GREATAND, g_DGREAT, g_LESSGREAT, g_CLOBBER, redirToken '<' T_Less, redirToken '>' T_Greater ] readIoFileOp = choice [g_DGREAT, g_LESSGREAT, g_GREATAND, g_LESSAND, g_CLOBBER, redirToken '<' T_Less, redirToken '>' T_Greater ]
readIoDuplicate = try $ do
id <- getNextId
op <- g_GREATAND <|> g_LESSAND
target <- readIoVariable <|> many1 digit <|> string "-"
return $ T_IoDuplicate id op target
prop_readIoFile = isOk readIoFile ">> \"$(date +%YYmmDD)\"" prop_readIoFile = isOk readIoFile ">> \"$(date +%YYmmDD)\""
readIoFile = called "redirection" $ do readIoFile = called "redirection" $ do
@ -1626,35 +1632,31 @@ readIoFile = called "redirection" $ do
op <- readIoFileOp op <- readIoFileOp
spacing spacing
file <- readFilename file <- readFilename
return $ T_FdRedirect id "" $ T_IoFile id op file return $ T_IoFile id op file
readIoVariable = try $ do readIoVariable = try $ do
char '{' char '{'
x <- readVariableName x <- readVariableName
char '}' char '}'
lookAhead readIoFileOp
return $ "{" ++ x ++ "}" return $ "{" ++ x ++ "}"
readIoNumber = try $ do readIoSource = try $ do
x <- many1 digit <|> string "&" x <- string "&" <|> readIoVariable <|> many digit
lookAhead readIoFileOp lookAhead $ void readIoFileOp <|> void (string "<<")
return x return x
prop_readIoNumberRedirect = isOk readIoNumberRedirect "3>&2" prop_readIoRedirect = isOk readIoRedirect "3>&2"
prop_readIoNumberRedirect2 = isOk readIoNumberRedirect "2> lol" prop_readIoRedirect2 = isOk readIoRedirect "2> lol"
prop_readIoNumberRedirect3 = isOk readIoNumberRedirect "4>&-" prop_readIoRedirect3 = isOk readIoRedirect "4>&-"
prop_readIoNumberRedirect4 = isOk readIoNumberRedirect "&> lol" prop_readIoRedirect4 = isOk readIoRedirect "&> lol"
prop_readIoNumberRedirect5 = isOk readIoNumberRedirect "{foo}>&2" prop_readIoRedirect5 = isOk readIoRedirect "{foo}>&2"
prop_readIoNumberRedirect6 = isOk readIoNumberRedirect "{foo}<&-" prop_readIoRedirect6 = isOk readIoRedirect "{foo}<&-"
readIoNumberRedirect = do readIoRedirect = do
id <- getNextId id <- getNextId
n <- readIoVariable <|> readIoNumber n <- readIoSource
op <- readHereString <|> readHereDoc <|> readIoFile redir <- readHereString <|> readHereDoc <|> readIoDuplicate <|> readIoFile
let actualOp = case op of T_FdRedirect _ "" x -> x
spacing spacing
return $ T_FdRedirect id n actualOp return $ T_FdRedirect id n redir
readIoRedirect = choice [ readIoNumberRedirect, readHereString, readHereDoc, readIoFile ] `thenSkip` spacing
readRedirectList = many1 readIoRedirect readRedirectList = many1 readIoRedirect
@ -1665,7 +1667,7 @@ readHereString = called "here string" $ do
spacing spacing
id2 <- getNextId id2 <- getNextId
word <- readNormalWord word <- readNormalWord
return $ T_FdRedirect id "" $ T_HereString id2 word return $ T_HereString id2 word
readNewlineList = many1 ((linefeed <|> carriageReturn) `thenSkip` spacing) readNewlineList = many1 ((linefeed <|> carriageReturn) `thenSkip` spacing)
readLineBreak = optional readNewlineList readLineBreak = optional readNewlineList