#7395: DefaultSignatures conflict with default implementations
----------------------------------+-----------------------------------------
    Reporter:  cgaebel            |       Owner:                           
        Type:  bug                |      Status:  new                      
    Priority:  normal             |   Milestone:                           
   Component:  Compiler           |     Version:  7.6.1                    
    Keywords:  DefaultSignatures  |          Os:  Unknown/Multiple         
Architecture:  Unknown/Multiple   |     Failure:  GHC rejects valid program
  Difficulty:  Unknown            |    Testcase:  http://hpaste.org/77290  
   Blockedby:                     |    Blocking:                           
     Related:                     |  
----------------------------------+-----------------------------------------

Comment(by tibbe):

 A test case is linked under the "Test Case" attribute above. Here's the
 same test case, inlined:

 {{{
 {-# LANGUAGE DefaultSignatures, TypeOperators, FlexibleContexts,
 DeriveGeneric #-}
 module Main ( main ) where

 import GHC.Generics

 class Klass a where
     func :: a -> Int
     func _ = 0

     -- This implementation is incompatible with the one above. What should
     -- happen instead is that this instance is selected whenever
 availible,
     -- and the one above should be used as a fallback.
     default func :: (Generic a, GKlass (Rep a)) => a -> Int
     func = gfunc . from

 class GKlass f where
     gfunc :: f a -> Int

 instance GKlass U1 where
      gfunc _ = 0

 instance Klass a => GKlass (K1 i a) where
     gfunc = (+1) . func . unK1

 instance GKlass a => GKlass (M1 i c a) where
     gfunc = gfunc . unM1

 instance (GKlass a, GKlass b) => GKlass (a :*: b) where
     gfunc (x :*: y) = 1 + gfunc x + gfunc y

 instance (GKlass a, GKlass b) => GKlass (a :+: b) where
     gfunc (L1 x) = 1 + gfunc x
     gfunc (R1 x) = 1 + gfunc x

 instance Klass Int where
     func = id

 data A = A { unA :: Int }
     deriving Generic

 -- A has a Generic instance. Therefore, should use gfunc.
 instance Klass A

 data B = B { unB :: Int }

 -- B does not have a Generic instance. Therefore, should use func.
 instance Klass B

 main :: IO ()
 main = print (func $ A 3, func $ B 3)
 }}}

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