Unused "do" bind [GHC-81995]

Flag: -Wunused-do-bind
Enabled by: -Wall

Many monadic actions perform side effects before returning a value.

Sometimes, we are only interested in the side effect of a monadic action, and not in the return value. In these cases, we should use appropriate functions indicating that we purposefully ignore the return value.

Even more, in monadic code without side effects such as the list monad, this warning may indicate a bug.

Examples

Action without side effect is completely ignored in pure monadic code

Error message

list/before/List.hs:6:3: warning: [GHC-81995] [-Wunused-do-bind]
    A do-notation statement discarded a result of type ‘Integer’
    Suggested fix: Suppress this warning by saying ‘_ <- return 1’
  |
6 |   return 1 -- This action has no side effects and is completely ignored.
  |   ^^^^^^^^
List.hs
Before
module List where

-- Evaluates to [2].
list :: [Int]
list = do
  return 1 -- This action has no side effects and is completely ignored.
  return 2
After
module List where

list :: [Int]
-- list = do return 2
list = [2]
Fix warning about unused "do" bind using `sequence_`

For example, sequence :: (Traversable t, Monad m) => t (m a) -> m (t a) performs all actions in a traversable container and returns the container with the return values. In a similar manner, sequence_ performs all actions but indicates that the we want to ignore the return value.

Error message

sequence/before/GetLine.hs:5:3: warning: [GHC-81995] [-Wunused-do-bind]
    A do-notation statement discarded a result of type ‘[()]’
    Suggested fix:
      Suppress this warning by saying
        ‘_ <- sequence [putStrLn "First line", putStrLn "Second line"]’
  |
5 |   sequence [putStrLn "First line", putStrLn "Second line"]
  |   ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
GetLine.hs
Before
module GetLine where

main :: IO ()
main = do
  sequence [putStrLn "First line", putStrLn "Second line"]
  putStrLn "Done."
After
module GetLine where

main :: IO ()
main = do
  sequence_ [putStrLn "First line", putStrLn "Second line"]
  putStrLn "Done."