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

GHC ghc-devs at haskell.org
Fri May 5 10:33:45 UTC 2017


#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


More information about the ghc-tickets mailing list