[GHC] #16114: strange "instance .. => .. => .. where ..."

#16114: strange "instance .. => .. => .. where ..." -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 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: -------------------------------------+------------------------------------- I don't understand what's happening here: {{{ GHCi, version 8.6.3: http://www.haskell.org/ghc/ :? for help Prelude> data T a Prelude> instance Eq a => Eq a => Eq (T a) where (==) = undefined <interactive>:2:10: error: • Class ‘Eq’ does not have a method ‘==’ • In the instance declaration for ‘Eq (T a)’ }}} Is that even syntactically correct? (ghc-8.4.4 says "malformed instance") If so, then I'd assume that `A => B => C` means `A && B => C`, that is, `(A,B) => C` in this case, but it does not, since this works: {{{ instance (Eq a, Eq a)=> Eq (T a) where (==) = undefined }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16114 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16114: strange "instance .. => .. => .. where ..." -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: simonpj (added) Comment: Good catch. This seems to have been caused by commit 1c062b794bf71a329f65813ce7b72fe2bd3935f0 (`Simplify rnLHsInstType`), which removed this "`Malformed instance`" error message. Thoughts, simonpj? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16114#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16114: strange "instance .. => .. => .. where ..." -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Assuming that we don't wish to accept the original program, I think we can blame `rnClsInstDecl`. [https://gitlab.haskell.org/ghc/ghc/blob/master/compiler/rename/RnSource.hs#L... This] is the first part of that function: {{{#!hs rnClsInstDecl :: ClsInstDecl GhcPs -> RnM (ClsInstDecl GhcRn, FreeVars) rnClsInstDecl (ClsInstDecl { cid_poly_ty = inst_ty, cid_binds = mbinds , cid_sigs = uprags, cid_tyfam_insts = ats , cid_overlap_mode = oflag , cid_datafam_insts = adts }) = do { (inst_ty', inst_fvs) <- rnLHsInstType (text "an instance declaration") inst_ty ; let (ktv_names, _, head_ty') = splitLHsInstDeclTy inst_ty' ; let cls = case hsTyGetAppHead_maybe head_ty' of Nothing -> mkUnboundName (mkTcOccFS (fsLit "<class>")) Just (dL->L _ cls) -> cls -- rnLHsInstType has added an error message -- if hsTyGetAppHead_maybe fails }}} Since we're using `splitLHsInstDeclTy` to decompose `inst_ty`, if we feed it something sketchy like `Eq a => Eq a => Eq (T a)` as input, then `head_ty'` will be `Eq a => Eq (T a)` (which is not headed by a class, leading to havoc later on). Notice that that comment at the bottom assumes that `rnLHsInstType` throws an error message if `inst_ty` is malformed. But in commit 1c062b794bf71a329f65813ce7b72fe2bd3935f0, we have: {{{#!diff diff --git a/compiler/rename/RnTypes.hs b/compiler/rename/RnTypes.hs index 2305a04..b2dafb2 100644 (file) --- a/compiler/rename/RnTypes.hs +++ b/compiler/rename/RnTypes.hs @@ -326,20 +326,8 @@ rnImplicitBndrs bind_free_tvs doc rnLHsInstType :: SDoc -> LHsSigType GhcPs -> RnM (LHsSigType GhcRn, FreeVars) -- Rename the type in an instance or standalone deriving decl -- The 'doc_str' is "an instance declaration" or "a VECTORISE pragma" -rnLHsInstType doc_str inst_ty - | Just cls <- getLHsInstDeclClass_maybe inst_ty - , isTcOcc (rdrNameOcc (unLoc cls)) - -- The guards check that the instance type looks like - -- blah => C ty1 .. tyn - = do { let full_doc = doc_str <+> text "for" <+> quotes (ppr cls) - ; rnHsSigType (GenericCtx full_doc) inst_ty } - - | otherwise -- The instance is malformed, but we'd still like - -- to make progress rather than failing outright, so - -- we report more errors. So we rename it anyway. - = do { addErrAt (getLoc (hsSigType inst_ty)) $ - text "Malformed instance:" <+> ppr inst_ty - ; rnHsSigType (GenericCtx doc_str) inst_ty } +-- Do not try to decompose the inst_ty in case it is malformed +rnLHsInstType doc inst_ty = rnHsSigType (GenericCtx doc) inst_ty mk_implicit_bndrs :: [Name] -- implicitly bound -> a -- payload }}} Notice that `rnLHsInstType` no longer errors if given malformed input! So `rnClsInstDecl` charges on under the false pretense that `rnLHsInstType` succeeded. Perhaps the right thing to do would be to move the old validity check from `rnLHsInstType` to `rnClsInstDecl`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16114#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16114: strange "instance .. => .. => .. where ..." -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
Notice that rnLHsInstType no longer errors if given malformed input!
I can't for the life of me figure out WHY we made that change. There is only one call to `rnLHsInstType`, and it makes sense * For `rnLHsInstType` to error on a malformed instance * To use the same function `getLHsInstDeclClass_maybe` as is already used for this purpose in `RnNames.getLocalNonValBinders` We need to discover the class in the renamer so that we have the right "parent" for lookups. So can we just put the check back inot `rnLHsInstType`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16114#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16114: strange "instance .. => .. => .. where ..." -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Some history on this ticket: you committed 1c062b794bf71a329f65813ce7b72fe2bd3935f0 after I complained (in https://phabricator.haskell.org/D4383#122346) that `rnLHsInstType` was overly complicated due to the previous validity checking. You responded (in https://phabricator.haskell.org/D4383#122347) that it was safe to remove this validity check from `rnLHsInstType` altogether, as `checkValidInstance` apparently performs the same check. I'm not sure if that was true at one point in time, but it certainly doesn't appear to be true as of GHC 8.6. As you say, we could certainly put the check back into `rnLHsInstType`. But to be honest, that might cause an overall regression in error message quality, judging from the changes to error messages (generally for the better) in commit 1c062b794bf71a329f65813ce7b72fe2bd3935f0. Another option would be to re-investigate `checkValidInstance`, confirm whether or not it checks for instances of the form `Eq a => Eq a => Eq (T a)`, and if not, add a check for it and see if it fires before we get this `Class ‘Eq’ does not have a method ‘==’` nonsense. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16114#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16114: strange "instance .. => .. => .. where ..." -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
Another option would be to re-investigate checkValidInstance
I don't think so. What I missed before is that ''the renamer needs to know'' which class is involved so it has the right "parent" for lookups. You can see this in the call to `getLHsInstDeclClass_maybe` in `RnNames.getLocalNonValBinders`. And it is also the cause of this ticket, because the instance got past the renamer only by remaming `(==)` not to the `(==)` from the `Eq` class, but to a new unrelated top-level binder. Yikes. I think putting up with marginally less-cool errors may be a price we have to pay. Rather than "mal-formed" we could say {{{ Class instances must be of the form context => C ty1 .. tyn where C is a class }}} or something more positive than "mal-formed". -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16114#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16114: strange "instance .. => .. => .. where ..." -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Alright, if you're happy with that error message, then so am I. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16114#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16114: strange "instance .. => .. => .. where ..." -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | https://gitlab.haskell.org/ghc/ghc/merge_requests/92 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => https://gitlab.haskell.org/ghc/ghc/merge_requests/92 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16114#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16114: strange "instance .. => .. => .. where ..." -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.6.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | rename/should_fail/T16114 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | https://gitlab.haskell.org/ghc/ghc/merge_requests/92 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => closed * testcase: => rename/should_fail/T16114 * resolution: => fixed * milestone: => 8.8.1 Comment: Landed in https://gitlab.haskell.org/ghc/ghc/commit/83a22066fbe136e4a984e8c90c1d3fd72b.... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16114#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16114: strange "instance .. => .. => .. where ..."
-------------------------------------+-------------------------------------
Reporter: j.waldmann | Owner: (none)
Type: bug | Status: closed
Priority: normal | Milestone: 8.8.1
Component: Compiler | Version: 8.6.3
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
| rename/should_fail/T16114
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: | https://gitlab.haskell.org/ghc/ghc/merge_requests/92
-------------------------------------+-------------------------------------
Comment (by Ryan Scott
participants (1)
-
GHC