[GHC] #13649: RebindableSyntax causes type errors when 'fail' is not defined, even if not used.

#13649: RebindableSyntax causes type errors when 'fail' is not defined, even if not used. -------------------------------------+------------------------------------- Reporter: AaronFriel | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc1 Keywords: | Operating System: Unknown/Multiple RebindableSyntax | Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- With -XRebindableSyntax and a wildcard pattern on an action, a spurious compiler error occurs if `fail` is not in scope: {{{ Not in scope: ‘fail’ Perhaps you want to add ‘fail’ to the import list in the import of ‘Prelude’ (rebind.hs:6:1-53). | 27 | _ <- m1 | ^^^^^^^ }}} {{{#!hs {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE RebindableSyntax #-} module Main where import Prelude (String, print, Maybe (..), error, id) class MyFunctor f where fmap :: (a -> b) -> f a -> f b class MyApplicative f where pure :: a -> f a (<*>) :: f (a -> b) -> f a -> f b class MyMonad m where return :: a -> m a (>>) :: m a -> m b -> m b (>>=) :: m a -> (a -> m b) -> m b join :: m (m a) -> m a -- Uncommenting the following lines allows testCase1 to compile: -- class MyFail m where -- fail :: String -> m a -- But testCase1 will not require a 'MyFail m' constraint. testCase1 :: MyMonad m => m a -> m () testCase1 m1 = do _ <- m1 return () testCase2 :: MyMonad m => m a -> m () testCase2 m1 = do m1 return () }}} In this example, testCase1 will fail to compile until the type class `MyFail` is uncommented. As with #13648, I think this looks like an easy fix before the 8.2.1 release, and I would be happy to submit a patch next week if someone could point me the way. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13649 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13649: RebindableSyntax causes type errors when 'fail' is not defined, even if not used. -------------------------------------+------------------------------------- Reporter: AaronFriel | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc1 Resolution: | Keywords: | RebindableSyntax Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): This is not really a bug, but rather how `do` notation is specified. If you look at https://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-470003.1... you will see {{{ do {p <- e; stmts} = let ok p = do {stmts} ok _ = fail "..." in e >>= ok }}} One could argue that if the pattern is `_`, the second line should be omitted, but where to stop? What about `do () <- …`, an obviously complete pattern, should the `fail` line be omitted as well? But that information might only be available after type-checking, whereas this happens before… I don’t have an opinion of my own here, just pointing out that the current behaviour is as specified, and that a change is not as trivial as it looks. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13649#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13649: RebindableSyntax causes type errors when 'fail' is not defined, even if not used. -------------------------------------+------------------------------------- Reporter: AaronFriel | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc1 Resolution: | Keywords: | RebindableSyntax Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by AaronFriel): Interesting, I thought that the lack of the constraint meant that GHC here was not following that spec. How does the `fail` get removed such that it doesn't entail a constraint? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13649#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13649: RebindableSyntax causes type errors when 'fail' is not defined, even if not used. -------------------------------------+------------------------------------- Reporter: AaronFriel | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc1 Resolution: | Keywords: | RebindableSyntax Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): That is indeed a good question. It seems that the type signature of `fail` is ignored completely. This might indicate that the renamer requires `fail` to be present, but that the type-checker does not see it. And `compiler/deSugar/DsExpr.hs` definitely does not emit a call to `fail` if the match can fail. In function `tcMonadFailOp` the `fail` part of a bind is only type-checked if the pattern can fail, using `isIrrefutableHsPat`. Potentially, the local function `getFailFunction` in {{{ rnStmt ctxt rnBody (L loc (BindStmt pat body _ _ _)) thing_inside }}} could do the same. Is that enough pointing-the-way for you to try to fix this? If you do, make a good note somewhere explaining the interplay of how the renamer, the type checker and the desugarer decide whether to assume a call to the `fail` function or not. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13649#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13649: RebindableSyntax causes type errors when 'fail' is not defined, even if not used. -------------------------------------+------------------------------------- Reporter: AaronFriel | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc1 Resolution: | Keywords: | RebindableSyntax Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes I agree... if the pattern returns true to `isIrrefutableHsPat` we should not look up the fail function. It'd be great if someone could fix this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13649#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13649: RebindableSyntax causes type errors when 'fail' is not defined, even if not used. -------------------------------------+------------------------------------- Reporter: AaronFriel | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc1 Resolution: | Keywords: | RebindableSyntax Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.2.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13649#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13649: RebindableSyntax causes type errors when 'fail' is not defined, even if not
used.
-------------------------------------+-------------------------------------
Reporter: AaronFriel | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.2.1
Component: Compiler | Version: 8.2.1-rc1
Resolution: | Keywords:
| RebindableSyntax
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#13649: RebindableSyntax causes type errors when 'fail' is not defined, even if not used. -------------------------------------+------------------------------------- Reporter: AaronFriel | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc1 Resolution: | Keywords: | RebindableSyntax Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3553 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge * differential: => Phab:D3553 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13649#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13649: RebindableSyntax causes type errors when 'fail' is not defined, even if not used. -------------------------------------+------------------------------------- Reporter: AaronFriel | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc1 Resolution: fixed | Keywords: | RebindableSyntax Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3553 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged with 56a4863b25687319a07db596bd47d724456317a5. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13649#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC