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

#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

#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 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 simonpj): I made a little progress with this, which I'll record. The bug is here in `RnEnv.lookupSubBndrOcc`. Usually this function looks up an unqualified `RdrName` and uses the parent info in the `GlobalRdrEnv` to disambiguate; and to check that the specified name is indeed a method of the parent class. But here are in the `Exact` `RdrName` case: {{{ lookupSubBndrOcc warn_if_deprec the_parent doc rdr_name | Just n <- isExact_maybe rdr_name -- This happens in derived code = do { n <- lookupExactOcc n ; return (Right n) } }}} In the example `'compare` refers precisely to `GHC.Classes.compare`, so we get an `Exact` `RdrName`. But that `compare` may not even be in scope, and may not be in the `GlobalRdrEnv`. We are omitting a check for the correct parent; hence the lack of error message. What to do? Either * If it's not in scope it must presumably be imported and hence in the `TypeEnv`. So we could look for parent-hood that way. A bit of a pain. * Or we could postpone the check altogether to the typechecker. I like this plan better because it works uniformly for local and imported things. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12387#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 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: | -------------------------------------+------------------------------------- Changes (by erikd): * cc: erikd (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12387#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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

#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): Well, perhaps the phrase "postponing" isn't quite accurate. It turns out that for associated type family instances, membership in a class is tested //twice//, once during renaming and once during typechecking. comment:3 shows an example of the latter, and this demonstrates the former: {{{#!hs {-# LANGUAGE TypeFamilies #-} module Foo where import GHC.Generics instance Eq () where type Rep () = Maybe }}} {{{ $ /opt/ghc/8.4.2/bin/ghc Bug.hs [1 of 1] Compiling Foo ( Bug.hs, Bug.o ) Bug.hs:7:8: error: ‘Rep’ is not a (visible) associated type of class ‘Eq’ | 7 | type Rep () = Maybe | ^^^ }}} So it might suffice to just check class membership for class methods additionally during typechecking, just like we do for associated type family instances. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12387#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12387: Template Haskell ignores class instance definitions with methods that don't belong to the class -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch 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): Phab:D4710 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D4710 Comment: I've implemented the idea from comment:4 in Phab:D4710. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12387#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12387: Template Haskell ignores class instance definitions with methods that don't
belong to the class
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: patch
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): Phab:D4710
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#12387: Template Haskell ignores class instance definitions with methods that don't belong to the class -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Template Haskell | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: th/T12387 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4710 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => closed * testcase: => th/T12387 * resolution: => fixed * milestone: => 8.6.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12387#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC