[GHC] #13284: Incoherent instance solving is over-eager

GHC ghc-devs at haskell.org
Thu Feb 16 00:56:52 UTC 2017


#13284: Incoherent instance solving is over-eager
-------------------------------------+-------------------------------------
           Reporter:  simonpj        |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.0.1
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 danilo2 writes (originally in #9432 comment:1)
 {{{
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE FunctionalDependencies #-}
 {-# LANGUAGE UndecidableInstances #-}
 {-# LANGUAGE OverlappingInstances #-}
 {-# LANGUAGE IncoherentInstances #-} -- the flag is niot needed by the
 example

 module Main where
 import Data.Typeable


 class CTest a b | a -> b where
     cTest :: a -> b

 -- this instance is choosen even if more specific is available!
 instance out~a => CTest a out where
     cTest = id

 instance CTest Int String where
     cTest _ = "test"


 main = do
     print $ typeOf $ cTest (5::Int)
 }}}
 The instance `CTest a out` even if more specific `(CTest Int String)` is
 in scope, which just breaks how `OverlappingInstances` work. If we disable
 the `IncoherentInstances` flag, the right one is selected.

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


More information about the ghc-tickets mailing list