[GHC] #11660: Remove Type pretty-printer in favor of IfaceType

#11660: Remove Type pretty-printer in favor of IfaceType -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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: -------------------------------------+------------------------------------- The `Type` pretty-printer has a fair amount of code in common with the pretty-printer for `IfaceType`. Moreover, both cases handle a number of special cases. With the introduction of `-fprint-explicit-runtime-reps` (Phab:D1961), there is now an inconsistency between these two. Let's resolve this inconsistency by eliminating the `Type` pretty-printer in favor of using the `IfaceType` printer. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11660 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11660: Remove Type pretty-printer in favor of IfaceType -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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 goldfire): Yes, this duplication has been annoying. I worry a bit in choosing to prioritize `IfaceType` over `Type` because `Type` can do more (that is, we have `typeKind` to hand). But perhaps it will enforce better pretty- printing hygiene to have fewer capabilities... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11660#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11660: Remove Type pretty-printer in favor of IfaceType -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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: | -------------------------------------+------------------------------------- Description changed by simonpj: @@ -4,1 +4,1 @@ - (Phab:D1961), there is now an inconsistency between these two. + (#11549, Phab:D1961), there is now an inconsistency between these two. New description: The `Type` pretty-printer has a fair amount of code in common with the pretty-printer for `IfaceType`. Moreover, both cases handle a number of special cases. With the introduction of `-fprint-explicit-runtime-reps` (#11549, Phab:D1961), there is now an inconsistency between these two. Let's resolve this inconsistency by eliminating the `Type` pretty-printer in favor of using the `IfaceType` printer. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11660#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11660: Remove Type pretty-printer in favor of IfaceType -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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 bgamari): I quickly looked at this; unfortunately more `SOURCE` imports of `TyCoRep` is almost inevitable under this change. Currently `IfaceType` must import `TyCoRep` due to the conversion functions. Now we'll also need the inverse import in order to implement the `Type` pretty-printer in terms of the `IfaceType` printer. I suppose we could move the `IfaceType` conversion functions to `Type`, although this seems like it would be an odd break with how the other iface constructs are handled. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11660#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11660: Remove Type pretty-printer in favor of IfaceType -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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): I'm sure we can deal with that. Eg in `TyCoRep` put just {{{ instance Outputable Type where ppr = pprType }}} and then yes `{-# SOURCE #-}` import `IfaceType` which defines `pprType` and others. Import `IfactType` into `Type` and re-export the pretty- printing functions. But before worrying much let's check that it works at all! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11660#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11660: Remove Type pretty-printer in favor of IfaceType -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.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): Phab:D2528 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D2528 * milestone: => 8.2.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11660#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11660: Remove Type pretty-printer in favor of IfaceType -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.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): Phab:D2528 Wiki Page: | -------------------------------------+------------------------------------- Changes (by johnleo): * cc: johnleo (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11660#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11660: Remove Type pretty-printer in favor of IfaceType -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.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): Phab:D2528 Wiki Page: | -------------------------------------+------------------------------------- Comment (by johnleo): Recognizing that this is a work in progress, if possible it would be nice to address some of the unicode issues noted in https://ghc.haskell.org/trac/ghc/ticket/12550 as part of this change. I'm happy to fix any remaining issues but will hold off until the patch is merged. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11660#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11660: Remove Type pretty-printer in favor of IfaceType -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.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): Phab:D2528 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Indeed, I'll try to fix those cases up as well. Thanks, John! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11660#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11660: Remove Type pretty-printer in favor of IfaceType -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12550, #12447, | Differential Rev(s): Phab:D2528 #11786, #11549 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * related: => #12550, #12447, #11786, #11549 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11660#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11660: Remove Type pretty-printer in favor of IfaceType -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: patch Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12550, #12447, | Differential Rev(s): Phab:D2528 #11786, #11549, #12024, #12697, | #12510 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * priority: normal => high * related: #12550, #12447, #11786, #11549 => #12550, #12447, #11786, #11549, #12024, #12697, #12510 Comment: Adding more related tickets... It'd be good to complete this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11660#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11660: Remove Type pretty-printer in favor of IfaceType -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: patch Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12550, #12447, | Differential Rev(s): Phab:D2528 #11786, #11549, #12024, #12697, | #12510 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Funny you say that; I actually dusted off the patch last night. It's very close to working; I just need to sort out some remaining printing inconsistencies and perhaps an import loop. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11660#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11660: Remove Type pretty-printer in favor of IfaceType -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: patch Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12550, #12447, | Differential Rev(s): Phab:D2528 #11786, #11549, #12024, #12697, | #12510 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): One thing slightly non-trivial issue that I've run into on this is that I seem to walk into holes while printing with the IfaceType printer which previously we avoided. For instance, `tcfail123` fails with, {{{ =====> tcfail123(normal) 61 of 82 [0, 51, 0] cd "./typecheck/should_fail/tcfail123.run" && "/opt/exp/ghc/ghc- ifacetype/inplace/test spaces/ghc-stage2" -c tcfail123.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -dno-debug-output Actual stderr output differs from expected: --- ./typecheck/should_fail/tcfail123.run/tcfail123.stderr.normalised 2016-10-14 09:36:08.560991222 -0400 +++ ./typecheck/should_fail/tcfail123.run/tcfail123.comp.stderr.normalised 2016-10-14 09:36:08.560991222 -0400 @@ -1,7 +1,14 @@ tcfail123.hs:11:9: Couldn't match a lifted type with an unlifted type - When matching the kind of ‘GHC.Prim.Int#’ - In the first argument of ‘f’, namely ‘3#’ - In the expression: f 3# - In an equation for ‘h’: h v = f 3# + When matching the kind of ‘GHC.Prim.Int#ghc: panic! (the 'impossible' happened) + (GHC version 8.1.20161014 for x86_64-unknown-linux): + toIfaceUnivCoProv hit a hole + {ax1} + Call stack: + CallStack (from HasCallStack): + prettyCurrentCallStack, called at compiler/utils/Outputable.hs:<line>:<column> in <package-id>:Outputable + callStackDoc, called at compiler/utils/Outputable.hs:<line>:<column> in <package-id>:Outputable + pprPanic, called at compiler/iface/IfaceType.hs:<line>:<column> in <package-id>:IfaceType + +Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} It's not entirely clear how best to deal with this, but it does make me worried that this idea may be on shaky ground. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11660#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11660: Remove Type pretty-printer in favor of IfaceType -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: patch Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12550, #12447, | Differential Rev(s): Phab:D2528 #11786, #11549, #12024, #12697, | #12510 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): The other issue is that rendering tuples, sums, and other built-in syntax things becomes a bit tricker. While previously we had access to the `TyCon` and could therefore simply use `isTupleTyCon_maybe` to identify tuples, now we only have the `IfaceTyCon` which can't easily be identified since it only gives us a `Name`. I can imagine a few (all fairly non-satisfactory) options here: * build a finite map of `TyCon` `Name`s that require special treatment. This is quite bad as it brings us back to the situation of building a map of a technically-infinite family of tycons * capture some analogue of `AlgTyConRhs` (which allows us to distinguish tuple `TyCon`s) in `IfaceTyCon` -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11660#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11660: Remove Type pretty-printer in favor of IfaceType -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: patch Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12550, #12447, | Differential Rev(s): Phab:D2528 #11786, #11549, #12024, #12697, | #12510 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Replying to [comment:13 bgamari]:
The other issue is that rendering tuples, sums, and other built-in syntax things becomes a bit tricker. While previously we had access to the `TyCon` and could therefore simply use `isTupleTyCon_maybe` to identify tuples, now we only have the `IfaceTyCon` which can't easily be identified since it only gives us a `Name`.
Use `IfaceTyConInfo`: it's precisely there to guide pretty-printing. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11660#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

One thing slightly non-trivial issue that I've run into on this is that I seem to walk into holes while printing with the IfaceType printer which
#11660: Remove Type pretty-printer in favor of IfaceType -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: patch Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12550, #12447, | Differential Rev(s): Phab:D2528 #11786, #11549, #12024, #12697, | #12510 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): previously we avoided. For instance, `tcfail123` fails The typechecker is trying to unify a lifted type with an unlifted one. So it produces {{{ [W] ax1 :: TYPE IntRep ~ TYPE LiftedPtrRep }}} which of course it can't solve. But rather than print that obscure message, it tries to print the offending type, which looks like {{{ Int# |> (hole{ax1}) }}} where `hole{ax1}` is the un-proven assertion above. The type printer suppresses the coercion (though you can see it with current GHC using `-fprint-explicit-coercions`). So for this and debugging reasons we do want to be able to print types with coercion holes in them, although they should never end up in interface files. So let's add `IfaceHoleProv` to `IfaceUnivCoProv`; and make `toIfaceType` use it. But serialisation can barf. Clearly this will need a Note, taken from this comment -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11660#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11660: Remove Type pretty-printer in favor of IfaceType -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: patch Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12550, #12447, | Differential Rev(s): Phab:D2528 #11786, #11549, #12024, #12697, | #12510 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): What's the inferred pattern type of `IsList` (#12697) {{{#!hs pattern IsList <- (eqTT TL -> Just HRefl) where IsList = TL }}} Is it {{{#!hs pattern List :: () => [] ~~ b => T b }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11660#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11660: Remove Type pretty-printer in favor of IfaceType -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: patch Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12550, #12447, | Differential Rev(s): Phab:D2528 #11786, #11549, #12024, #12697, | #12510 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): I've updated Phab:D2528 with the current state of my branch, which almost passes the testsuite. There 21 testsuite failures, nearly all of which are trivial changes in parentheses. In fact, I am quite tempted to accept the new output since it looks significantly more consistent than the previous output. However, there is one rather tricky testsuite failure that I'm a bit unsure how to handle. Namely, when we go to print an equality we look at the types involved to determine what operator to print. However, since we only have `IfaceType`s we can't see through type synonyms. This means that if we have an equality, {{{ (a :: GHC.Types.*) ~ (b :: GHC.Types.⋆) }}} we will render it as a heterogeneous equality (with a kind annotation on each operand) since the kinds look different (although in reality are synonyms). The solution for this that I am currently leaning towards is to represent equalities explicitly in `IfaceType` and ensure that they carry their "flavor" for pretty-printing purposes. **Failing tests**: `TEST="TypeSkolEscape T10632 T7939 T2431 ghci059 T7525 T7019a tcfail130 T9222 T8912 T8958 T12634 T2766 IPFail ContextStack2 T11252 ClassOperator tcfail041 tcrun045 tcfail211 T10858 T5837"` -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11660#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11660: Remove Type pretty-printer in favor of IfaceType -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: patch Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12550, #12447, | Differential Rev(s): Phab:D2528 #11786, #11549, #12024, #12697, | #12510 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I have no good advice to suggest for comment:17. Printing equality is currently an unpleasant compromise and would love a brand new approach. In particular, do not worry about wibbles against the status quo! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11660#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11660: Remove Type pretty-printer in favor of IfaceType
-------------------------------------+-------------------------------------
Reporter: bgamari | Owner:
Type: task | Status: patch
Priority: high | Milestone: 8.2.1
Component: Compiler | Version: 7.10.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #12550, #12447, | Differential Rev(s): Phab:D2528
#11786, #11549, #12024, #12697, |
#12510 |
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#11660: Remove Type pretty-printer in favor of IfaceType -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: closed Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12550, #12447, | Differential Rev(s): Phab:D2528 #11786, #11549, #12024, #12697, | #12510 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed Comment: It has been done. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11660#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC