[GHC] #15852: Bad axiom produced for polykinded data family

#15852: Bad axiom produced for polykinded data family -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.7 Keywords: TypeFamilies, | Operating System: Unknown/Multiple TypeInType | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- When I say {{{#!hs data family DF a (b :: k) data instance DF (Proxy c) :: Proxy j -> Type }}} with `-ddump-tc`, I get {{{ axiom Scratch.D:R:DFProxyProxy0 :: forall k1 k2 (c :: k1) (j :: k2) (a :: Proxy j). DF (Proxy c) a = Scratch.R:DFProxyProxy k1 k2 c j }}} This is bogus, because `a` should be on the RHS, too. It's not clear to me whether this is a pretty-printing bug or a real one. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15852 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15852: Bad axiom produced for polykinded data family -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.7 Resolution: | Keywords: TypeFamilies, | TypeInType 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 goldfire): My guess is that it is a pretty-printing bug, as if it were anything more serious would have been discovered by now. I would start by looking at `Coercion.pprCoAxiom`. Actually, better than just fixing this bug would be removing `Coercion.pprCoAxiom` in favor of the `IfaceAxiom` case of `pprIfaceDecl`. Unless it's not a pretty-printing bug. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15852#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15852: Bad axiom produced for polykinded data family -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.7 Resolution: | Keywords: TypeFamilies, | TypeInType 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): I think your hunch about it being a pretty-printing bug is right on the money. Moreover, I believe the `IfaceAxiom` case of `pprIfaceDecl` actually //is// the culprit, since: * `Coercion.pprCoAxiom` just calls `Coercion.ppr_co_ax_branch`, which already eta-expands the LHSes of data family instances. * `pprIfaceDecl` (for `IfaceAxiom`s) calls `pprAxBranch` which, judging from its current implementation: {{{#!hs pprAxBranch :: SDoc -> IfaceAxBranch -> SDoc pprAxBranch pp_tc (IfaceAxBranch { ifaxbTyVars = tvs , ifaxbCoVars = cvs , ifaxbLHS = pat_tys , ifaxbRHS = rhs , ifaxbIncomps = incomps }) = hang ppr_binders 2 (hang pp_lhs 2 (equals <+> ppr rhs)) $+$ nest 2 maybe_incomps where ppr_binders = sdocWithDynFlags $ \dflags -> ppWhen (gopt Opt_PrintExplicitForalls dflags) ppr_binders' ppr_binders' | null tvs && null cvs = empty | null cvs = brackets (pprWithCommas (pprIfaceTvBndr True) tvs) | otherwise = brackets (pprWithCommas (pprIfaceTvBndr True) tvs <> semi <+> pprWithCommas pprIfaceIdBndr cvs) pp_lhs = hang pp_tc 2 (pprParendIfaceAppArgs pat_tys) maybe_incomps = ppUnless (null incomps) $ parens $ text "incompatible indices:" <+> ppr incomps }}} Doesn't perform any sort of eta-expansion. In order to fix this, it looks like we'll need some equivalent of `etaExpandFamInstLHS`, but for iface data types. There's one major wrinkle that presents itself: how do we know that we're dealing with a data family instance in `pprAxBranch`? It's not obvious to me if that information is stored somewhere (I couldn't find anything in `IfaceTyCon`, for instance), and if not, where it //ought// to be stored. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15852#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15852: Bad axiom produced for polykinded data family -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.7 Resolution: | Keywords: TypeFamilies, | TypeInType 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): `IfaceTyConInfo` or `IfaceTyConSort` might be possible candidates for storing this information. Currently, these are defined as: {{{#!hs data IfaceTyConInfo -- Used to guide pretty-printing -- and to disambiguate D from 'D (they share a name) = IfaceTyConInfo { ifaceTyConIsPromoted :: IsPromoted , ifaceTyConSort :: IfaceTyConSort } -- | The various types of TyCons which have special, built-in syntax. data IfaceTyConSort = IfaceNormalTyCon -- ^ a regular tycon | IfaceTupleTyCon !Arity !TupleSort -- ^ e.g. @(a, b, c)@ or @(#a, b, c#)@. | IfaceSumTyCon !Arity -- ^ e.g. @(a | b | c)@ | IfaceEqualityTyCon -- ^ A heterogeneous equality TyCon }}} (The Haddocks for `IfaceTyConSort` are misleading, since //every// `IfaceTyCon` has one, not just those with special, built-in syntax. Regardless of how we fix this bug, we should change that documentation to reflect reality.) My vote would be to extend one of these data types with an extra field of type `IfaceTyConParent`, which would be sufficient to tell if a `TyCon` came from a data family instance or not. Then it would just be a matter of plumbing this information to `pprAxBranch` from its call sites. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15852#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15852: Bad axiom produced for polykinded data family -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.7 Resolution: | Keywords: TypeFamilies, | TypeInType 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 goldfire): My pointing to `pprCoAxiom` was from its use in `TcRnDriver.ppr_tycons`. Given the appearance of `"COERCION AXIOMS"` in `ppr_tycons`, I thought it was what produced the output I saw, which also contains that string. Maybe I missed a beat somewhere, but I think you may be barking up the wrong tree. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15852#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15852: Bad axiom produced for polykinded data family -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.7 Resolution: | Keywords: TypeFamilies, | TypeInType 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): Oh dear. Yes, I //was// barking up the wrong tree—thank you for setting me straight. Now that I dig closer into `ppr_co_axiom_branch` (which is the real culprit), I now understand what went wrong. When implementing `etaExpandFamInstLHS`, I left [http://git.haskell.org/ghc.git/blob/d30352add1da67dd0346613853cd423c7becbaeb... this comment]: {{{#!hs -- @Note [Eta reduction for data families]@ in "FamInstEnv". Because the -- right-hand side is where the eta-reduced variables are obtained from, it -- is not returned from this function (as there is never a need to modify it). }}} In retrospect, I have no idea what I was smoking when I wrote this comment, because it's completely wrong. The right-hand side //is// eta- reduced, and that's what we're seeing in `-ddump-tc`. (Moreover, we aren't obtaining the eta-reduced variables from the RHS at all. They're actually being taken from the `tyConTyVars` of the representation `TyCon`.) This suggests a straightforward fix: just eta expand the RHS as well, and return that from `etaExpandFamInstLHS` (or really, it just should be called `etaExpandFamInst`). I'll give that a shot. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15852#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15852: Bad axiom produced for polykinded data family -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.7 Resolution: | Keywords: TypeFamilies, | TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5328 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D5328 * milestone: => 8.8.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15852#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15852: Bad axiom produced for polykinded data family
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone: 8.8.1
Component: Compiler | Version: 8.7
Resolution: | Keywords: TypeFamilies,
| TypeInType
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D5328
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#15852: Bad axiom produced for polykinded data family -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.7 Resolution: fixed | Keywords: TypeFamilies, | TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5328 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15852#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC