[GHC] #12387: Template Haskell ignores class instance definitions with methods that don't belong to the class

GHC ghc-devs at haskell.org
Wed Jul 13 00:03:23 UTC 2016


#12387: Template Haskell ignores class instance definitions with methods that don't
belong to the class
-------------------------------------+-------------------------------------
           Reporter:  RyanGlScott    |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Template       |           Version:  8.0.1
  Haskell                            |
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  GHC accepts
  Unknown/Multiple                   |  invalid program
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 {{{#!hs
 {-# LANGUAGE TemplateHaskell #-}
 {-# OPTIONS_GHC -ddump-splices #-}
 module Main where

 import Language.Haskell.TH.Lib

 data Foo = Foo

 $(do d <- instanceD (cxt []) (conT ''Eq `appT` conT ''Foo)
             [funD 'compare [clause [] (normalB $ varE 'undefined) []]]
      return [d])

 main :: IO ()
 main = print $ Foo == Foo
 }}}

 {{{
 $ /opt/ghc/8.0.1/bin/runghc Bug.hs
 Bug.hs:(9,3)-(11,15): Splicing declarations
     do { d_a2hL <- instanceD
                      (cxt [])
                      (conT ''Eq `appT` conT ''Foo)
                      [funD 'compare [clause [] (normalB $ varE 'undefined)
 []]];
          return [d_a2hL] }
   ======>
     instance Eq Foo where
       compare = undefined

 Bug.hs:9:3: warning: [-Wmissing-methods]
     • No explicit implementation for
         either ‘==’ or ‘/=’
     • In the instance declaration for ‘Eq Foo’
 Bug.hs: stack overflow
 }}}

 `compare` obviously doesn't belong to `Eq`, yet GHC happily accepts an `Eq
 Foo` instance with a definition for `compare`! Worse yet, there's now
 neither a definition for `(==)` nor `(/=)`, so the default definition of
 `(==)` triggers an infinite loop, blowing the stack at runtime.

 I don't know how pervasive this bug is. That is, I'm not sure if you could
 also attach associated type family instances, pattern synonyms, etc. that
 don't belong to the class either.

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


More information about the ghc-tickets mailing list