
#12387: Template Haskell ignores class instance definitions with methods that don't belong to the class -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): To address my hunch in the original description, it turns out that the same issue does //not// affect associated type family instances. That is, if you try compiling this program: {{{#!hs {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-# OPTIONS_GHC -ddump-splices #-} module Main where import GHC.Generics import Language.Haskell.TH.Lib data Foo = Foo $(do d <- instanceD (cxt []) (conT ''Eq `appT` conT ''Foo) [tySynInstD ''Rep $ tySynEqn [conT ''Foo] (conT ''Maybe)] return [d]) main :: IO () main = print $ Foo == Foo }}} Then it will rightly complain about `Rep` not being an associated type of `Eq`: {{{ $ /opt/ghc/8.4.2/bin/ghc Bug.hs [1 of 1] Compiling Main ( Bug.hs, Bug.o ) Bug.hs:(11,3)-(13,15): Splicing declarations do d_a2Bz <- instanceD (cxt []) (conT ''Eq `appT` conT ''Foo) [tySynInstD ''Rep $ tySynEqn [conT ''Foo] (conT ''Maybe)] return [d_a2Bz] ======> instance Eq Foo where type Rep Foo = Maybe Bug.hs:11:3: error: • Class ‘Eq’ does not have an associated type ‘Rep’ • In the type instance declaration for ‘Rep’ In the instance declaration for ‘Eq Foo’ | 11 | $(do d <- instanceD (cxt []) (conT ''Eq `appT` conT ''Foo) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^... }}} That's because this particular validity check is performed [http://git.haskell.org/ghc.git/blob/5f15d53a98ad2f26465730d8c3463ccc58f6d94a... during typechecking], not renaming. This makes me believe that postponing the analogous check for class methods would also be wise (i.e., simonpj's second bullet point in comment:1). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12387#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler