Fix "warn-unused-do-bind" warnings where we really do want to ignore the result
authorIan Lynagh <igloo@earth.li>
Thu, 9 Jul 2009 16:39:12 +0000 (16:39 +0000)
committerIan Lynagh <igloo@earth.li>
Thu, 9 Jul 2009 16:39:12 +0000 (16:39 +0000)
Foreign/C/Error.hs
Foreign/Marshal/Pool.hs
Foreign/Marshal/Utils.hs
GHC/IO.hs
GHC/IO/Buffer.hs
Text/ParserCombinators/ReadP.hs
Text/Read/Lex.hs

index ea38694..d2e6f64 100644 (file)
@@ -378,7 +378,8 @@ throwErrnoIfRetryMayBlock pred loc f on_block  =
         if err == eINTR
           then throwErrnoIfRetryMayBlock pred loc f on_block
           else if err == eWOULDBLOCK || err == eAGAIN
-                 then do on_block; throwErrnoIfRetryMayBlock pred loc f on_block
+                 then do _ <- on_block
+                         throwErrnoIfRetryMayBlock pred loc f on_block
                  else throwErrno loc
       else return res
 
index 9c07558..47e4f86 100644 (file)
@@ -143,7 +143,7 @@ pooledRealloc = pr undefined
 pooledReallocBytes :: Pool -> Ptr a -> Int -> IO (Ptr a)
 pooledReallocBytes (Pool pool) ptr size = do
    let cPtr = castPtr ptr
-   throwIf (not . (cPtr `elem`)) (\_ -> "pointer not in pool") (readIORef pool)
+   _ <- throwIf (not . (cPtr `elem`)) (\_ -> "pointer not in pool") (readIORef pool)
    newPtr <- reallocBytes cPtr size
    ptrs <- readIORef pool
    writeIORef pool (newPtr : delete cPtr ptrs)
index d800afe..5ef1dba 100644 (file)
@@ -158,14 +158,14 @@ withMany withFoo (x:xs) f = withFoo x $ \x' ->
 -- first (destination); the copied areas may /not/ overlap
 --
 copyBytes               :: Ptr a -> Ptr a -> Int -> IO ()
-copyBytes dest src size  = do memcpy dest src (fromIntegral size)
+copyBytes dest src size  = do _ <- memcpy dest src (fromIntegral size)
                               return ()
 
 -- |Copies the given number of bytes from the second area (source) into the
 -- first (destination); the copied areas /may/ overlap
 --
 moveBytes               :: Ptr a -> Ptr a -> Int -> IO ()
-moveBytes dest src size  = do memmove dest src (fromIntegral size)
+moveBytes dest src size  = do _ <- memmove dest src (fromIntegral size)
                               return ()
 
 
index 865a09c..c805004 100644 (file)
--- a/GHC/IO.hs
+++ b/GHC/IO.hs
@@ -338,7 +338,7 @@ blocked = IO $ \s -> case asyncExceptionsBlocked# s of
                         (# s', i #) -> (# s', i /=# 0# #)
 
 onException :: IO a -> IO b -> IO a
-onException io what = io `catchException` \e -> do what
+onException io what = io `catchException` \e -> do _ <- what
                                                    throw (e :: SomeException)
 
 finally :: IO a         -- ^ computation to run first
@@ -348,7 +348,7 @@ finally :: IO a         -- ^ computation to run first
 a `finally` sequel =
   block (do
     r <- unblock a `onException` sequel
-    sequel
+    _ <- sequel
     return r
   )
 
index 4cd13a6..18304fe 100644 (file)
@@ -243,7 +243,9 @@ newBuffer bytes sz state = do
 slideContents :: Buffer Word8 -> IO (Buffer Word8)
 slideContents buf@Buffer{ bufL=l, bufR=r, bufRaw=raw } = do
   let elems = r - l
-  withRawBuffer raw $ \p -> memcpy p (p `plusPtr` l) (fromIntegral elems)
+  withRawBuffer raw $ \p ->
+      do _ <- memcpy p (p `plusPtr` l) (fromIntegral elems)
+         return ()
   return buf{ bufL=0, bufR=elems }
 
 foreign import ccall unsafe "memcpy"
index 9e6dcee..09fc10d 100644 (file)
@@ -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@.
index 94292e0..3329135 100644 (file)
@@ -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 [])