Shadowing in toIface* output

Simon Peyton Jones simon.peytonjones at gmail.com
Thu Apr 7 12:57:01 UTC 2022


>
> OK, I must be doing something wrong then. I am now looking at Tidy (not
> Prep) output, and I see Core like this:
>
>
>
>   showsPrec :: forall a. Show a => Int -> a -> ShowS
>
>   [GblId[ClassOp],
>
>    Arity=1,
>
>    Caf=NoCafRefs,
>
>    Str=<S!P(SL,A,A)>,
>
>    RULES: Built in rule for showsPrec: "Class op showsPrec"]
>
>   showsPrec
>
>     = \ (@a_a1G3) (v_B1 :: Show a_a1G3) ->
>
>         case v_B1 of v_B1 { C:Show v_B2 v_B3 v_B4 -> v_B2 }
>
>
>
> so if I’m reading this right, these vs are still shadowing.
>

That looks very odd.  If that gets serialised into a .hi file it won't work
at all.

If you can repro this with GHC, can you open a ticket for it.

It is true (as I discovered when spelunking as a result of this thread)
that Tidy does not tidy the "implicit bindings"  See this code in
GHC.Iface.Tidy:

      -- See Note [Injecting implicit bindings]
      all_tidy_binds = implicit_binds ++ tidy_binds'

I think we must be assuming (without documenting it) that implicit_binds
already satisfies the (undocumented) output invariants of Tidy.

See https://gitlab.haskell.org/ghc/ghc/-/issues/21333, where I suggest
improving this documentation, incl this implicit_binds assumption.  Zubin
may be doing this.

I can't account for what you are seeing though.

Simon

On Tue, 5 Apr 2022 at 05:08, Erdi, Gergo <Gergo.Erdi at sc.com> wrote:

> PUBLIC
>
>
>
> Ah, it seems Tidy doesn’t traverse the bindings that are created for
> typeclass methods. I guess the idea is that I should be able to recreate
> them from the typeclass declaration? So how do I know 1. which bindings
> exactly should be saved to reconstruct my original full desugared module
> and 2. How do I fill in these missing pieces during reconstruction?
>
>
>
>
>
>
>
> *From:* ghc-devs <ghc-devs-bounces at haskell.org> *On Behalf Of *Erdi,
> Gergo via ghc-devs
> *Sent:* Tuesday, April 5, 2022 11:09 AM
> *To:* Simon Peyton Jones <simon.peytonjones at gmail.com>; Gergo Érdi <
> gergo at erdi.hu>
> *Cc:* GHC Devs <ghc-devs at haskell.org>
> *Subject:* [External] RE: Re: Shadowing in toIface* output
>
>
>
> OK, I must be doing something wrong then. I am now looking at Tidy (not
> Prep) output, and I see Core like this:
>
>
>
>   showsPrec :: forall a. Show a => Int -> a -> ShowS
>
>   [GblId[ClassOp],
>
>    Arity=1,
>
>    Caf=NoCafRefs,
>
>    Str=<S!P(SL,A,A)>,
>
>    RULES: Built in rule for showsPrec: "Class op showsPrec"]
>
>   showsPrec
>
>     = \ (@a_a1G3) (v_B1 :: Show a_a1G3) ->
>
>         case v_B1 of v_B1 { C:Show v_B2 v_B3 v_B4 -> v_B2 }
>
>
>
> so if I’m reading this right, these vs are still shadowing.
>
>
>
> I am using tidyProgram on the output of hscSimplify, and then taking the
> cg_binds of its result. What else should I do to get tidy (heh) Tidy
> output?
>
>
>
>
>
> *From:* ghc-devs <ghc-devs-bounces at haskell.org> *On Behalf Of *Simon
> Peyton Jones
> *Sent:* Monday, April 4, 2022 4:28 PM
> *To:* Gergő Érdi <gergo at erdi.hu>
> *Cc:* GHC Devs <ghc-devs at haskell.org>
> *Subject:* [External] Re: Shadowing in toIface* output
>
>
>
> So does that mean Tidy produces unique `occNameFS`s, and then `Prep`
> breaks them?
>
>
>
> Tidy does not produce unique OccNames.  Rather, it avoids *shadowing*, so
> that if you delete all the uniques and print out the program (which is
> precisely what happens in an .hi file) you'll still get something sensible.
>
>
>
> I'm not sure whether or not Prep maintains this invariant.  There is no
> particular reason it should.  It might, but it is not (currently) a goal.
>
>
>
> Simon
>
>
>
> On Sat, 2 Apr 2022 at 04:35, Gergő Érdi <gergo at erdi.hu> wrote:
>
> So does that mean Tidy produces unique `occNameFS`s, and then `Prep`
> breaks them?
>
> On Fri, Apr 1, 2022 at 10:35 PM Josh Meredith
> <joshmeredith2008 at gmail.com> wrote:
> >
> > Hi,
> >
> > I encountered this when we used that for Plutus. I'll have to dig up the
> details, but IIRC `toIfaceExpr` expects GHC to have already tidied the
> output, which deals with this issue of overlapping variable names.
> >
> > Cheers,
> > Josh
> >
> > On Sat, 2 Apr 2022 at 01:26, ÉRDI Gergő <gergo at erdi.hu> wrote:
> >>
> >> Hi,
> >>
> >> I'm trying to save (Prep'd) Core bindings right next to the serialized
> >> `ModIface` (so basically `put_`ing them into the same bytestream, after
> the
> >> `ModIface`), and that's exactly what the functions in `GHC.CoreToIface`
> >> seem to be for, so I expected it to Just Work. However, I noticed that I
> >> very frequently get problems with shadowing. For example, Core that
> looks
> >> like `\v{u1} v{u2} -> v{u1}` would get translated to `\v v -> v`, which
> is
> >> disastrous since these locally bound `Var`s are represented as just
> their
> >> `getOccFS` (i.e. the `FastString` `"v"`).
> >>
> >> But this can't be right: if `toIfaceExpr` &c. would fail this blatently,
> >> then the unfoldings couldn't be saved & restored, which is something GHC
> >> itself does as part of normal `.hi` file handling. So clearly I must be
> >> doing something wrong.
> >>
> >> So I guess my question could be, what could be causing `toIfaceExpr` (a
> >> pure function!) to behave this way for my Cores? But then, if I look at
> >> the implementation of `toIface*`, I can see that it really doesn't do
> >> anything smarter than just storing `getOccFS` in the interface (no
> >> uniques in sight)-- so maybe my *real* question is, what is GHC itself
> >> doing so that it doesn't have this same problem?
> >>
> >> Thanks,
> >>         Gergo
> >> _______________________________________________
> >> ghc-devs mailing list
> >> ghc-devs at haskell.org
> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
> <https://clicktime.symantec.com/3BestP7qr2g6Y7xBfCxdDwr6xU?u=http%3A%2F%2Fmail.haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-devs>
> >
> > _______________________________________________
> > ghc-devs mailing list
> > ghc-devs at haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
> <https://clicktime.symantec.com/3BestP7qr2g6Y7xBfCxdDwr6xU?u=http%3A%2F%2Fmail.haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-devs>
> _______________________________________________
> ghc-devs mailing list
> ghc-devs at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
> <https://clicktime.symantec.com/3BestP7qr2g6Y7xBfCxdDwr6xU?u=http%3A%2F%2Fmail.haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-devs>
>
>
> This email and any attachments are confidential and may also be
> privileged. If you are not the intended recipient, please delete all copies
> and notify the sender immediately. You may wish to refer to the
> incorporation details of Standard Chartered PLC, Standard Chartered Bank
> and their subsidiaries at https: //www.sc.com/en/our-locations
>
> Where you have a Financial Markets relationship with Standard Chartered
> PLC, Standard Chartered Bank and their subsidiaries (the "Group"),
> information on the regulatory standards we adhere to and how it may affect
> you can be found in our Regulatory Compliance Statement at https: //
> www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //
> www.sc.com/rcs/fm
>
> Insofar as this communication is not sent by the Global Research team and
> contains any market commentary, the market commentary has been prepared by
> the sales and/or trading desk of Standard Chartered Bank or its affiliate.
> It is not and does not constitute research material, independent research,
> recommendation or financial advice. Any market commentary is for
> information purpose only and shall not be relied on for any other purpose
> and is subject to the relevant disclaimers available at https: //
> www.sc.com/en/regulatory-disclosures/#market-disclaimer.
>
> Insofar as this communication is sent by the Global Research team and
> contains any research materials prepared by members of the team, the
> research material is for information purpose only and shall not be relied
> on for any other purpose, and is subject to the relevant disclaimers
> available at https: //
> research.sc.com/research/api/application/static/terms-and-conditions.
>
> Insofar as this e-mail contains the term sheet for a proposed transaction,
> by responding affirmatively to this e-mail, you agree that you have
> understood the terms and conditions in the attached term sheet and
> evaluated the merits and risks of the transaction. We may at times also
> request you to sign the term sheet to acknowledge the same.
>
> Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/
> for important information with respect to derivative products.
>
> This email and any attachments are confidential and may also be
> privileged. If you are not the intended recipient, please delete all copies
> and notify the sender immediately. You may wish to refer to the
> incorporation details of Standard Chartered PLC, Standard Chartered Bank
> and their subsidiaries at https: //www.sc.com/en/our-locations
>
> Where you have a Financial Markets relationship with Standard Chartered
> PLC, Standard Chartered Bank and their subsidiaries (the "Group"),
> information on the regulatory standards we adhere to and how it may affect
> you can be found in our Regulatory Compliance Statement at https: //
> www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //
> www.sc.com/rcs/fm
>
> Insofar as this communication is not sent by the Global Research team and
> contains any market commentary, the market commentary has been prepared by
> the sales and/or trading desk of Standard Chartered Bank or its affiliate.
> It is not and does not constitute research material, independent research,
> recommendation or financial advice. Any market commentary is for
> information purpose only and shall not be relied on for any other purpose
> and is subject to the relevant disclaimers available at https: //
> www.sc.com/en/regulatory-disclosures/#market-disclaimer.
>
> Insofar as this communication is sent by the Global Research team and
> contains any research materials prepared by members of the team, the
> research material is for information purpose only and shall not be relied
> on for any other purpose, and is subject to the relevant disclaimers
> available at https: //
> research.sc.com/research/api/application/static/terms-and-conditions.
>
> Insofar as this e-mail contains the term sheet for a proposed transaction,
> by responding affirmatively to this e-mail, you agree that you have
> understood the terms and conditions in the attached term sheet and
> evaluated the merits and risks of the transaction. We may at times also
> request you to sign the term sheet to acknowledge the same.
>
> Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/
> for important information with respect to derivative products.
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20220407/35fd5224/attachment.html>


More information about the ghc-devs mailing list