[GHC] #8671: Rebindable syntax creates bogus warning

#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

#8671: Rebindable syntax creates bogus warning -------------------------------------------------+------------------------- Reporter: thomaseding | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Incorrect warning at | Unknown/Multiple compile-time | Difficulty: Test Case: | Unknown Blocking: | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Comment (by simonpj): Interesting. I suppose your implicit proposal is that we should suppress the do-notation-related warnings if `-XRebindableSyntax` is in force? I'd be ok with that, and it'd be easy to do. Other opinions? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8671#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8671: Rebindable syntax creates bogus warning -------------------------------------------------+------------------------- Reporter: thomaseding | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Incorrect warning at | Unknown/Multiple compile-time | Difficulty: Test Case: | Unknown Blocking: | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Comment (by thomaseding): I'd be fine with simply having the warning suppressed in that case. Though I could see the warning be useful for rebound do-notation where it makes sense (e.g. monads that have restrictions on their kinds http://blog .omega-prime.co.uk/?p=127). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8671#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8671: Rebindable syntax creates bogus warning -------------------------------------------------+------------------------- Reporter: thomaseding | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Incorrect warning at | Unknown/Multiple compile-time | Difficulty: Test Case: | Unknown Blocking: | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Comment (by thomaseding): Just some initial thoughts that may or may not be useful -- concerning conditionally suppressing the warning based on what the syntax is rebound to... ---- Consider {{{ blah = do x -- suppose that GHC issues the warning for this (whether the warning is correct or not) y }}} Translates to {{{ blah = x >> y }}} Before issuing the warning, consider translating the code to {{{ blah = x >>= (\_ -> y) }}} If this compiles, then issue the warning. Otherwise do not. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8671#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8671: Rebindable syntax creates bogus warning -------------------------------------+------------------------------------- Reporter: | Owner: thomaseding | Status: new Type: bug | Milestone: Priority: normal | Version: 7.6.3 Component: Compiler | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: Incorrect | Related Tickets: warning at compile-time | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by gintas): * os: Windows => Unknown/Multiple Comment: This doesn't look Windows-specific. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8671#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8671: Rebindable syntax creates bogus warning -------------------------------------+------------------------------------- Reporter: | Owner: thomaseding | Status: new Type: bug | Milestone: Priority: normal | Version: 7.6.3 Component: Compiler | Keywords: (Type checker) | Architecture: Unknown/Multiple Resolution: | Difficulty: Unknown Operating System: | Blocked By: Unknown/Multiple | Related Tickets: Type of failure: Incorrect | warning at compile-time | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by thomie): * component: Compiler => Compiler (Type checker) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8671#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC