Template Haskell ignores class instance definitions with methods that don't belong to the class
{-# 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.
Trac metadata
Trac field | Value |
---|---|
Version | 8.0.1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Template Haskell |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |