Use standard Haskell 'void' instead of custom

This commit is contained in:
Vidar Holen 2017-07-08 10:23:51 -07:00
parent b064cf3038
commit bd13224907
1 changed files with 12 additions and 14 deletions

View File

@ -357,10 +357,8 @@ unexpecting s p = try $
notFollowedBy2 = unexpecting "" notFollowedBy2 = unexpecting ""
disregard = void
reluctantlyTill p end = reluctantlyTill p end =
(lookAhead (disregard (try end) <|> eof) >> return []) <|> do (lookAhead (void (try end) <|> eof) >> return []) <|> do
x <- p x <- p
more <- reluctantlyTill p end more <- reluctantlyTill p end
return $ x:more return $ x:more
@ -469,7 +467,7 @@ readConditionContents single =
guardArithmetic = do guardArithmetic = do
try . lookAhead $ disregard (oneOf "+*/%") <|> disregard (string "- ") try . lookAhead $ void (oneOf "+*/%") <|> void (string "- ")
parseProblem ErrorC 1076 $ parseProblem ErrorC 1076 $
if single if single
then "Trying to do math? Use e.g. [ $((i/2+7)) -ge 18 ]." then "Trying to do math? Use e.g. [ $((i/2+7)) -ge 18 ]."
@ -512,7 +510,7 @@ readConditionContents single =
parseProblemAt pos ErrorC 1021 parseProblemAt pos ErrorC 1021
"You need a space before the \\)" "You need a space before the \\)"
fail "Missing space before )" fail "Missing space before )"
disregard spacing void spacing
return x return x
where endedWith str (T_NormalWord id s@(_:_)) = where endedWith str (T_NormalWord id s@(_:_)) =
case last s of T_Literal id s -> str `isSuffixOf` s case last s of T_Literal id s -> str `isSuffixOf` s
@ -605,7 +603,7 @@ readConditionContents single =
readNormalLiteral "( " <|> readNormalLiteral "( " <|>
readPipeLiteral <|> readPipeLiteral <|>
readGlobLiteral) readGlobLiteral)
disregard spacing void spacing
return $ T_NormalWord id parts return $ T_NormalWord id parts
where where
readGlobLiteral = do readGlobLiteral = do
@ -1152,7 +1150,7 @@ readBackTicked quoted = called "backtick expansion" $ do
verifyEof verifyEof
return cmds return cmds
backtick = backtick =
disregard (char '`') <|> do void (char '`') <|> do
pos <- getPosition pos <- getPosition
char '´' char '´'
parseProblemAt pos ErrorC 1077 parseProblemAt pos ErrorC 1077
@ -1647,7 +1645,7 @@ readPendingHereDocs = do
hereData <- anyChar `reluctantlyTill` do hereData <- anyChar `reluctantlyTill` do
many linewhitespace many linewhitespace
string endToken string endToken
disregard (char '\n') <|> eof void (char '\n') <|> eof
do do
spaces <- many linewhitespace spaces <- many linewhitespace
verifyHereDoc dashed quoted spaces hereData verifyHereDoc dashed quoted spaces hereData
@ -1773,7 +1771,7 @@ readSeparatorOp = do
spacing spacing
return f return f
readSequentialSep = disregard (g_Semi >> readLineBreak) <|> disregard readNewlineList readSequentialSep = void (g_Semi >> readLineBreak) <|> void readNewlineList
readSeparator = readSeparator =
do do
separator <- readSeparatorOp separator <- readSeparatorOp
@ -2197,14 +2195,14 @@ readSelectClause = called "select loop" $ do
readInClause = do readInClause = do
g_In g_In
things <- readCmdWord `reluctantlyTill` things <- readCmdWord `reluctantlyTill`
(disregard g_Semi <|> disregard linefeed <|> disregard g_Do) (void g_Semi <|> void linefeed <|> void g_Do)
do { do {
lookAhead g_Do; lookAhead g_Do;
parseNote ErrorC 1063 "You need a line feed or semicolon before the 'do'."; parseNote ErrorC 1063 "You need a line feed or semicolon before the 'do'.";
} <|> do { } <|> do {
optional g_Semi; optional g_Semi;
disregard allspacing; void allspacing;
} }
return things return things
@ -2266,7 +2264,7 @@ prop_readFunctionDefinition11= isWarning readFunctionDefinition "function foo{\n
readFunctionDefinition = called "function" $ do readFunctionDefinition = called "function" $ do
functionSignature <- try readFunctionSignature functionSignature <- try readFunctionSignature
allspacing allspacing
disregard (lookAhead $ oneOf "{(") <|> parseProblem ErrorC 1064 "Expected a { to open the function definition." void (lookAhead $ oneOf "{(") <|> parseProblem ErrorC 1064 "Expected a { to open the function definition."
group <- readBraceGroup <|> readSubshell group <- readBraceGroup <|> readSubshell
return $ functionSignature group return $ functionSignature group
where where
@ -2451,7 +2449,7 @@ readAssignmentWordExt lenient = try $ do
pos <- getPosition pos <- getPosition
op <- readAssignmentOp op <- readAssignmentOp
hasRightSpace <- liftM (not . null) spacing hasRightSpace <- liftM (not . null) spacing
isEndOfCommand <- liftM isJust $ optionMaybe (try . lookAhead $ (disregard (oneOf "\r\n;&|)") <|> eof)) isEndOfCommand <- liftM isJust $ optionMaybe (try . lookAhead $ (void (oneOf "\r\n;&|)") <|> eof))
if not hasLeftSpace && (hasRightSpace || isEndOfCommand) if not hasLeftSpace && (hasRightSpace || isEndOfCommand)
then do then do
when (variable /= "IFS" && hasRightSpace && not isEndOfCommand) $ when (variable /= "IFS" && hasRightSpace && not isEndOfCommand) $
@ -2606,7 +2604,7 @@ g_Semi = do
tryToken ";" T_Semi tryToken ";" T_Semi
keywordSeparator = keywordSeparator =
eof <|> disregard (try allspacingOrFail) <|> disregard (oneOf ";()[<>&|") eof <|> void (try allspacingOrFail) <|> void (oneOf ";()[<>&|")
readKeyword = choice [ g_Then, g_Else, g_Elif, g_Fi, g_Do, g_Done, g_Esac, g_Rbrace, g_Rparen, g_DSEMI ] readKeyword = choice [ g_Then, g_Else, g_Elif, g_Fi, g_Do, g_Done, g_Esac, g_Rbrace, g_Rparen, g_DSEMI ]