#5316: ghc rejects a program at first but will accept it if one insists
---------------------------------+------------------------------------------
    Reporter:  jcpetruzza        |       Owner:                           
        Type:  bug               |      Status:  new                      
    Priority:  normal            |   Component:  Compiler                 
     Version:  7.0.4             |    Keywords:                           
    Testcase:                    |   Blockedby:                           
          Os:  Unknown/Multiple  |    Blocking:                           
Architecture:  Unknown/Multiple  |     Failure:  GHC rejects valid program
---------------------------------+------------------------------------------
 Consider these two modules (boiled down example from the checkers
 package):

 {{{
 {-# LANGUAGE ScopedTypeVariables, FlexibleContexts #-}

 module T1

 where

 import Test.QuickCheck
 import Text.Show.Functions ()


 f :: forall m a b.  ( Arbitrary (a->b) ) => m (a,b) -> Property
 f = const $ property (undefined :: (a->b) -> Bool)
 }}}

 {{{
 module T2  where

 import Control.Concurrent

 g = threadDelay maxBound
 }}}

 I see the following interaction:

 {{{
 $ rm *hi *.o
 $ ghc --make -c -O  T1 T2
 [1 of 2] Compiling T2               ( T2.hs, T2.o )
 [2 of 2] Compiling T1               ( T1.hs, T1.o )

 T1.hs:12:13:
     Overlapping instances for Show (a -> b)
       arising from a use of `property'
     Matching instances:
       instance Show (a -> b) -- Defined in Text.Show.Functions
       instance Show base:System.Event.Manager.IOCallback
         -- Defined in base:System.Event.Manager
     (The choice depends on the instantiation of `a, b'
      To pick the first instance above, use -XIncoherentInstances
      when compiling the other instance declarations)
     In the second argument of `($)', namely
       `property (undefined :: (a -> b) -> Bool)'
     In the expression: const $ property (undefined :: (a -> b) -> Bool)
     In an equation for `f':
         f = const $ property (undefined :: (a -> b) -> Bool)
 $ ghc --make -c -O  T1 T2
 [2 of 2] Compiling T1               ( T1.hs, T1.o )
 $ ghc --make -c -O  T1 T2
 $ ls
 T1.hi T1.hs T1.o  T2.hi T2.hs T2.o
 }}}

 I see this consistent behaviour in versions 7.0.{1,2,3,4} but not with
 6.12.1

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