#824: overlapping instances and separate compilation
-----------------------------------+----------------------------------------
    Reporter:  [EMAIL PROTECTED]  |        Owner:         
        Type:  bug                 |       Status:  new    
    Priority:  normal              |    Milestone:         
   Component:  Compiler            |      Version:  6.5    
    Severity:  normal              |     Keywords:         
          Os:  Unknown             |   Difficulty:  Unknown
Architecture:  Unknown             |  
-----------------------------------+----------------------------------------
There's three issues here that all seem to revolve around overlapping
 instances
 and separate compilation.

 1) First, a documentation issue:

   It is not clear whether it makes sense to set '-fallow-overlapping-
 instances'
   with different values per compilation unit or this flag should be
 constant
   across the whole build.

 2) Secondly, I see that code that once worked fine in ghc 6.4 no longer
 compiles with ghc 6.5.  Note these files:

 Makefile:
 {{{
 main: Main.hs Indexed.o
         ghc -o main Main.hs Indexed.o

 Indexed.o : Indexed.hs
         ghc -fglasgow-exts -c $<                                  # Fails
         #ghc -fglasgow-exts -fallow-overlapping-instances -c $<   # Works
 }}}

 Main.hs:
 {{{
 {-# OPTIONS -fglasgow-exts -fallow-overlapping-instances #-}
 module Main where
 import Indexed

 instance Indexed [Int] Int where
    xs @@ i = xs !! fromIntegral i

 f :: [Int] -> Int
 f ys = ys @@ (1 :: Int)

 main = print (f [5..])
 }}}

 Indexed.hs:
 {{{
 module Indexed where

 import Data.List

 class Indexed f a where
     (@@) :: Integral i => f -> i -> a

 instance Indexed [a] a where
     (@@) = genericIndex
 }}}

 I get the following:
 {{{
 $ make clean; make
 rm *.hi *.o
 ghc -fglasgow-exts -c Indexed.hs                                  # Fails
 #ghc -fglasgow-exts -fallow-overlapping-instances -c Indexed.hs   # Works
 ghc -o main Main.hs Indexed.o

 Main.hs:9:7:
     Overlapping instances for Indexed [Int] Int
       arising from use of `@@' at Main.hs:9:7-22
     Matching instances:
       instance Indexed [a] a -- Imported from Indexed
       instance [overlap ok] Indexed [Int] Int -- Defined at Main.hs:5:0
     In the expression: ys @@ (1 :: Int)
     In the definition of `f': f ys = ys @@ (1 :: Int)
 make: *** [main] Error 1

 $ ghc --version
 The Glorious Glasgow Haskell Compilation System, version 6.5.20060526

 }}}
 Is this a bug or a 6.5 feature?  If it's a feature, then is there no way
 to have a single object file
 that can be used in one project that uses overlapping instances and
 another which doesn't?

 3) Thirdly, I've noticed that --make (in ghc and implicitly in ghci) seems
 broken here.  The recompilation checker doesn't seem to regenerate the .hi
 files when pragmas such as the following come and go in the file:
 {{{
   {-# OPTIONS -fallow-overlapping-instances -#}
 }}}
 And it appears that in 6.5 the .hi should change here.

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