#2572: scoped type variables: bad error message, and wrong semantics?
----------------------------------------+-----------------------------------
    Reporter:  igloo                    |       Owner:         
        Type:  bug                      |      Status:  new    
    Priority:  normal                   |   Milestone:  6.10.1 
   Component:  Compiler (Type checker)  |     Version:  6.9    
    Severity:  normal                   |    Keywords:         
  Difficulty:  Unknown                  |    Testcase:  reify  
Architecture:  Unknown                  |          Os:  Unknown
----------------------------------------+-----------------------------------
 With this module (a cut-down version of reify):
 {{{
 {-# OPTIONS -fglasgow-exts #-}

 module Foo where

 type GTypeFun = forall a . a -> ()

 gmapType :: Int -> GTypeFun
 gmapType _ (_ :: a) = undefined
 }}}
 GHC gives the rather perplexing error:
 {{{
 Foo.hs:8:12:
     The scoped type variables `a' and `a'
       are bound to the same type (variable)
       Distinct scoped type variables must be distinct
     In the pattern: _ :: a
     In the definition of `gmapType': gmapType _ (_ :: a) = undefined
 }}}
 Having locations for the two `a`s would be useful.

 This module gives the same error:
 {{{
 {-# OPTIONS -fglasgow-exts #-}

 module Foo where

 gmapType :: Int -> (forall a . a -> ())
 gmapType _ (_ :: a) = undefined
 }}}

 GHC 6.8.2 accepts both modules.

 I don't think that the forall in the type signature should bring `a` into
 scope for the body, as it doesn't bring it into scope for the type
 signature.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2572>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to