[GHC] #15800: Overlapping instances error with single instance

GHC ghc-devs at haskell.org
Wed Oct 24 21:37:43 UTC 2018


#15800: Overlapping instances error with single instance
-------------------------------------+-------------------------------------
           Reporter:  roland         |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.6.1
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  GHC rejects
  Unknown/Multiple                   |  valid program
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 {{{
 {-# LANGUAGE MultiParamTypeClasses, FlexibleContexts, FlexibleInstances
 #-}

 module Bug where

 class C a b

 instance C a Int

 x :: ()
 x = undefined :: C a Int => ()
 }}}

 {{{
 ghc -c Bug.hs

 Bug.hs:10:18: error:
     • Overlapping instances for C a0 Int
       Matching givens (or their superclasses):
         C a Int
           bound by an expression type signature:
                      forall a. C a Int => ()
           at Bug.hs:10:18-30
       Matching instances: instance C a Int -- Defined at Bug.hs:7:10
       (The choice depends on the instantiation of ‘a0’)
     • In the ambiguity check for an expression type signature
       To defer the ambiguity check to use sites, enable
 AllowAmbiguousTypes
       In an expression type signature: C a Int => ()
       In the expression: undefined :: C a Int => ()
    |
 10 | x = undefined :: C a Int => ()
    |                  ^^^^^^^^^^^^^
 }}}

 The "matching instances" bit of the error messages only lists a single
 instance. Doesn't it take at least two instances for something to overlap?

 Also, following the algorithm laid out in the user guide (section
 "Overlapping Instances"), it appears this program should be accepted.

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


More information about the ghc-tickets mailing list