#5320: check_overlap panic (7.1 regression)
-----------------------------------+----------------------------------------
    Reporter:  mikhail.vorozhtsov  |        Owner:                    
        Type:  bug                 |       Status:  new               
    Priority:  normal              |    Milestone:                    
   Component:  Compiler            |      Version:  7.1               
    Keywords:                      |     Testcase:                    
   Blockedby:                      |   Difficulty:                    
          Os:  Unknown/Multiple    |     Blocking:                    
Architecture:  Unknown/Multiple    |      Failure:  Compile-time crash
-----------------------------------+----------------------------------------

Comment(by simonpj):

 Harump. I'll fix the crash, but it does expose a little problem.  Consider
 this program
 {{{
 {-# LANGUAGE FlexibleInstances, FlexibleContexts,
              ScopedTypeVariables, MultiParamTypeClasses, TypeFamilies #-}

 module Foo where

 class C a b where op :: a -> b
 instance C Int b
 type family F a

 f :: forall w. C Int w => Int -> w -> F Int
 f x y = op x :: F Int
 }}}
 The call of `op` gives rise to a wanted constraint `(C Int (F Int))` which
 you would think would be satisfied from the `(C Int b)` instance
 declaration.  But actually we get this:
 {{{
 Foo.hs:10:9:
     Overlapping instances for C Int (F Int)
       arising from a use of `op'
     Matching instances: instance C Int b -- Defined at Foo.hs:6:10-16
     There exists a (perhaps superclass) match:
       from the context (C Int w)
         bound by the type signature for f :: C Int w => Int -> w -> F Int
         at Foo.hs:10:1-21
 }}}
 GHC is saying (a bit stupidly) that `(C Int (F Int))` might ultimately
 reduce, by evaluating the call to `F`,  to `(C Int w)`, which could be
 satisfied from the constraint in the signature rather than the instance
 declaration.  Of course, it can't.  But it wouldn't have been so stupid if
 the program had been
 {{{
 g :: forall w. C Int w => Int -> w -> F [w]
 g x y = op x :: F [w]
 }}}
 Now it's not so stupid; `(F [w])` might indeed reduce to `w`.

 But it's delicate, and may end up rejecdting a program that really should
 be accepted (like `f`).  Not sure what to do here.

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