summaryrefslogtreecommitdiff
path: root/libraries/base/Text
diff options
context:
space:
mode:
authorIan Lynagh <igloo@earth.li>2009-07-09 16:39:12 +0000
committerIan Lynagh <igloo@earth.li>2009-07-09 16:39:12 +0000
commitd521a6aeb63d1d9587a656dbe9807735763b3661 (patch)
treea40390fd2b06b5dab78db65c34beb538ca54426f /libraries/base/Text
parent201a2888eea007f06fd741dc754e4a10c40a674b (diff)
downloadhaskell-d521a6aeb63d1d9587a656dbe9807735763b3661.tar.gz
Fix "warn-unused-do-bind" warnings where we really do want to ignore the result
Diffstat (limited to 'libraries/base/Text')
-rw-r--r--libraries/base/Text/ParserCombinators/ReadP.hs14
-rw-r--r--libraries/base/Text/Read/Lex.hs20
2 files changed, 17 insertions, 17 deletions
diff --git a/libraries/base/Text/ParserCombinators/ReadP.hs b/libraries/base/Text/ParserCombinators/ReadP.hs
index 9e6dcee8ed..09fc10d79b 100644
--- a/libraries/base/Text/ParserCombinators/ReadP.hs
+++ b/libraries/base/Text/ParserCombinators/ReadP.hs
@@ -287,7 +287,7 @@ string :: String -> ReadP String
string this = do s <- look; scan this s
where
scan [] _ = do return this
- scan (x:xs) (y:ys) | x == y = do get; scan xs ys
+ scan (x:xs) (y:ys) | x == y = do _ <- get; scan xs ys
scan _ _ = do pfail
munch :: (Char -> Bool) -> ReadP String
@@ -298,7 +298,7 @@ munch p =
do s <- look
scan s
where
- scan (c:cs) | p c = do get; s <- scan cs; return (c:s)
+ scan (c:cs) | p c = do _ <- get; s <- scan cs; return (c:s)
scan _ = do return ""
munch1 :: (Char -> Bool) -> ReadP String
@@ -321,7 +321,7 @@ skipSpaces =
do s <- look
skip s
where
- skip (c:s) | isSpace c = do get; skip s
+ skip (c:s) | isSpace c = do _ <- get; skip s
skip _ = do return ()
count :: Int -> ReadP a -> ReadP [a]
@@ -332,9 +332,9 @@ count n p = sequence (replicate n p)
between :: ReadP open -> ReadP close -> ReadP a -> ReadP a
-- ^ @between open close p@ parses @open@, followed by @p@ and finally
-- @close@. Only the value of @p@ is returned.
-between open close p = do open
+between open close p = do _ <- open
x <- p
- close
+ _ <- close
return x
option :: a -> ReadP a -> ReadP a
@@ -375,12 +375,12 @@ sepBy1 p sep = liftM2 (:) p (many (sep >> p))
endBy :: ReadP a -> ReadP sep -> ReadP [a]
-- ^ @endBy p sep@ parses zero or more occurrences of @p@, separated and ended
-- by @sep@.
-endBy p sep = many (do x <- p ; sep ; return x)
+endBy p sep = many (do x <- p ; _ <- sep ; return x)
endBy1 :: ReadP a -> ReadP sep -> ReadP [a]
-- ^ @endBy p sep@ parses one or more occurrences of @p@, separated and ended
-- by @sep@.
-endBy1 p sep = many1 (do x <- p ; sep ; return x)
+endBy1 p sep = many1 (do x <- p ; _ <- sep ; return x)
chainr :: ReadP a -> ReadP (a -> a -> a) -> a -> ReadP a
-- ^ @chainr p op x@ parses zero or more occurrences of @p@, separated by @op@.
diff --git a/libraries/base/Text/Read/Lex.hs b/libraries/base/Text/Read/Lex.hs
index 94292e0a2c..33291354b8 100644
--- a/libraries/base/Text/Read/Lex.hs
+++ b/libraries/base/Text/Read/Lex.hs
@@ -151,10 +151,10 @@ notANumber = 0 :% 0
lexLitChar :: ReadP Lexeme
lexLitChar =
- do char '\''
+ do _ <- char '\''
(c,esc) <- lexCharE
guard (esc || c /= '\'') -- Eliminate '' possibility
- char '\''
+ _ <- char '\''
return (Char c)
lexChar :: ReadP Char
@@ -195,7 +195,7 @@ lexCharE =
return (chr (fromInteger n))
lexCntrlChar =
- do char '^'
+ do _ <- char '^'
c <- get
case c of
'@' -> return '\^@'
@@ -279,7 +279,7 @@ lexCharE =
lexString :: ReadP Lexeme
lexString =
- do char '"'
+ do _ <- char '"'
body id
where
body f =
@@ -293,11 +293,11 @@ lexString =
+++ lexCharE
lexEmpty =
- do char '\\'
+ do _ <- char '\\'
c <- get
case c of
'&' -> do return ()
- _ | isSpace c -> do skipSpaces; char '\\'; return ()
+ _ | isSpace c -> do skipSpaces; _ <- char '\\'; return ()
_ -> do pfail
-- ---------------------------------------------------------------------------
@@ -314,7 +314,7 @@ lexNumber
lexHexOct :: ReadP Lexeme
lexHexOct
- = do char '0'
+ = do _ <- char '0'
base <- lexBaseChar
digits <- lexDigits base
return (Int (val (fromIntegral base) 0 digits))
@@ -359,12 +359,12 @@ lexDecNumber =
lexFrac :: ReadP (Maybe Digits)
-- Read the fractional part; fail if it doesn't
-- start ".d" where d is a digit
-lexFrac = do char '.'
+lexFrac = do _ <- char '.'
fraction <- lexDigits 10
return (Just fraction)
lexExp :: ReadP (Maybe Integer)
-lexExp = do char 'e' +++ char 'E'
+lexExp = do _ <- char 'e' +++ char 'E'
exp <- signedExp +++ lexInteger 10
return (Just exp)
where
@@ -382,7 +382,7 @@ lexDigits base =
return xs
where
scan (c:cs) f = case valDig base c of
- Just n -> do get; scan cs (f.(n:))
+ Just n -> do _ <- get; scan cs (f.(n:))
Nothing -> do return (f [])
scan [] f = do return (f [])