#6161: Program with missing instance accepted by compiler, program <<loops>>
-----------------------------------------+----------------------------------
 Reporter:  wlguest                      |          Owner:          
     Type:  bug                          |         Status:  new     
 Priority:  normal                       |      Component:  Compiler
  Version:  7.4.1                        |       Keywords:  loop    
       Os:  Linux                        |   Architecture:  x86     
  Failure:  GHC accepts invalid program  |       Testcase:          
Blockedby:                               |       Blocking:          
  Related:                               |  
-----------------------------------------+----------------------------------
 The following program is accepted by the compiler even though (Fam Float)
 has no Super instance which is needed for Duper. testProg <<loops>> when
 run.

 Even with the Super (Fam Float) instance added, testProg continues to
 <<loop>> unless the Duper (Fam a) constraint on Foo a is replaced by a
 Super (Fam a) constraint.

 The problem seems to be an instance of
 [http://hackage.haskell.org/trac/ghc/ticket/5751 #5751], but I'm not
 really sure.

 {{{

 {-# LANGUAGE TypeFamilies, FlexibleContexts, FlexibleInstances #-}

 data family Fam  a

 data instance Fam Float = FamFloat Float

 class Super a where
   testSup :: a -> Float

 class Super a => Duper a where
   testDup :: a -> Float

 --class ( Super (Fam a) ) => Foo a where
 class Duper (Fam a) => Foo a where
   testFoo :: Fam a -> Float

 instance Foo a => Duper (Fam a) where
   testDup x = testFoo x + testSup x

 --instance Super (Fam Float) where
 --  testSup (FamFloat x) = x

 instance Foo Float where
   testFoo (FamFloat _) = 5.0

 testProg :: Float
 testProg = testDup (FamFloat 3.0)
 }}}

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

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to