[GHC] #15863: Splcing a type class method selects the wrong instance

GHC ghc-devs at haskell.org
Mon Nov 5 15:15:33 UTC 2018


#15863: Splcing a type class method selects the wrong instance
-------------------------------------+-------------------------------------
           Reporter:  mpickering     |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.6.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:
-------------------------------------+-------------------------------------
 Consider these 4 modules as concocted by Csongor.

 The wrong instance is selected when you splice in `B.me` into `D`.

 https://gist.github.com/mpickering/959a95525647802414ab50e8e6ed490c

 {{{
 module A where

 class C a where
   foo :: a -> String

 instance C Int where
 foo _ = "int"
 }}}

 {{{
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE NoMonomorphismRestriction #-}
 module B where

 import A

 import Language.Haskell.TH

 instance C a => C [a] where
   foo _ = "list"

 me :: Q (TExp ([Int] -> String))
 me = [|| foo ||]
 }}}

 {{{
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE NoMonomorphismRestriction #-}
 module C where

 import A

 import Language.Haskell.TH

 instance {-# OVERLAPPING #-} C [Int] where
 foo _ = "list2"
 }}}

 {{{
 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE NoMonomorphismRestriction #-}
 module D where

 import A
 import B
 import C

 main2 = $$(me) [1 :: Int]
 }}}

 {{{
 >>> main2
 "list2"
 }}}


 In `B`, `B.me` is created by quoting `foo`. `B.me :: Q (TExp ([Int] ->
 String))` so in order to type check this quote we need to solve the
 instance `C [Int]` which we should do by using the instance defined in `B`
 (and `A`).

 In module `C` we define a different overlapping instance (note that this
 could be in a completely different library not under our control).

 When we then splice `B.me` into `D`, the instance from `C` is used and can
 be witnessed by printing `main2` which shows `"list2"` rather than
 `"list"` as expected.

 This is a symptom of the fact that the renamed rather than the typechecked
 AST is serialised I think.

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


More information about the ghc-tickets mailing list