[GHC] #8994: type checker could not deduce ambiguous instances

GHC ghc-devs at haskell.org
Mon Apr 14 05:53:19 UTC 2014


#8994: type checker could not deduce ambiguous instances
------------------------------------+-------------------------------------
       Reporter:  divip             |             Owner:
           Type:  bug               |            Status:  new
       Priority:  normal            |         Milestone:
      Component:  Compiler          |           Version:  7.8.2
       Keywords:                    |  Operating System:  Unknown/Multiple
   Architecture:  Unknown/Multiple  |   Type of failure:  None/Unknown
     Difficulty:  Unknown           |         Test Case:
     Blocked By:                    |          Blocking:
Related Tickets:                    |
------------------------------------+-------------------------------------
 GHC halts with a type error on the following program.
 If I comment out a seemingly unrelated part, it compiles though.

 Tested with GHC 7.8.2

 {{{#!haskell
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE TypeFamilies #-}

 class
   (F a ~ Int) =>  -- if this line is commented out, the program compiles
                  C a where
     type F a

     f :: b -> a

 run :: (forall a. C a => a) -> ()
 run _ = ()

 x = run (f 0)  -- type error: Could not deduce (Num b0) arising from the
 literal ‘0’ from the context (C a)
 }}}

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


More information about the ghc-tickets mailing list