#4966: Type checking regression
----------------------------------------+-----------------------------------
    Reporter:  igloo                    |        Owner:  simonpj     
        Type:  bug                      |       Status:  new         
    Priority:  highest                  |    Milestone:  7.0.2       
   Component:  Compiler (Type checker)  |      Version:  7.0.1       
    Keywords:                           |     Testcase:              
   Blockedby:                           |   Difficulty:              
          Os:  Unknown/Multiple         |     Blocking:              
Architecture:  Unknown/Multiple         |      Failure:  None/Unknown
----------------------------------------+-----------------------------------
 This module:
 {{{
 {-# LANGUAGE EmptyDataDecls #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE UndecidableInstances #-}
 {-# LANGUAGE OverlappingInstances #-}

 module HTk.Toolkit.TreeList (getObjectFromTreeList) where

 class Eq c => CItem c

 data StateEntry a = StateEntry (TreeListObject a)
                                a -- Comment this 'a' out and it type
 checks
     deriving Eq

 getObjectFromTreeList :: CItem a => [StateEntry a] -> Bool
 getObjectFromTreeList state = (head state == head state)

 data CItem a => TreeListObject a

 instance CItem a => Eq (TreeListObject a)

 class GUIObject w where
   toGUIObject     :: w -> GUIOBJECT

 instance GUIObject w => Eq w where
   w1 == w2 = toGUIObject w1 == toGUIObject w2

 data GUIOBJECT

 instance Eq GUIOBJECT where
   (==) = undefined
   (/=) = undefined
 }}}
 is accepted by 7.0.1, but not by 7.0-branch or HEAD:
 {{{
 Q.hs:16:43:
     Could not deduce (GUIObject a) arising from a use of `=='
     from the context (CItem a)
       bound by the type signature for
                  getObjectFromTreeList :: CItem a => [StateEntry a] ->
 Bool
       at Q.hs:16:1-56
     Possible fix:
       add (GUIObject a) to the context of
         the type signature for
           getObjectFromTreeList :: CItem a => [StateEntry a] -> Bool
     In the expression: (head state == head state)
     In an equation for `getObjectFromTreeList':
         getObjectFromTreeList state = (head state == head state)
 }}}
 If you comment out the `a` then it is accepted by all 3.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4966>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to