#2247: GHC accepts FD violations, unless the conflicing instances are used
----------------------------------------+-----------------------------------
    Reporter:  claus                    |        Owner:         
        Type:  bug                      |       Status:  new    
    Priority:  normal                   |    Milestone:         
   Component:  Compiler (Type checker)  |      Version:  6.9    
    Severity:  normal                   |   Resolution:         
    Keywords:  TF vs FD                 |     Testcase:         
Architecture:  Unknown                  |           Os:  Unknown
----------------------------------------+-----------------------------------
Comment (by claus):

 here is a slight variation that does not rely on a GHCi session to raise
 the issue
 {{{
 module Improve where

 class FD a b | a -> b
 instance CFD a b => FD a b

 class {- FD a b => -} CFD a b
 instance CFD Bool Char
 instance CFD Bool Bool

 f' :: FD Bool Bool => Bool
 f' = True

 g' :: FD Bool Char => Bool
 g' = False

 x = f'
 }}}

 {{{
 module Main where
 import Improve

 y = g'

 main = print (x,y)
 }}}

 GHC (6.9.20080217) accepts this, and the executable outputs
 `(True,False)`, even though the first component depends on `instance FD
 Bool Bool` while the second depends on `instance FD Bool Char`.

 Inlining `x` as `f'` is sufficient to raise the expected error message.

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