
#8671: Rebindable syntax creates bogus warning -------------------------+------------------------------------------------- Reporter: | Owner: thomaseding | Status: new Type: bug | Milestone: Priority: | Version: 7.6.3 normal | Operating System: Windows Component: | Type of failure: Incorrect warning at Compiler | compile-time Keywords: | Test Case: Architecture: | Blocking: Unknown/Multiple | Difficulty: | Unknown | Blocked By: | Related Tickets: | -------------------------+------------------------------------------------- {{{ {-# LANGUAGE RebindableSyntax #-} import Data.Void import Prelude ((.), ($), Int, id, Num(..)) (>>) :: (b -> c) -> (a -> b) -> (a -> c) (>>) = (.) return :: Void -> Void return = absurd run :: a -> (a -> b) -> b run x f = f x result :: Int result = run 8 $ do \n -> n * n id (+ 7) (* 2) }}} Compile with -Wall issues incorrect warnings. In fact the suggested fixes cause compile errors if implemented. {{{ Test.hs:22:5: Warning: A do-notation statement discarded a result of type Int. Suppress this warning by saying "_ <- \ n -> (*) n n", or by using the flag -fno-warn-unused-do-bind Test.hs:23:5: Warning: A do-notation statement discarded a result of type Int. Suppress this warning by saying "_ <- id", or by using the flag -fno-warn-unused-do-bind Test.hs:24:5: Warning: A do-notation statement discarded a result of type Int. Suppress this warning by saying "_ <- (( \ x_ -> (+) x_ 7))", or by using the flag -fno-warn-unused-do-bind }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8671 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler