#3592: Eta-contraction gives a rather bogus type error message
----------------------------------------+-----------------------------------
    Reporter:  guest                    |        Owner:  simonpj     
        Type:  bug                      |       Status:  new         
    Priority:  normal                   |    Milestone:  7.4.1       
   Component:  Compiler (Type checker)  |      Version:  6.10.3      
    Keywords:                           |     Testcase:              
   Blockedby:                           |   Difficulty:  Unknown     
          Os:  Unknown/Multiple         |     Blocking:              
Architecture:  Unknown/Multiple         |      Failure:  None/Unknown
----------------------------------------+-----------------------------------

Comment(by simonpj):

 For this module
 {{{
 {-# LANGUAGE RankNTypes #-}
 module T3592 where

 type T a = Show a => a

 f :: T a -> String
 f = show

 g :: T a -> String
 g x = show x

 }}}
 We now get
 {{{
 T3592.hs:7:5:                           -- Eta contracted version
     No instance for (Show (T a))
       arising from a use of `show'
     Possible fix: add an instance declaration for (Show (T a))
     In the expression: show
     In an equation for `f': f = show

 T3592.hs:10:12:                          -- Not eta contracted
     No instance for (Show a)
       arising from a use of `x'
     In the first argument of `show', namely `x'
     In the expression: show x
     In an equation for `g': g x = show x
 }}}
 So the error messages are slightly different, because of the implicit
 instantiation of 'x' when it is explicit, but I think both are reasonable.
 I think I'll declare this one done.

 I'll add a test.

 Simon

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3592#comment:6>
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