#2937: source file that compiled fine fails to recompile after touching it (yes,
another one)
-----------------------------+----------------------------------------------
Reporter:  rwbarton          |          Owner:                  
    Type:  bug               |         Status:  new             
Priority:  normal            |      Component:  Compiler        
 Version:  6.11              |       Severity:  normal          
Keywords:                    |       Testcase:                  
      Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
-----------------------------+----------------------------------------------
 I'm using the development snapshot `ghc-6.11.20090107` and ran into a bug
 very similar to #2888, but I think it is different because I could not
 reproduce that bug in my version.

 The setup is very similar: File `A.hs` contains
 {{{
 {-# LANGUAGE TypeFamilies #-}
 module A where
 class Foo a where
   data Bar a :: * -> *
 }}}
 and file `B.hs` contains
 {{{
 {-# LANGUAGE TypeFamilies #-}
 module B where
 import A
 instance Foo Int where
   data Bar Int x where
     Baz :: Bar Int String
 }}}
 Then:
 {{{
 rwbar...@functor:/tmp/a$ ghc --make B
 [1 of 2] Compiling A                ( A.hs, A.o )
 [2 of 2] Compiling B                ( B.hs, B.o )
 rwbar...@functor:/tmp/a$ touch B.hs
 rwbar...@functor:/tmp/a$ ghc --make B
 [2 of 2] Compiling B                ( B.hs, B.o )

 B.hs:8:2:
     Arguments that do not correspond to a class parameter must be
 variables
     Instead of a variable, found Int
     In the associated type instance for `Bar'
     In the instance declaration for `Foo Int'
 }}}

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