#2307: Poor warning for conflicting functional dependencies
--------------------------+-------------------------------------------------
 Reporter:  NeilMitchell  |          Owner:             
     Type:  bug           |         Status:  new        
 Priority:  normal        |      Milestone:  6.10 branch
Component:  Compiler      |        Version:  6.8.2      
 Severity:  normal        |     Resolution:             
 Keywords:                |     Difficulty:  Unknown    
 Testcase:                |   Architecture:  Unknown    
       Os:  Unknown       |  
--------------------------+-------------------------------------------------
Changes (by igloo):

  * difficulty:  => Unknown
  * milestone:  => 6.10 branch

Comment:

 Thanks for the report! Here is a minimal testcase:
 {{{
 {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies,
              OverlappingInstances, UndecidableInstances,
 IncoherentInstances,
              FlexibleInstances #-}

 module Foo where

 class C a b c | a -> b, a -> c
 instance C Int (Maybe String) Float
 instance C Int (Maybe Bool)   Double
 }}}
 With the HEAD:
 {{{
 Proof_default.hs:8:0:
     Functional dependencies conflict between instance declarations:
       instance [incoherent] C Int (Maybe String) Float
         -- Defined at Proof_default.hs:8:0-34
       instance [incoherent] C Int (Maybe Bool) Double
         -- Defined at Proof_default.hs:9:0-35
       instance [incoherent] C Int (Maybe Bool) Double
         -- Defined at Proof_default.hs:9:0-35
 }}}
 Before just nubbing the instances, we should make sure that it's not a bug
 that it is finding the same one multiple times in the first place.

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