From gergo at erdi.hu Fri Apr 1 08:04:54 2022 From: gergo at erdi.hu (=?ISO-8859-2?Q?=C9RDI_Gerg=F5?=) Date: Fri, 1 Apr 2022 16:04:54 +0800 (+08) Subject: Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings Message-ID: Hi, I'm CC-ing the Clash mailing list because I believe they should have encountered the same problem (and perhaps have found a solution to it already!). I'm trying to use `.hi` files compiled with `ExposeAllUnfoldings` set to reconstruct full Core bindings for further processing. By and large, this works, but I get tripped up on identifiers whose unfolding is only given as `OtherCon []`. It is unclear to me what is causing this -- some of them are recursive bindings while others are not. The problem, of course, is that if all I know about an identifier is that it is `OtherCon []`, that doesn't allow me to restore its definition. So is there a way to tell GHC to put "full" unfoldings everywhere in `ExposeAllUnfoldings` mode? Thanks, Gergo From matthewtpickering at gmail.com Fri Apr 1 12:27:19 2022 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Fri, 1 Apr 2022 13:27:19 +0100 Subject: Windows CI instability Message-ID: Hi all, Currently the windows CI issue is experiencing high amounts of instability so if your patch fails for this reason then don't worry. We are attempting to fix it. Cheers, Matt From christiaan.baaij at gmail.com Fri Apr 1 12:39:25 2022 From: christiaan.baaij at gmail.com (Christiaan Baaij) Date: Fri, 1 Apr 2022 14:39:25 +0200 Subject: [clash-language] Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings In-Reply-To: References: Message-ID: So if I understand correctly, OtherCon is only created here: https://gitlab.haskell.org/ghc/ghc/-/blob/a952dd80d40bf6b67194a44ff71d7bf75957d29e/compiler/GHC/Core/Opt/Simplify.hs#L3071-3077 simplAlt env _ imposs_deflt_cons case_bndr' cont' (Alt DEFAULT bndrs rhs) = assert (null bndrs) $ do { let env' = addBinderUnfolding env case_bndr' (mkOtherCon imposs_deflt_cons) -- Record the constructors that the case-binder *can't* be. ; rhs' <- simplExprC env' rhs cont' ; return (Alt DEFAULT [] rhs') } What you should know is that in Core case-expressions are actually more like: case scrut as b of alts where `b` binds the evaluated result of `scrut. So if I am to understand the `simplAlt` code correctly, `case_bndr'` is the binder for the evaluated result of `scrut`. And what is recorded in the unfolding is that once we get to the DEFAULT pattern, we know that `case_bndr'` cannot be the constructors in `imposs_deflt_cons` (probably the constructor matched by the other alternatives). Now... there's also a FloutOut pass, which might have floated that `case_bndr'` to the TopLevel. And I think that is what you're seeing, and I think you can simply ignore them. Also... another thing that you should know is that -fexpose-all-unfoldings doesn't actually expose *all* unfoldings. Bottoming bindings are never exposed. That's why in the Clash compiler we have the following code when loading core-expressions from .hi files https://github.com/clash-lang/clash-compiler/blob/cb93b418865e244da50e1d2bc85fbc01bf761f3f/clash-ghc/src-ghc/Clash/GHC/LoadInterfaceFiles.hs#L473-L481 loadExprFromTyThing :: CoreSyn.CoreBndr -> GHC.TyThing -> Maybe CoreSyn.CoreExpr loadExprFromTyThing bndr tyThing = case tyThing of GHC.AnId _id | Var.isId _id -> let _idInfo = Var.idInfo _id unfolding = IdInfo.unfoldingInfo _idInfo in case unfolding of CoreSyn.CoreUnfolding {} -> Just (CoreSyn.unfoldingTemplate unfolding) CoreSyn.DFunUnfolding dfbndrs dc es -> Just (MkCore.mkCoreLams dfbndrs (MkCore.mkCoreConApps dc es)) CoreSyn.NoUnfolding #if MIN_VERSION_ghc(9,0,0) | Demand.isDeadEndSig $ IdInfo.strictnessInfo _idInfo #else | Demand.isBottomingSig $ IdInfo.strictnessInfo _idInfo #endif -> do let noUnfoldingErr = "no_unfolding " ++ showPpr unsafeGlobalDynFlags bndr Just (MkCore.mkAbsentErrorApp (Var.varType _id) noUnfoldingErr) _ -> Nothing _ -> Nothing i.e. when we encounter a NoUnfolding with a bottoming demand signature, we conjure an absentError out of thin air. On Fri, 1 Apr 2022 at 10:05, ÉRDI Gergő wrote: > Hi, > > I'm CC-ing the Clash mailing list because I believe they should have > encountered the same problem (and perhaps have found a solution to it > already!). > > I'm trying to use `.hi` files compiled with `ExposeAllUnfoldings` set to > reconstruct full Core bindings for further processing. By and large, this > works, but I get tripped up on identifiers whose unfolding is only given > as `OtherCon []`. It is unclear to me what is causing this -- some of them > are recursive bindings while others are not. > > The problem, of course, is that if all I know about an identifier is that > it is `OtherCon []`, that doesn't allow me to restore its definition. So > is there a way to tell GHC to put "full" unfoldings everywhere in > `ExposeAllUnfoldings` mode? > > Thanks, > Gergo > > -- > You received this message because you are subscribed to the Google Groups > "Clash - Hardware Description Language" group. > To unsubscribe from this group and stop receiving emails from it, send an > email to clash-language+unsubscribe at googlegroups.com. > To view this discussion on the web visit > https://groups.google.com/d/msgid/clash-language/alpine.DEB.2.22.394.2204011556570.3183073%40galaxy > . > -------------- next part -------------- An HTML attachment was scrubbed... URL: From gergo at erdi.hu Fri Apr 1 13:37:08 2022 From: gergo at erdi.hu (=?ISO-8859-2?Q?=C9RDI_Gerg=F5?=) Date: Fri, 1 Apr 2022 21:37:08 +0800 (+08) Subject: [clash-language] Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings In-Reply-To: References: Message-ID: This doesn't quite match my experience. For example, the following toplevel definition gets an `OtherCon []` unfolding: nonEmptySubsequences :: [a] -> [[a]] nonEmptySubsequences [] = [] nonEmptySubsequences (x:xs) = [x] : foldr f [] (nonEmptySubsequences xs) where f ys r = ys : (x:ys) : r as can be seen with: $ ghc -fforce-recomp -fexpose-all-unfoldings -ddump-prep -dsuppress-uniques A.hs -- RHS size: {terms: 37, types: 55, coercions: 0, joins: 0/6} A.nonEmptySubsequences [Occ=LoopBreaker] :: forall a. [a] -> [[a]] [GblId, Arity=1, Unf=OtherCon []] A.nonEmptySubsequences = \ (@ a) (ds [Occ=Once1!] :: [a]) -> ... So this is not a lifted `case`-bound variable, but a bonafide user-originating toplevel definition. And its value also isn't bottom. On Fri, 1 Apr 2022, Christiaan Baaij wrote: > So if I understand correctly, OtherCon is only created here:https://gitlab.haskell.org/ghc/ghc/-/blob/a952dd80d40bf6b67194a44ff71d7bf75957d29e/co > mpiler/GHC/Core/Opt/Simplify.hs#L3071-3077 > > simplAlt env _ imposs_deflt_cons case_bndr' cont' (Alt DEFAULT bndrs rhs) >   = assert (null bndrs) $ >     do  { let env' = addBinderUnfolding env case_bndr' >                                         (mkOtherCon imposs_deflt_cons) >                 -- Record the constructors that the case-binder *can't* be. >         ; rhs' <- simplExprC env' rhs cont' >         ; return (Alt DEFAULT [] rhs') } > > What you should know is that in Core case-expressions are actually more like: > > case scrut as b of alts > > where `b` binds the evaluated result of `scrut. > > So if I am to understand the `simplAlt` code correctly, `case_bndr'` is the binder for > the evaluated result of `scrut`. > And what is recorded in the unfolding is that once we get to the DEFAULT pattern, we > know that `case_bndr'` cannot be the constructors in `imposs_deflt_cons` (probably the > constructor matched by the other alternatives). > > Now... there's also a FloutOut pass, which might have floated that `case_bndr'` to the > TopLevel. > And I think that is what you're seeing, and I think you can simply ignore them. > > > Also... another thing that you should know is that -fexpose-all-unfoldings doesn't > actually expose *all* unfoldings. > Bottoming bindings are never exposed. > That's why in the Clash compiler we have the following code when loading > core-expressions from .hi fileshttps://github.com/clash-lang/clash-compiler/blob/cb93b418865e244da50e1d2bc85fbc01bf7 > 61f3f/clash-ghc/src-ghc/Clash/GHC/LoadInterfaceFiles.hs#L473-L481 > > loadExprFromTyThing :: CoreSyn.CoreBndr -> GHC.TyThing -> Maybe CoreSyn.CoreExpr > loadExprFromTyThing bndr tyThing = case tyThing of >   GHC.AnId _id | Var.isId _id -> >     let _idInfo    = Var.idInfo _id >         unfolding  = IdInfo.unfoldingInfo _idInfo >     in case unfolding of >       CoreSyn.CoreUnfolding {} -> >         Just (CoreSyn.unfoldingTemplate unfolding) >       CoreSyn.DFunUnfolding dfbndrs dc es -> >         Just (MkCore.mkCoreLams dfbndrs (MkCore.mkCoreConApps dc es)) >       CoreSyn.NoUnfolding > #if MIN_VERSION_ghc(9,0,0) >         | Demand.isDeadEndSig $ IdInfo.strictnessInfo _idInfo > #else >         | Demand.isBottomingSig $ IdInfo.strictnessInfo _idInfo > #endif >         -> do >           let noUnfoldingErr = "no_unfolding " ++ showPpr unsafeGlobalDynFlags bndr >           Just (MkCore.mkAbsentErrorApp (Var.varType _id) noUnfoldingErr) >       _ -> Nothing >   _ -> Nothing > > i.e. when we encounter a NoUnfolding with a bottoming demand signature, we conjure an > absentError out of thin air. > > > On Fri, 1 Apr 2022 at 10:05, ÉRDI Gergő wrote: > Hi, > > I'm CC-ing the Clash mailing list because I believe they should have > encountered the same problem (and perhaps have found a solution to it > already!). > > I'm trying to use `.hi` files compiled with `ExposeAllUnfoldings` set to > reconstruct full Core bindings for further processing. By and large, this > works, but I get tripped up on identifiers whose unfolding is only given > as `OtherCon []`. It is unclear to me what is causing this -- some of them > are recursive bindings while others are not. > > The problem, of course, is that if all I know about an identifier is that > it is `OtherCon []`, that doesn't allow me to restore its definition. So > is there a way to tell GHC to put "full" unfoldings everywhere in > `ExposeAllUnfoldings` mode? > > Thanks, >         Gergo > > -- > You received this message because you are subscribed to the Google Groups > "Clash - Hardware Description Language" group. > To unsubscribe from this group and stop receiving emails from it, send an > email to clash-language+unsubscribe at googlegroups.com. > To view this discussion on the web visithttps://groups.google.com/d/msgid/clash-language/alpine.DEB.2.22.394.2204011556570.31 > 83073%40galaxy. > > > -- .--= ULLA! =-----------------. \ http://gergo.erdi.hu \ `---= gergo at erdi.hu =-------' From sylvain at haskus.fr Fri Apr 1 13:56:05 2022 From: sylvain at haskus.fr (Sylvain Henry) Date: Fri, 1 Apr 2022 15:56:05 +0200 Subject: [clash-language] Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings In-Reply-To: References: Message-ID: The unfolding is present if you add `-fno-omit-interface-pragmas` and dump with `-ddump-simpl`. CorePrep drops unfoldings, see Note [Drop unfoldings and rules] in GHC.CoreToStg.Prep. The logic for unfolding exposition by Tidy is now in: https://gitlab.haskell.org/ghc/ghc/-/blob/a952dd80d40bf6b67194a44ff71d7bf75957d29e/compiler/GHC/Driver/Config/Tidy.hs#L40 If you use the GHC API you can now invoke Tidy with different TidyOpts. On 01/04/2022 15:37, ÉRDI Gergő wrote: > This doesn't quite match my experience. For example, the following > toplevel definition gets an `OtherCon []` unfolding: > > nonEmptySubsequences :: [a] -> [[a]] > nonEmptySubsequences [] = [] > nonEmptySubsequences (x:xs) = [x] : foldr f [] (nonEmptySubsequences xs) >   where >     f ys r = ys : (x:ys) : r > > as can be seen with: > > $ ghc -fforce-recomp -fexpose-all-unfoldings -ddump-prep > -dsuppress-uniques A.hs > > -- RHS size: {terms: 37, types: 55, coercions: 0, joins: 0/6} > A.nonEmptySubsequences [Occ=LoopBreaker] :: forall a. [a] -> [[a]] > [GblId, Arity=1, Unf=OtherCon []] > A.nonEmptySubsequences >   = \ (@ a) (ds [Occ=Once1!] :: [a]) -> ... > > > So this is not a lifted `case`-bound variable, but a bonafide > user-originating toplevel definition. And its value also isn't bottom. > > > On Fri, 1 Apr 2022, Christiaan Baaij wrote: > >> So if I understand correctly, OtherCon is only created >> here:https://gitlab.haskell.org/ghc/ghc/-/blob/a952dd80d40bf6b67194a44ff71d7bf75957d29e/co >> mpiler/GHC/Core/Opt/Simplify.hs#L3071-3077 >> >> simplAlt env _ imposs_deflt_cons case_bndr' cont' (Alt DEFAULT bndrs >> rhs) >>   = assert (null bndrs) $ >>     do  { let env' = addBinderUnfolding env case_bndr' >>                                         (mkOtherCon imposs_deflt_cons) >>                 -- Record the constructors that the case-binder >> *can't* be. >>         ; rhs' <- simplExprC env' rhs cont' >>         ; return (Alt DEFAULT [] rhs') } >> >> What you should know is that in Core case-expressions are actually >> more like: >> >> case scrut as b of alts >> >> where `b` binds the evaluated result of `scrut. >> >> So if I am to understand the `simplAlt` code correctly, `case_bndr'` >> is the binder for >> the evaluated result of `scrut`. >> And what is recorded in the unfolding is that once we get to the >> DEFAULT pattern, we >> know that `case_bndr'` cannot be the constructors in >> `imposs_deflt_cons` (probably the >> constructor matched by the other alternatives). >> >> Now... there's also a FloutOut pass, which might have floated that >> `case_bndr'` to the >> TopLevel. >> And I think that is what you're seeing, and I think you can simply >> ignore them. >> >> >> Also... another thing that you should know is that >> -fexpose-all-unfoldings doesn't >> actually expose *all* unfoldings. >> Bottoming bindings are never exposed. >> That's why in the Clash compiler we have the following code when loading >> core-expressions from .hi >> fileshttps://github.com/clash-lang/clash-compiler/blob/cb93b418865e244da50e1d2bc85fbc01bf7 >> 61f3f/clash-ghc/src-ghc/Clash/GHC/LoadInterfaceFiles.hs#L473-L481 >> >> loadExprFromTyThing :: CoreSyn.CoreBndr -> GHC.TyThing -> Maybe >> CoreSyn.CoreExpr >> loadExprFromTyThing bndr tyThing = case tyThing of >>   GHC.AnId _id | Var.isId _id -> >>     let _idInfo    = Var.idInfo _id >>         unfolding  = IdInfo.unfoldingInfo _idInfo >>     in case unfolding of >>       CoreSyn.CoreUnfolding {} -> >>         Just (CoreSyn.unfoldingTemplate unfolding) >>       CoreSyn.DFunUnfolding dfbndrs dc es -> >>         Just (MkCore.mkCoreLams dfbndrs (MkCore.mkCoreConApps dc es)) >>       CoreSyn.NoUnfolding >> #if MIN_VERSION_ghc(9,0,0) >>         | Demand.isDeadEndSig $ IdInfo.strictnessInfo _idInfo >> #else >>         | Demand.isBottomingSig $ IdInfo.strictnessInfo _idInfo >> #endif >>         -> do >>           let noUnfoldingErr = "no_unfolding " ++ showPpr >> unsafeGlobalDynFlags bndr >>           Just (MkCore.mkAbsentErrorApp (Var.varType _id) >> noUnfoldingErr) >>       _ -> Nothing >>   _ -> Nothing >> >> i.e. when we encounter a NoUnfolding with a bottoming demand >> signature, we conjure an >> absentError out of thin air. >> >> >> On Fri, 1 Apr 2022 at 10:05, ÉRDI Gergő wrote: >>       Hi, >> >>       I'm CC-ing the Clash mailing list because I believe they should >> have >>       encountered the same problem (and perhaps have found a solution >> to it >>       already!). >> >>       I'm trying to use `.hi` files compiled with >> `ExposeAllUnfoldings` set to >>       reconstruct full Core bindings for further processing. By and >> large, this >>       works, but I get tripped up on identifiers whose unfolding is >> only given >>       as `OtherCon []`. It is unclear to me what is causing this -- >> some of them >>       are recursive bindings while others are not. >> >>       The problem, of course, is that if all I know about an >> identifier is that >>       it is `OtherCon []`, that doesn't allow me to restore its >> definition. So >>       is there a way to tell GHC to put "full" unfoldings everywhere in >>       `ExposeAllUnfoldings` mode? >> >>       Thanks, >>               Gergo >> >>       -- >>       You received this message because you are subscribed to the >> Google Groups >>       "Clash - Hardware Description Language" group. >>       To unsubscribe from this group and stop receiving emails from >> it, send an >>       email to clash-language+unsubscribe at googlegroups.com. >>       To view this discussion on the web >> visithttps://groups.google.com/d/msgid/clash-language/alpine.DEB.2.22.394.2204011556570.31 >>       83073%40galaxy. >> >> >> > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From gergo at erdi.hu Fri Apr 1 14:09:18 2022 From: gergo at erdi.hu (=?ISO-8859-2?Q?=C9RDI_Gerg=F5?=) Date: Fri, 1 Apr 2022 22:09:18 +0800 (+08) Subject: [clash-language] Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings In-Reply-To: References: Message-ID: On Fri, 1 Apr 2022, Sylvain Henry wrote: > The unfolding is present if you add `-fno-omit-interface-pragmas` and dump > with `-ddump-simpl`. CorePrep drops unfoldings, see Note [Drop unfoldings and > rules] in GHC.CoreToStg.Prep. Thanks, I forgot to mention that I am already using `NoOmitInterfacePragmas`, but I wasn't aware that the Prep stage drops unfoldings (and in fact, I am using Prep output in my real program). But if that's the case, how come most of my Ids still have unfoldings, and only a couple of them are missing? From gergo at erdi.hu Fri Apr 1 14:25:42 2022 From: gergo at erdi.hu (=?ISO-8859-2?Q?=C9RDI_Gerg=F5?=) Date: Fri, 1 Apr 2022 22:25:42 +0800 (+08) Subject: Shadowing in toIface* output Message-ID: 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 From joshmeredith2008 at gmail.com Fri Apr 1 14:33:39 2022 From: joshmeredith2008 at gmail.com (Josh Meredith) Date: Sat, 2 Apr 2022 01:33:39 +1100 Subject: Shadowing in toIface* output In-Reply-To: References: Message-ID: 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ő 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 > -------------- next part -------------- An HTML attachment was scrubbed... URL: From zubin at well-typed.com Fri Apr 1 14:39:10 2022 From: zubin at well-typed.com (Zubin Duggal) Date: Fri, 1 Apr 2022 20:09:10 +0530 Subject: Shadowing in toIface* output In-Reply-To: References: Message-ID: <20220401143910.rghtmrfkgrbtqqsl@zubin-msi> I suspect these are implicit bindings that you will need to filter out and regenerate from the tycons. You might find this HLS PR instructive as it implements something quite similar to what you seem to want: https://github.com/haskell/haskell-language-server/pull/2813 It is also relevant to question about OtherCon and unfoldings you asked earlier, as it implements a workaround for ignoring this information during testing of the generated core. Fortunately we don't need to care about this as we only use the serialized core to generate bytecode, where this information is not relevant. I believe the only reason OtherCon isn't zapped by corePrep in GHC is because core lint tends to complain if it is. Cheers, Zubin. On 22/04/01 22:25, ÉRDI Gergő 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 From simon.peytonjones at gmail.com Fri Apr 1 16:48:15 2022 From: simon.peytonjones at gmail.com (Simon Peyton Jones) Date: Fri, 1 Apr 2022 17:48:15 +0100 Subject: Shadowing in toIface* output In-Reply-To: <20220401143910.rghtmrfkgrbtqqsl@zubin-msi> References: <20220401143910.rghtmrfkgrbtqqsl@zubin-msi> Message-ID: I have opened #21333 to track this poor documentation of tidyProgram. Zubin may be right about implicit bindings (as I remark in the ticket) but if so we should fix that so that the no-shadowing invariant does hold. I don't want clients to have to work around this, as Zubin implies HLS is doing. If it doesn't, can someone add a repo case? Would someone like to put up an MR for #21333? -- I have made a stab in the ticket itself. Simon On Fri, 1 Apr 2022 at 15:40, Zubin Duggal wrote: > I suspect these are implicit bindings that you will need to filter out > and regenerate from the tycons. > > You might find this HLS PR instructive as it implements something quite > similar > to what you seem to want: > https://github.com/haskell/haskell-language-server/pull/2813 > > It is also relevant to question about OtherCon and unfoldings you asked > earlier, as it implements a workaround for ignoring this information > during testing of the generated core. Fortunately we don't need to care > about this as we only use the serialized core to generate bytecode, > where this information is not relevant. > > I believe the only reason OtherCon isn't zapped by corePrep in GHC is > because core lint tends to complain if it is. > > Cheers, > Zubin. > > On 22/04/01 22:25, ÉRDI Gergő 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 > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simon.peytonjones at gmail.com Fri Apr 1 16:51:19 2022 From: simon.peytonjones at gmail.com (Simon Peyton Jones) Date: Fri, 1 Apr 2022 17:51:19 +0100 Subject: Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings In-Reply-To: References: Message-ID: I don't think any top-level Ids should have OtherCon [] unfoldings? If they do, can you give a repro case? OtherCon [] unfoldings usually mean "I know this variable is evaluated, but I don't know what its value is. E.g data T = MkT !a !a f (MkT x y) = ... here x and y have OtherCon [] unfoldings. They are definitely not bottom! You may want stronger invariants on the output of CorePrep than we have hitherto sought. Can you explain what they are? And why you want the output of CorePrep not CoreTidy? Thanks Simon On Fri, 1 Apr 2022 at 09:13, ÉRDI Gergő wrote: > Hi, > > I'm CC-ing the Clash mailing list because I believe they should have > encountered the same problem (and perhaps have found a solution to it > already!). > > I'm trying to use `.hi` files compiled with `ExposeAllUnfoldings` set to > reconstruct full Core bindings for further processing. By and large, this > works, but I get tripped up on identifiers whose unfolding is only given > as `OtherCon []`. It is unclear to me what is causing this -- some of them > are recursive bindings while others are not. > > The problem, of course, is that if all I know about an identifier is that > it is `OtherCon []`, that doesn't allow me to restore its definition. So > is there a way to tell GHC to put "full" unfoldings everywhere in > `ExposeAllUnfoldings` mode? > > Thanks, > Gergo > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From gergo at erdi.hu Sat Apr 2 03:30:40 2022 From: gergo at erdi.hu (=?UTF-8?B?R2VyZ8WRIMOJcmRp?=) Date: Sat, 2 Apr 2022 11:30:40 +0800 Subject: Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings In-Reply-To: References: Message-ID: I'm using Prep's output (mostly so that it's in ANF) in my full compilation pipeline, so ideally I would save Prep'd Core in my .hi-equivalents so that I don't have to rerun Prep on them every time I use them. I'll get back to you with some concrete examples of `OtherCon []` vs. meaningful unfoldings next week. Merging with my other question about shadowing problems with `toIface*`, in summary it seems that what I really should be doing, is compiling up to Tidy, taking the `CoreBinding`s from there and using `toIfaceBinding` on them to save the definitions. On Sat, Apr 2, 2022 at 12:53 AM Simon Peyton Jones wrote: > > I don't think any top-level Ids should have OtherCon [] unfoldings? If they do, can you give a repro case? OtherCon [] unfoldings usually mean "I know this variable is evaluated, but I don't know what its value is. E.g > data T = MkT !a !a > f (MkT x y) = ... > > here x and y have OtherCon [] unfoldings. They are definitely not bottom! > > You may want stronger invariants on the output of CorePrep than we have hitherto sought. Can you explain what they are? And why you want the output of CorePrep not CoreTidy? > > Thanks > > Simon > > On Fri, 1 Apr 2022 at 09:13, ÉRDI Gergő wrote: >> >> Hi, >> >> I'm CC-ing the Clash mailing list because I believe they should have >> encountered the same problem (and perhaps have found a solution to it >> already!). >> >> I'm trying to use `.hi` files compiled with `ExposeAllUnfoldings` set to >> reconstruct full Core bindings for further processing. By and large, this >> works, but I get tripped up on identifiers whose unfolding is only given >> as `OtherCon []`. It is unclear to me what is causing this -- some of them >> are recursive bindings while others are not. >> >> The problem, of course, is that if all I know about an identifier is that >> it is `OtherCon []`, that doesn't allow me to restore its definition. So >> is there a way to tell GHC to put "full" unfoldings everywhere in >> `ExposeAllUnfoldings` mode? >> >> Thanks, >> Gergo >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From gergo at erdi.hu Sat Apr 2 03:34:38 2022 From: gergo at erdi.hu (=?UTF-8?B?R2VyZ8WRIMOJcmRp?=) Date: Sat, 2 Apr 2022 11:34:38 +0800 Subject: Shadowing in toIface* output In-Reply-To: References: Message-ID: 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 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ő 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 > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From mail at joachim-breitner.de Sat Apr 2 11:28:07 2022 From: mail at joachim-breitner.de (Joachim Breitner) Date: Sat, 02 Apr 2022 13:28:07 +0200 Subject: Could margebot squash? Message-ID: Hi, as far as I understand, the expected workflow for MRs is that when they are ready, the developer manually squashes the chronological commit history of the MR into a logical one with polished commit messages, typically consisting of a single commit, but could be multiple ones, and then assigns the MR to margebot, which will rebase that sequence of commits onto the staging branch and eventually merges that into master. One downside of this approach is that it requires destructive changes to work-in-progres branches: I might think the MR is ready, squash the commit sequence into a single commit, but then more work is ready. Now it’s hard to revert individual patches, or collaborate with others, because the git history was disrupted. Another is that the commit message itself isn’t very easily visible to reviewers. In other similarly sized projects (e.g. mathlib) I often see a mode where the actual commits of the MR are ignored (so they can represent the true git history of the branch, including merges and all that grit, which is good for collaboration and for reviewers to understand what has happened, without requiring developers to spend cosmetics effort on them), and upon merging by margebot/bors/mergify/whatever, the MR is merged as a single commit with the description taken from the MR description (which encourages developers to keep the MR description up to date as the MR develops, reviewers can easily see that). A downside of this that you’ll always get one commit on master per MR. If you like to submit a curated list of logical commits within one MR, then this would not work, and you’d have to use multiple MRs. Has this been considered? (I don’t want to cause unnecessary disruption with a presumptious call for action here; take it as a comment to weigh in in if and when this part of our infrastructure is about to change anyways, or maybe a careful probe if my sentiment may be shared widely.) Cheers, Joachim -- Joachim Breitner mail at joachim-breitner.de http://www.joachim-breitner.de/ From lists at richarde.dev Sun Apr 3 23:55:00 2022 From: lists at richarde.dev (Richard Eisenberg) Date: Sun, 3 Apr 2022 23:55:00 +0000 Subject: Could margebot squash? In-Reply-To: References: Message-ID: <010f017ff1da7519-d6a190bb-6772-48b5-a28e-aa4799417440-000000@us-east-2.amazonses.com> Both the current workflow and the one Joachim proposes here make sense to me, with different pros and cons. But I think now is not the time for this debate: what we have currently isn't working well enough to consider design changes. That is, CI frequently has spurious failures, and it remains (for me, at least) mostly a hope that margebot works when assigned. (There are various conditions that stop margebot from working, though without reporting any error messages.) My understanding is that we were trying to get sufficient support within GitLab so that merge trains didn't rely on margebot. I thus think that CI reliability and maintainability should be our focus in this area; reorienting to a new design would, I fear, distract our limited energy away from that focus. Richard > On Apr 2, 2022, at 7:28 AM, Joachim Breitner wrote: > > Hi, > > as far as I understand, the expected workflow for MRs is that when they > are ready, the developer manually squashes the chronological commit > history of the MR into a logical one with polished commit messages, > typically consisting of a single commit, but could be multiple ones, > and then assigns the MR to margebot, which will rebase that sequence of > commits onto the staging branch and eventually merges that into master. > > One downside of this approach is that it requires destructive changes > to work-in-progres branches: I might think the MR is ready, squash the > commit sequence into a single commit, but then more work is ready. Now > it’s hard to revert individual patches, or collaborate with others, > because the git history was disrupted. > > Another is that the commit message itself isn’t very easily visible to > reviewers. > > In other similarly sized projects (e.g. mathlib) I often see a mode > where the actual commits of the MR are ignored (so they can represent > the true git history of the branch, including merges and all that grit, > which is good for collaboration and for reviewers to understand what > has happened, without requiring developers to spend cosmetics effort on > them), and upon merging by margebot/bors/mergify/whatever, the MR is > merged as a single commit with the description taken from the MR > description (which encourages developers to keep the MR description up > to date as the MR develops, reviewers can easily see that). > > A downside of this that you’ll always get one commit on master per MR. > If you like to submit a curated list of logical commits within one MR, > then this would not work, and you’d have to use multiple MRs. > > > Has this been considered? > > (I don’t want to cause unnecessary disruption with a presumptious call > for action here; take it as a comment to weigh in in if and when this > part of our infrastructure is about to change anyways, or maybe a > careful probe if my sentiment may be shared widely.) > > Cheers, > Joachim > > > -- > Joachim Breitner > mail at joachim-breitner.de > http://www.joachim-breitner.de/ > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From ben at smart-cactus.org Mon Apr 4 02:20:54 2022 From: ben at smart-cactus.org (Ben Gamari) Date: Sun, 03 Apr 2022 22:20:54 -0400 Subject: Could margebot squash? In-Reply-To: References: Message-ID: <874k39twrp.fsf@smart-cactus.org> Joachim Breitner writes: > Hi, > > as far as I understand, the expected workflow for MRs is that when they > are ready, the developer manually squashes the chronological commit > history of the MR into a logical one with polished commit messages, > typically consisting of a single commit, but could be multiple ones, > and then assigns the MR to margebot, which will rebase that sequence of > commits onto the staging branch and eventually merges that into master. > > One downside of this approach is that it requires destructive changes > to work-in-progres branches: I might think the MR is ready, squash the > commit sequence into a single commit, but then more work is ready. Now > it’s hard to revert individual patches, or collaborate with others, > because the git history was disrupted. > > Another is that the commit message itself isn’t very easily visible to > reviewers. > > In other similarly sized projects (e.g. mathlib) I often see a mode > where the actual commits of the MR are ignored (so they can represent > the true git history of the branch, including merges and all that grit, > which is good for collaboration and for reviewers to understand what > has happened, without requiring developers to spend cosmetics effort on > them), and upon merging by margebot/bors/mergify/whatever, the MR is > merged as a single commit with the description taken from the MR > description (which encourages developers to keep the MR description up > to date as the MR develops, reviewers can easily see that). > > A downside of this that you’ll always get one commit on master per MR. > If you like to submit a curated list of logical commits within one MR, > then this would not work, and you’d have to use multiple MRs. > We would certainly want this to be optional. I, for one, do try when possible to maintain fine-grained histories. Requiring one MR per commit would make this significantly more labor-intensive. > Has this been considered? > > (I don’t want to cause unnecessary disruption with a presumptious call > for action here; take it as a comment to weigh in in if and when this > part of our infrastructure is about to change anyways, or maybe a > careful probe if my sentiment may be shared widely.) > Indeed we have considered this and, if we didn't need to use marge-bot, GitLab itself has quite good support for optionally squashing. Sadly though, we do need to use Marge for the reasons described in #19046. In the past we have been rather conservative about what features of Marge we have used since experience has shown it lacking in robustness. In general I'd very much like to move away from Marge but this will require help from GitLab upstream. I have made our need of this feature clear to upstream (and thankfully several other FOSS projects have made similar requests) but progress has been quite slow. Thankfully there appears [1] to be a recent uptick in activity; here's to hoping that it will happen in the next few releases. Cheers, - Ben [1] https://gitlab.com/groups/gitlab-org/-/epics/4911 -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 487 bytes Desc: not available URL: From mail at joachim-breitner.de Mon Apr 4 05:33:23 2022 From: mail at joachim-breitner.de (Joachim Breitner) Date: Mon, 4 Apr 2022 05:33:23 +0000 (UTC) Subject: Could margebot squash? In-Reply-To: <874k39twrp.fsf@smart-cactus.org> References: <874k39twrp.fsf@smart-cactus.org> Message-ID: <75b40b09-ae18-416c-913c-88460aefae71@joachim-breitner.de> 04.04.2022 04:21:01 Ben Gamari : > Thankfully there > appears [1] to be a recent uptick in activity; here's to hoping that it > will happen in the next few releases. Thanks, that's a good prospect then :-) From simon.peytonjones at gmail.com Mon Apr 4 08:04:25 2022 From: simon.peytonjones at gmail.com (Simon Peyton Jones) Date: Mon, 4 Apr 2022 09:04:25 +0100 Subject: Could margebot squash? In-Reply-To: References: Message-ID: One downside of this approach is that it requires destructive changes to work-in-progres branches: I might think the MR is ready, squash the commit sequence into a single commit, but then more work is ready. Now it’s hard to revert individual patches, or collaborate with others, because the git history was disrupted. Another is that the commit message itself isn’t very easily visible to reviewers. I couldn't parse this. What does "but then more work is ready" mean? Why is it hard to collaborate with others? Which commit message "itself isn’t very easily visible to reviewers."? I regard squashing as a positive bonus. I take a long series of commits with messages like "bugfix" and "fix comments" and put them into one or more logical commits, each doing (so far as poss) as single thing, each with a comprehensible commit message. That makes it *easier* to collaborate, and easier to review subsequently. (Agreed, there is a moment when I need to hold the token, but that's seldom a problem.) TL;DR: I don't yet understand the problem you are trying to solve, still less the solution. Simon On Sat, 2 Apr 2022 at 12:30, Joachim Breitner wrote: > Hi, > > as far as I understand, the expected workflow for MRs is that when they > are ready, the developer manually squashes the chronological commit > history of the MR into a logical one with polished commit messages, > typically consisting of a single commit, but could be multiple ones, > and then assigns the MR to margebot, which will rebase that sequence of > commits onto the staging branch and eventually merges that into master. > > One downside of this approach is that it requires destructive changes > to work-in-progres branches: I might think the MR is ready, squash the > commit sequence into a single commit, but then more work is ready. Now > it’s hard to revert individual patches, or collaborate with others, > because the git history was disrupted. > > Another is that the commit message itself isn’t very easily visible to > reviewers. > > In other similarly sized projects (e.g. mathlib) I often see a mode > where the actual commits of the MR are ignored (so they can represent > the true git history of the branch, including merges and all that grit, > which is good for collaboration and for reviewers to understand what > has happened, without requiring developers to spend cosmetics effort on > them), and upon merging by margebot/bors/mergify/whatever, the MR is > merged as a single commit with the description taken from the MR > description (which encourages developers to keep the MR description up > to date as the MR develops, reviewers can easily see that). > > A downside of this that you’ll always get one commit on master per MR. > If you like to submit a curated list of logical commits within one MR, > then this would not work, and you’d have to use multiple MRs. > > > Has this been considered? > > (I don’t want to cause unnecessary disruption with a presumptious call > for action here; take it as a comment to weigh in in if and when this > part of our infrastructure is about to change anyways, or maybe a > careful probe if my sentiment may be shared widely.) > > Cheers, > Joachim > > > -- > Joachim Breitner > mail at joachim-breitner.de > http://www.joachim-breitner.de/ > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simon.peytonjones at gmail.com Mon Apr 4 08:25:30 2022 From: simon.peytonjones at gmail.com (Simon Peyton Jones) Date: Mon, 4 Apr 2022 09:25:30 +0100 Subject: Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings In-Reply-To: References: Message-ID: Merging with my other question about shadowing problems with `toIface*`, in summary it seems that what I really should be doing, is compiling up to Tidy, taking the `CoreBinding`s from there and using `toIfaceBinding` on them to save the definitions. It's hard for me to be helpful here, because I don't know what invariants you want. They might be: - ANF - Fully saturated primops - No shadowing of OccNames - Globally unique Uniques or some combination of these. (Perhaps more -- read Note [CorePrep Overview]!) If you can write down precisely what you want, you can probably achieve it, starting from either the output of Tidy or the output of Prep. What is missing in GHC is a clear statement of the invariants on the output of Tidy, for which I opened #21333. If you felt able to offer an MR for that, it'd be fantastic. Simon On Sat, 2 Apr 2022 at 04:30, Gergő Érdi wrote: > I'm using Prep's output (mostly so that it's in ANF) in my full > compilation pipeline, so ideally I would save Prep'd Core in my > .hi-equivalents so that I don't have to rerun Prep on them every time > I use them. > > I'll get back to you with some concrete examples of `OtherCon []` vs. > meaningful unfoldings next week. > > Merging with my other question about shadowing problems with > `toIface*`, in summary it seems that what I really should be doing, is > compiling up to Tidy, taking the `CoreBinding`s from there and using > `toIfaceBinding` on them to save the definitions. > > On Sat, Apr 2, 2022 at 12:53 AM Simon Peyton Jones > wrote: > > > > I don't think any top-level Ids should have OtherCon [] unfoldings? If > they do, can you give a repro case? OtherCon [] unfoldings usually mean "I > know this variable is evaluated, but I don't know what its value is. E.g > > data T = MkT !a !a > > f (MkT x y) = ... > > > > here x and y have OtherCon [] unfoldings. They are definitely not bottom! > > > > You may want stronger invariants on the output of CorePrep than we have > hitherto sought. Can you explain what they are? And why you want the > output of CorePrep not CoreTidy? > > > > Thanks > > > > Simon > > > > On Fri, 1 Apr 2022 at 09:13, ÉRDI Gergő wrote: > >> > >> Hi, > >> > >> I'm CC-ing the Clash mailing list because I believe they should have > >> encountered the same problem (and perhaps have found a solution to it > >> already!). > >> > >> I'm trying to use `.hi` files compiled with `ExposeAllUnfoldings` set to > >> reconstruct full Core bindings for further processing. By and large, > this > >> works, but I get tripped up on identifiers whose unfolding is only given > >> as `OtherCon []`. It is unclear to me what is causing this -- some of > them > >> are recursive bindings while others are not. > >> > >> The problem, of course, is that if all I know about an identifier is > that > >> it is `OtherCon []`, that doesn't allow me to restore its definition. So > >> is there a way to tell GHC to put "full" unfoldings everywhere in > >> `ExposeAllUnfoldings` mode? > >> > >> Thanks, > >> Gergo > >> _______________________________________________ > >> ghc-devs mailing list > >> ghc-devs at haskell.org > >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > > _______________________________________________ > > ghc-devs mailing list > > ghc-devs at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simon.peytonjones at gmail.com Mon Apr 4 08:28:00 2022 From: simon.peytonjones at gmail.com (Simon Peyton Jones) Date: Mon, 4 Apr 2022 09:28:00 +0100 Subject: Shadowing in toIface* output In-Reply-To: References: Message-ID: 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 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 > 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ő 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 > > > > _______________________________________________ > > ghc-devs mailing list > > ghc-devs at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at joachim-breitner.de Mon Apr 4 08:30:39 2022 From: mail at joachim-breitner.de (Joachim Breitner) Date: Mon, 04 Apr 2022 10:30:39 +0200 Subject: Could margebot squash? In-Reply-To: References: Message-ID: Hi, as Richard rightfully says, this is not an aspect of our workflow that we should change right now, so consider this thread now a leisurely coffee machine chat full of hypotheticals, not a concrete call for action. But I’m happy to elaborate the technical details here. Am Montag, dem 04.04.2022 um 09:04 +0100 schrieb Simon Peyton Jones: > One downside of this approach is that it requires destructive changes > to work-in-progres branches: I might think the MR is ready, squash the > commit sequence into a single commit, but then more work is ready. Now > it’s hard to revert individual patches, or collaborate with others, > because the git history was disrupted. > > Another is that the commit message itself isn’t very easily visible to > reviewers. > > I couldn't parse this.  What does "but then more work is ready" mean? > Why is it hard to collaborate with others? I think I meant “more work is needed”. Consider the no-app-invariant- MR. I asked Sebastian to collaborate with me on the branch. It could have happened that he was making anther refinement to the DmdAnal while I was preparing the branch for merging. If I made final adjustments, squashed the commits and force-pushed the branch while he was working on it, then he can’t push his branch anymore and has a hell of a time of figuring out what went wrong, because by squashing and force-pushing (the “force” is telling) git lost the history it needs to cleanly merge my changes into his branch to push it again. In “my” workflow, you never have to force-push a feature-branch, so this problem does not occur. >  Which commit message "itself isn’t very easily visible to reviewers."? Again, consider the no-app-invariant MR. You approved it, without even knowing what the final commit message would be, because I didn’t squash yet. So the commit message that will end up on master was not visible to you as a reviewer. In “my” workflow, the final commit message will be taken from the MR description, very visible to a reviewer and easily editable by all. Maybe a minor point (commit messages are not as important as, say, good Notes) but still. Also, I often see that MR descriptions are not kept up-to-date as the MR changes; this workflow creates more incentives to keep the MR description good. > I regard squashing as a positive bonus.  I take a long series of > commits with messages like "bugfix" and "fix comments" and put them > into one or more logical commits, each doing (so far as poss) as > single thing, each with a comprehensible commit message.  I do too! There is still squashing happening, but it is done by margebot, not you manually, and only “in transit” to master – your feature branch is left alone in the process. (This means there would only be _one_ logical commit per MR, not multiple, which may be the biggest downside of this. I thought I disliked the workflow for that reason as well, until I worked with it in a few projects, and I no longer missed it. Multiple logical commits didn’t seem that useful after all, especially since they are no longer individually CI-checked, etc.) Anyways, probably these things become easier and prettier (or simply different) once we can use Gitlab’s native merge train. And unfortunately every workflow is a compromise in one way or another with git… Cheers, Joachim -- Joachim Breitner mail at joachim-breitner.de http://www.joachim-breitner.de/ From Gergo.Erdi at sc.com Tue Apr 5 03:08:53 2022 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Tue, 5 Apr 2022 03:08:53 +0000 Subject: Shadowing in toIface* output Message-ID: PUBLIC 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=, 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 On Behalf Of Simon Peyton Jones Sent: Monday, April 4, 2022 4:28 PM To: Gergő Érdi Cc: GHC Devs Subject: [External] Re: Shadowing in toIface* output ATTENTION: This email came from an external source. Do not open attachments or click on links from unknown senders or unexpected emails. Always report suspicious emails using the Report As Phishing button in Outlook to protect the Bank and our clients. 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 > 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 > 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ő > 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 > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs _______________________________________________ ghc-devs mailing list ghc-devs at haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-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. -------------- next part -------------- An HTML attachment was scrubbed... URL: From Gergo.Erdi at sc.com Tue Apr 5 04:08:00 2022 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Tue, 5 Apr 2022 04:08:00 +0000 Subject: Shadowing in toIface* output In-Reply-To: References: Message-ID: 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 On Behalf Of Erdi, Gergo via ghc-devs Sent: Tuesday, April 5, 2022 11:09 AM To: Simon Peyton Jones ; Gergo Érdi Cc: GHC Devs 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=, 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 > On Behalf Of Simon Peyton Jones Sent: Monday, April 4, 2022 4:28 PM To: Gergő Érdi > Cc: GHC Devs > 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 > 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 > 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ő > 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 > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs _______________________________________________ ghc-devs mailing list ghc-devs at haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-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: From ben at smart-cactus.org Tue Apr 5 13:53:02 2022 From: ben at smart-cactus.org (Ben Gamari) Date: Tue, 05 Apr 2022 09:53:02 -0400 Subject: Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings In-Reply-To: References: Message-ID: <87y20jskmg.fsf@smart-cactus.org> Simon Peyton Jones writes: > I don't think any top-level Ids should have OtherCon [] unfoldings? If > they do, can you give a repro case? OtherCon [] unfoldings usually mean "I > know this variable is evaluated, but I don't know what its value is. E.g > data T = MkT !a !a > f (MkT x y) = ... > > here x and y have OtherCon [] unfoldings. They are definitely not bottom! > Is there a reason why we wouldn't potentially give a static data constructor application an OtherCon [] unfolding? I would guess that usually these are small enough to have a CoreUnfolding, but in cases where the expression is too large to have an unstable unfolding we might rather want to give it an OtherCon []. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 487 bytes Desc: not available URL: From sgraf1337 at gmail.com Tue Apr 5 14:12:53 2022 From: sgraf1337 at gmail.com (Sebastian Graf) Date: Tue, 05 Apr 2022 14:12:53 +0000 Subject: Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings In-Reply-To: <87y20jskmg.fsf@smart-cactus.org> References: <87y20jskmg.fsf@smart-cactus.org> Message-ID: Top-level data structures tend to get OtherCon [] unfoldings when they are marked NOINLINE. KindRep bindings are one particular example, and they appear quite often, too. Why are KindReps are NOINLINE? Because (from Note [Grand plan for Typeable]) The KindReps can unfortunately get quite large. Moreover, the simplifier will float out various pieces of them, resulting in numerous top-level bindings. Consequently we mark the KindRep bindings as noinline, ensuring that the float-outs don't make it into the interface file. This is important since there is generally little benefit to inlining KindReps and they would otherwise strongly affect compiler performance. But perhaps it's not top-level *data structures* without unfoldings that Gergő worries about. Sebastian ------ Originalnachricht ------ Von: "Ben Gamari" An: "Simon Peyton Jones" ; "ÉRDI Gergő" Cc: "GHC Devs" ; clash-language at googlegroups.com Gesendet: 05.04.2022 15:53:02 Betreff: Re: Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings >Simon Peyton Jones writes: > >> I don't think any top-level Ids should have OtherCon [] unfoldings? If >> they do, can you give a repro case? OtherCon [] unfoldings usually mean "I >> know this variable is evaluated, but I don't know what its value is. E.g >> data T = MkT !a !a >> f (MkT x y) = ... >> >> here x and y have OtherCon [] unfoldings. They are definitely not bottom! >> >Is there a reason why we wouldn't potentially give a static data >constructor application an OtherCon [] unfolding? I would guess that >usually these are small enough to have a CoreUnfolding, but in cases >where the expression is too large to have an unstable unfolding we might >rather want to give it an OtherCon []. > >Cheers, > >- Ben > -------------- next part -------------- An HTML attachment was scrubbed... URL: From zubin at well-typed.com Tue Apr 5 18:32:06 2022 From: zubin at well-typed.com (Zubin Duggal) Date: Wed, 6 Apr 2022 00:02:06 +0530 Subject: Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings In-Reply-To: References: <87y20jskmg.fsf@smart-cactus.org> Message-ID: <20220405183206.fsstvgthjxcok3tf@zubin-msi> Core Tidy also turns CoreUnfoldings to `OtherCon []` while zapping unfoldings. On 22/04/05 14:12, Sebastian Graf wrote: >Top-level data structures tend to get OtherCon [] unfoldings when they >are marked NOINLINE. > >KindRep bindings are one particular example, and they appear quite >often, too. > >Why are KindReps are NOINLINE? Because (from Note [Grand plan for >Typeable]) > > The KindReps can unfortunately get quite large. Moreover, the >simplifier will > float out various pieces of them, resulting in numerous top-level >bindings. > Consequently we mark the KindRep bindings as noinline, ensuring that >the > float-outs don't make it into the interface file. This is important >since > there is generally little benefit to inlining KindReps and they would > otherwise strongly affect compiler performance. > >But perhaps it's not top-level *data structures* without unfoldings >that Gergő worries about. > >Sebastian > >------ Originalnachricht ------ >Von: "Ben Gamari" >An: "Simon Peyton Jones" ; "ÉRDI Gergő" > >Cc: "GHC Devs" ; clash-language at googlegroups.com >Gesendet: 05.04.2022 15:53:02 >Betreff: Re: Avoiding `OtherCon []` unfoldings, restoring definitions >from unfoldings > >>Simon Peyton Jones writes: >> >>> I don't think any top-level Ids should have OtherCon [] unfoldings? If >>> they do, can you give a repro case? OtherCon [] unfoldings usually mean "I >>> know this variable is evaluated, but I don't know what its value is. E.g >>> data T = MkT !a !a >>> f (MkT x y) = ... >>> >>> here x and y have OtherCon [] unfoldings. They are definitely not bottom! >>> >>Is there a reason why we wouldn't potentially give a static data >>constructor application an OtherCon [] unfolding? I would guess that >>usually these are small enough to have a CoreUnfolding, but in cases >>where the expression is too large to have an unstable unfolding we might >>rather want to give it an OtherCon []. >> >>Cheers, >> >>- Ben >> >_______________________________________________ >ghc-devs mailing list >ghc-devs at haskell.org >http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From Gergo.Erdi at sc.com Wed Apr 6 02:04:33 2022 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Wed, 6 Apr 2022 02:04:33 +0000 Subject: Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings Message-ID: PUBLIC Just so this isn't prematurely all lost, I went back and looked for this example. With the following two definitions: subsequences :: [a] -> [[a]] subsequences xs = [] : nonEmptySubsequences xs nonEmptySubsequences :: [a] -> [[a]] nonEmptySubsequences [] = [] nonEmptySubsequences (x:xs) = [x] : foldr f [] (nonEmptySubsequences xs) where f ys r = ys : (x : ys) : r If I save the interface, load it back and look at the unfoldings, I see that `subsequences` has a useful unfolding: subsequences Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [0] 30 10} Whereas `nonEmptySubsequenes` has a trivial one: nonEmptySubsequences OtherCon [] The interface I save is created from the ModDetails returned by tidyProgram. ExposeAllUnfoldings is set. Unfortunately, I am unable to reproduce this from the command line using the GHC executable, so before I put in the effort of making a minimal example of using the GHC API to get this result, I would first like to know if this is even an interesting case, or if there is some explanation for why one of these two would have an unfolding when the other doesn't, in certain cases. -----Original Message----- From: ghc-devs On Behalf Of Gergo Érdi Sent: Saturday, April 2, 2022 11:31 AM To: Simon Peyton Jones Cc: GHC Devs ; clash-language at googlegroups.com Subject: [External] Re: Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings I'm using Prep's output (mostly so that it's in ANF) in my full compilation pipeline, so ideally I would save Prep'd Core in my .hi-equivalents so that I don't have to rerun Prep on them every time I use them. I'll get back to you with some concrete examples of `OtherCon []` vs. meaningful unfoldings next week. Merging with my other question about shadowing problems with `toIface*`, in summary it seems that what I really should be doing, is compiling up to Tidy, taking the `CoreBinding`s from there and using `toIfaceBinding` on them to save the definitions. 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. From simon.peytonjones at gmail.com Wed Apr 6 07:37:09 2022 From: simon.peytonjones at gmail.com (Simon Peyton Jones) Date: Wed, 6 Apr 2022 08:37:09 +0100 Subject: Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings In-Reply-To: References: Message-ID: Hi Gergo If you think GHC has a but, can you open a ticket about this? It's all getting lost in a maze of emails. Can you also give precise repro instructions? In an attempt to reproduce, I have just compiled this module (the code you gave) {-# OPTIONS_GHC -fexpose-all-unfoldings #-} module Foo where nonEmptySubsequences :: [a] -> [[a]] nonEmptySubsequences [] = [] nonEmptySubsequences (x:xs) = [x] : foldr f [] (nonEmptySubsequences xs) where f ys r = ys : (x:ys) : r subsequences :: [a] -> [[a]] subsequences xs = [] : nonEmptySubsequences xs with HEAD, and -O. Unlike you, I see both unfoldings in the interface file. So clearly you and I are doing different things -- but I can't work out what is different without more precision about what you are doing. (It would be harder if it only happens when you use GHC as a library, but I think you are seeing this behaviour in regular GHC.) Thanks Simon On Wed, 6 Apr 2022 at 03:05, Erdi, Gergo wrote: > PUBLIC > > Just so this isn't prematurely all lost, I went back and looked for this > example. With the following two definitions: > > subsequences :: [a] -> [[a]] > subsequences xs = [] : nonEmptySubsequences xs > > nonEmptySubsequences :: [a] -> [[a]] > nonEmptySubsequences [] = [] > nonEmptySubsequences (x:xs) = [x] : foldr f [] (nonEmptySubsequences xs) > where f ys r = ys : (x : ys) : r > > If I save the interface, load it back and look at the unfoldings, I see > that `subsequences` has a useful unfolding: > > subsequences Unf{Src=, TopLvl=True, Value=True, > ConLike=True, WorkFree=True, Expandable=True, > Guidance=IF_ARGS [0] 30 10} > > Whereas `nonEmptySubsequenes` has a trivial one: > > nonEmptySubsequences OtherCon [] > > The interface I save is created from the ModDetails returned by > tidyProgram. ExposeAllUnfoldings is set. > > Unfortunately, I am unable to reproduce this from the command line using > the GHC executable, so before I put in the effort of making a minimal > example of using the GHC API to get this result, I would first like to know > if this is even an interesting case, or if there is some explanation for > why one of these two would have an unfolding when the other doesn't, in > certain cases. > > -----Original Message----- > From: ghc-devs On Behalf Of Gergo Érdi > Sent: Saturday, April 2, 2022 11:31 AM > To: Simon Peyton Jones > Cc: GHC Devs ; clash-language at googlegroups.com > Subject: [External] Re: Avoiding `OtherCon []` unfoldings, restoring > definitions from unfoldings > > > I'm using Prep's output (mostly so that it's in ANF) in my full > compilation pipeline, so ideally I would save Prep'd Core in my > .hi-equivalents so that I don't have to rerun Prep on them every time I use > them. > > I'll get back to you with some concrete examples of `OtherCon []` vs. > meaningful unfoldings next week. > > Merging with my other question about shadowing problems with `toIface*`, > in summary it seems that what I really should be doing, is compiling up to > Tidy, taking the `CoreBinding`s from there and using `toIfaceBinding` on > them to save the definitions. > > 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: From Gergo.Erdi at sc.com Wed Apr 6 07:49:20 2022 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Wed, 6 Apr 2022 07:49:20 +0000 Subject: Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings Message-ID: PUBLIC Please see this question in my previous email: * Unfortunately, I am unable to reproduce this from the command line using the GHC executable, so before I put in the effort of making a minimal example of using the GHC API to get this result, I would first like to know if this is even an interesting case, or if there is some explanation for why one of these two would have an unfolding when the other doesn't, in certain cases. So I can NOT reproduce it with just a GHC command line, only with my program (that uses GHC as a library). So it will require extra effort to get something you or others can just run, hence my question: is there anything here that is worth pursuing at all? Or who cares, since I'm not using unfoldings anymore (I've switched over to storing IfaceExprs directly), and it works in GHC-the-program? From: Simon Peyton Jones Sent: Wednesday, April 6, 2022 3:37 PM To: Erdi, Gergo Cc: Gergo Érdi ; GHC Devs ; clash-language at googlegroups.com Subject: [External] Re: Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings Hi Gergo If you think GHC has a but, can you open a ticket about this? It's all getting lost in a maze of emails. Can you also give precise repro instructions? In an attempt to reproduce, I have just compiled this module (the code you gave) {-# OPTIONS_GHC -fexpose-all-unfoldings #-} module Foo where nonEmptySubsequences :: [a] -> [[a]] nonEmptySubsequences [] = [] nonEmptySubsequences (x:xs) = [x] : foldr f [] (nonEmptySubsequences xs) where f ys r = ys : (x:ys) : r subsequences :: [a] -> [[a]] subsequences xs = [] : nonEmptySubsequences xs with HEAD, and -O. Unlike you, I see both unfoldings in the interface file. So clearly you and I are doing different things -- but I can't work out what is different without more precision about what you are doing. (It would be harder if it only happens when you use GHC as a library, but I think you are seeing this behaviour in regular GHC.) Thanks Simon On Wed, 6 Apr 2022 at 03:05, Erdi, Gergo > wrote: PUBLIC Just so this isn't prematurely all lost, I went back and looked for this example. With the following two definitions: subsequences :: [a] -> [[a]] subsequences xs = [] : nonEmptySubsequences xs nonEmptySubsequences :: [a] -> [[a]] nonEmptySubsequences [] = [] nonEmptySubsequences (x:xs) = [x] : foldr f [] (nonEmptySubsequences xs) where f ys r = ys : (x : ys) : r If I save the interface, load it back and look at the unfoldings, I see that `subsequences` has a useful unfolding: subsequences Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [0] 30 10} Whereas `nonEmptySubsequenes` has a trivial one: nonEmptySubsequences OtherCon [] The interface I save is created from the ModDetails returned by tidyProgram. ExposeAllUnfoldings is set. Unfortunately, I am unable to reproduce this from the command line using the GHC executable, so before I put in the effort of making a minimal example of using the GHC API to get this result, I would first like to know if this is even an interesting case, or if there is some explanation for why one of these two would have an unfolding when the other doesn't, in certain cases. -----Original Message----- From: ghc-devs > On Behalf Of Gergo Érdi Sent: Saturday, April 2, 2022 11:31 AM To: Simon Peyton Jones > Cc: GHC Devs >; clash-language at googlegroups.com Subject: [External] Re: Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings I'm using Prep's output (mostly so that it's in ANF) in my full compilation pipeline, so ideally I would save Prep'd Core in my .hi-equivalents so that I don't have to rerun Prep on them every time I use them. I'll get back to you with some concrete examples of `OtherCon []` vs. meaningful unfoldings next week. Merging with my other question about shadowing problems with `toIface*`, in summary it seems that what I really should be doing, is compiling up to Tidy, taking the `CoreBinding`s from there and using `toIfaceBinding` on them to save the definitions. 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: From simon.peytonjones at gmail.com Wed Apr 6 08:10:04 2022 From: simon.peytonjones at gmail.com (Simon Peyton Jones) Date: Wed, 6 Apr 2022 09:10:04 +0100 Subject: Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings In-Reply-To: References: Message-ID: OK. As I said earlier, the 'OtherCon []' unfoldings are unexpected to me. But if - We can't reproduce it without a lot of effort - It's not important to you any more then let's just let it lie. Simon On Wed, 6 Apr 2022 at 08:51, Erdi, Gergo wrote: > PUBLIC > > > > Please see this question in my previous email: > > > > - Unfortunately, I am unable to reproduce this from the command line > using the GHC executable, so before I put in the effort of making a minimal > example of using the GHC API to get this result, I would first like to know > if this is even an interesting case, or if there is some explanation for > why one of these two would have an unfolding when the other doesn't, in > certain cases. > > > > So I can NOT reproduce it with just a GHC command line, only with my > program (that uses GHC as a library). So it will require extra effort to > get something you or others can just run, hence my question: is there > anything here that is worth pursuing at all? Or who cares, since I’m not > using unfoldings anymore (I’ve switched over to storing IfaceExprs > directly), and it works in GHC-the-program? > > > > *From:* Simon Peyton Jones > *Sent:* Wednesday, April 6, 2022 3:37 PM > *To:* Erdi, Gergo > *Cc:* Gergo Érdi ; GHC Devs ; > clash-language at googlegroups.com > *Subject:* [External] Re: Avoiding `OtherCon []` unfoldings, restoring > definitions from unfoldings > > > > Hi Gergo > > > > If you think GHC has a but, can you open a ticket about this? It's all > getting lost in a maze of emails. > > > > Can you also give precise repro instructions? In an attempt to reproduce, > I have just compiled this module (the code you gave) > > > > {-# OPTIONS_GHC -fexpose-all-unfoldings #-} > > module Foo where > > nonEmptySubsequences :: [a] -> [[a]] > nonEmptySubsequences [] = [] > nonEmptySubsequences (x:xs) = [x] : foldr f [] (nonEmptySubsequences xs) > where > f ys r = ys : (x:ys) : r > > subsequences :: [a] -> [[a]] > subsequences xs = [] : nonEmptySubsequences xs > > > > with HEAD, and -O. Unlike you, I see both unfoldings in the interface > file. So clearly you and I are doing different things -- but I can't work > out what is different without more precision about what you are doing. > (It would be harder if it only happens when you use GHC as a library, but I > think you are seeing this behaviour in regular GHC.) > > > > Thanks > > > > Simon > > > > On Wed, 6 Apr 2022 at 03:05, Erdi, Gergo wrote: > > PUBLIC > > Just so this isn't prematurely all lost, I went back and looked for this > example. With the following two definitions: > > subsequences :: [a] -> [[a]] > subsequences xs = [] : nonEmptySubsequences xs > > nonEmptySubsequences :: [a] -> [[a]] > nonEmptySubsequences [] = [] > nonEmptySubsequences (x:xs) = [x] : foldr f [] (nonEmptySubsequences xs) > where f ys r = ys : (x : ys) : r > > If I save the interface, load it back and look at the unfoldings, I see > that `subsequences` has a useful unfolding: > > subsequences Unf{Src=, TopLvl=True, Value=True, > ConLike=True, WorkFree=True, Expandable=True, > Guidance=IF_ARGS [0] 30 10} > > Whereas `nonEmptySubsequenes` has a trivial one: > > nonEmptySubsequences OtherCon [] > > The interface I save is created from the ModDetails returned by > tidyProgram. ExposeAllUnfoldings is set. > > Unfortunately, I am unable to reproduce this from the command line using > the GHC executable, so before I put in the effort of making a minimal > example of using the GHC API to get this result, I would first like to know > if this is even an interesting case, or if there is some explanation for > why one of these two would have an unfolding when the other doesn't, in > certain cases. > > -----Original Message----- > From: ghc-devs On Behalf Of Gergo Érdi > Sent: Saturday, April 2, 2022 11:31 AM > To: Simon Peyton Jones > Cc: GHC Devs ; clash-language at googlegroups.com > Subject: [External] Re: Avoiding `OtherCon []` unfoldings, restoring > definitions from unfoldings > > > I'm using Prep's output (mostly so that it's in ANF) in my full > compilation pipeline, so ideally I would save Prep'd Core in my > .hi-equivalents so that I don't have to rerun Prep on them every time I use > them. > > I'll get back to you with some concrete examples of `OtherCon []` vs. > meaningful unfoldings next week. > > Merging with my other question about shadowing problems with `toIface*`, > in summary it seems that what I really should be doing, is compiling up to > Tidy, taking the `CoreBinding`s from there and using `toIfaceBinding` on > them to save the definitions. > > 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: From matthewtpickering at gmail.com Wed Apr 6 08:59:59 2022 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Wed, 6 Apr 2022 09:59:59 +0100 Subject: Release Updates - 9.4.1 and 9.2.3 Message-ID: Hi all, We have now forked the 9.4 branch. There are a few outstanding patches which have not yet been finished but which are essential to the release. * (#21019) Windows Toolchain Updates - Ben * (#20405) Partial Register Stall - Ben/Andreas * (!7812) Syntactic Unification - Sam The target date for the first alpha for 9.4.1 is 1st May. We have started preparing the 9.2.3 release in order to fix issues discovered in the 9.2.2 release. I will post separately to the list shortly when the schedule for this release is confirmed. The release manager for this release is Zubin. Cheers, Matt From sgraf1337 at gmail.com Wed Apr 6 12:18:18 2022 From: sgraf1337 at gmail.com (Sebastian Graf) Date: Wed, 6 Apr 2022 14:18:18 +0200 Subject: Release Updates - 9.4.1 and 9.2.3 In-Reply-To: References: Message-ID: Hi Matthew, Depending on whether https://gitlab.haskell.org/ghc/ghc/-/issues/21229 is deemed a blocker for 9.4 (I'd say it is, but YMMV), we should include https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7788 in the list. Perhaps we should make it dependent on whether !7788 is ready to merge by May or whether it ends up as the only patch that holds back the release. Sebastian Am Mi., 6. Apr. 2022 um 11:00 Uhr schrieb Matthew Pickering < matthewtpickering at gmail.com>: > Hi all, > > We have now forked the 9.4 branch. > > There are a few outstanding patches which have not yet been finished > but which are essential to the release. > > * (#21019) Windows Toolchain Updates - Ben > * (#20405) Partial Register Stall - Ben/Andreas > * (!7812) Syntactic Unification - Sam > > The target date for the first alpha for 9.4.1 is 1st May. > > We have started preparing the 9.2.3 release in order to fix issues > discovered in the 9.2.2 release. I will post separately to the list > shortly when the schedule for this release is confirmed. The release > manager for this release is Zubin. > > Cheers, > > Matt > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simon.peytonjones at gmail.com Wed Apr 6 21:55:09 2022 From: simon.peytonjones at gmail.com (Simon Peyton Jones) Date: Wed, 6 Apr 2022 22:55:09 +0100 Subject: Git problem Message-ID: Friends I see this bash$ git status On branch wip/romes/ttg-splices-improvements Your branch is up to date with 'origin/wip/romes/ttg-splices-improvements'. Changes not staged for commit: (use "git add ..." to update what will be committed) (use "git restore ..." to discard changes in working directory) (commit or discard the untracked or modified content in submodules) modified: libraries/Cabal (modified content) modified: libraries/unix (modified content) But I don't want those library changes, whatever they are. They look like Unstaged changes (2) modified libraries/Cabal @@ -1 +1 @@ -Subproject commit d638e33dbc056048b393964286c7fe394b2730d7 +Subproject commit d638e33dbc056048b393964286c7fe394b2730d7-dirty modified libraries/unix @@ -1 +1 @@ -Subproject commit 1f72ccec55c1b61299310b994754782103a617f5 +Subproject commit 1f72ccec55c1b61299310b994754782103a617f5-dirty *But using git submodule update does nothing.* How can I get my submodules in sync with this branch? Thanks Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From ietf-dane at dukhovni.org Thu Apr 7 00:34:46 2022 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Wed, 6 Apr 2022 20:34:46 -0400 Subject: Git problem In-Reply-To: References: Message-ID: On Wed, Apr 06, 2022 at 10:55:09PM +0100, Simon Peyton Jones wrote: > I see this > bash$ git status > On branch wip/romes/ttg-splices-improvements > Your branch is up to date with 'origin/wip/romes/ttg-splices-improvements'. > > modified libraries/Cabal > +Subproject commit d638e33dbc056048b393964286c7fe394b2730d7-dirty > modified libraries/unix > +Subproject commit 1f72ccec55c1b61299310b994754782103a617f5-dirty > > How can I get my submodules in sync with this branch? ( cd libraries/Cabal && { git clean -xdf .; git checkout .; } ) ( cd libraries/unix && { git clean -xdf .; git checkout .; } ) -- Viktor. From gergo at erdi.hu Thu Apr 7 06:46:30 2022 From: gergo at erdi.hu (=?UTF-8?B?R2VyZ8WRIMOJcmRp?=) Date: Thu, 7 Apr 2022 14:46:30 +0800 Subject: Warning about glomming Message-ID: Using -DDEBUG, I see a warning about glomming from OccurAnal. Having read the relevant Note, the situation is exactly what's described here: since I'm using cross-module specializations, the specializer will generate rewrite rules that replace external references with local forward references. But the one thing the Note doesn't explicitly state is why this is reported as a warning. It sounds like OccurAnal is well equipped to fix this problem. So is glomming a sign of a problem or is it not? If I see that warning, does that point to a problem in how I use the GHC API, a problem in the code that I'm trying to compile, or neither? From simon.peytonjones at gmail.com Thu Apr 7 08:12:13 2022 From: simon.peytonjones at gmail.com (Simon Peyton Jones) Date: Thu, 7 Apr 2022 09:12:13 +0100 Subject: Warning about glomming In-Reply-To: References: Message-ID: It's a warning directed solely at compiler authors (hence -DDEBUG). If a lot of glomming is happening, it might be due to some scoping or dependency analysis bug -- e.g. perhaps OccAnal isn't putting bindings in proper dependency order, or perhaps some plugin is gratuitously scrambling the order of the top level definitions. Or it might be legitimate, as in your case. Perhaps adding a Note with the code that generates the warning (or wherever you looked -- where was that?) would be better. I always like to look for ways to reply not just to Gergo but to all the future Gergos who stumble over this. Gergo might you offer a patch? Simon On Thu, 7 Apr 2022 at 07:47, Gergő Érdi wrote: > Using -DDEBUG, I see a warning about glomming from OccurAnal. Having > read the relevant Note, the situation is exactly what's described > here: since I'm using cross-module specializations, the specializer > will generate rewrite rules that replace external references with > local forward references. > > But the one thing the Note doesn't explicitly state is why this is > reported as a warning. It sounds like OccurAnal is well equipped to > fix this problem. So is glomming a sign of a problem or is it not? If > I see that warning, does that point to a problem in how I use the GHC > API, a problem in the code that I'm trying to compile, or neither? > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simon.peytonjones at gmail.com Thu Apr 7 09:02:41 2022 From: simon.peytonjones at gmail.com (Simon Peyton Jones) Date: Thu, 7 Apr 2022 10:02:41 +0100 Subject: Git problem In-Reply-To: References: Message-ID: Thanks Viktor -- I'll try that Simon On Thu, 7 Apr 2022 at 01:37, Viktor Dukhovni wrote: > On Wed, Apr 06, 2022 at 10:55:09PM +0100, Simon Peyton Jones wrote: > > > I see this > > bash$ git status > > On branch wip/romes/ttg-splices-improvements > > Your branch is up to date with > 'origin/wip/romes/ttg-splices-improvements'. > > > > modified libraries/Cabal > > +Subproject commit d638e33dbc056048b393964286c7fe394b2730d7-dirty > > modified libraries/unix > > +Subproject commit 1f72ccec55c1b61299310b994754782103a617f5-dirty > > > > How can I get my submodules in sync with this branch? > > ( cd libraries/Cabal && { git clean -xdf .; git checkout .; } ) > ( cd libraries/unix && { git clean -xdf .; git checkout .; } ) > > -- > Viktor. > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simon.peytonjones at gmail.com Thu Apr 7 12:57:01 2022 From: simon.peytonjones at gmail.com (Simon Peyton Jones) Date: Thu, 7 Apr 2022 13:57:01 +0100 Subject: Shadowing in toIface* output In-Reply-To: References: Message-ID: > > 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=, > > 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 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 *On Behalf Of *Erdi, > Gergo via ghc-devs > *Sent:* Tuesday, April 5, 2022 11:09 AM > *To:* Simon Peyton Jones ; Gergo Érdi < > gergo at erdi.hu> > *Cc:* GHC Devs > *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=, > > 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 *On Behalf Of *Simon > Peyton Jones > *Sent:* Monday, April 4, 2022 4:28 PM > *To:* Gergő Érdi > *Cc:* GHC Devs > *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 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 > 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ő 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 > > > > > _______________________________________________ > > ghc-devs mailing list > > ghc-devs at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-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: From matthewtpickering at gmail.com Thu Apr 7 14:52:30 2022 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Thu, 7 Apr 2022 15:52:30 +0100 Subject: Release Updates - 9.4.1 and 9.2.3 In-Reply-To: References: Message-ID: Hi Sebastian, I don't think I understand the severity of #21229, is it an incorrect runtime result? If so, we should definitely fix it before 9.4.1. Thanks for bringing it to my attention. Matt On Wed, Apr 6, 2022 at 1:18 PM Sebastian Graf wrote: > > Hi Matthew, > > Depending on whether https://gitlab.haskell.org/ghc/ghc/-/issues/21229 is deemed a blocker for 9.4 (I'd say it is, but YMMV), we should include https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7788 in the list. > Perhaps we should make it dependent on whether !7788 is ready to merge by May or whether it ends up as the only patch that holds back the release. > > Sebastian > > Am Mi., 6. Apr. 2022 um 11:00 Uhr schrieb Matthew Pickering : >> >> Hi all, >> >> We have now forked the 9.4 branch. >> >> There are a few outstanding patches which have not yet been finished >> but which are essential to the release. >> >> * (#21019) Windows Toolchain Updates - Ben >> * (#20405) Partial Register Stall - Ben/Andreas >> * (!7812) Syntactic Unification - Sam >> >> The target date for the first alpha for 9.4.1 is 1st May. >> >> We have started preparing the 9.2.3 release in order to fix issues >> discovered in the 9.2.2 release. I will post separately to the list >> shortly when the schedule for this release is confirmed. The release >> manager for this release is Zubin. >> >> Cheers, >> >> Matt >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From gergo at erdi.hu Fri Apr 8 01:28:53 2022 From: gergo at erdi.hu (=?ISO-8859-2?Q?=C9RDI_Gerg=F5?=) Date: Fri, 8 Apr 2022 09:28:53 +0800 (+08) Subject: Shadowing in toIface* output In-Reply-To: References: Message-ID: On Thu, 7 Apr 2022, Simon Peyton Jones wrote: > If you can repro this with GHC, can you open a ticket for it. https://gitlab.haskell.org/ghc/ghc/-/issues/21363 From gergo at erdi.hu Fri Apr 8 01:58:02 2022 From: gergo at erdi.hu (=?ISO-8859-2?Q?=C9RDI_Gerg=F5?=) Date: Fri, 8 Apr 2022 09:58:02 +0800 (+08) Subject: Warning about glomming In-Reply-To: References: Message-ID: On Thu, 7 Apr 2022, Simon Peyton Jones wrote: > Gergo might you offer a patch? https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7964 From ben at smart-cactus.org Fri Apr 8 14:53:16 2022 From: ben at smart-cactus.org (Ben Gamari) Date: Fri, 08 Apr 2022 10:53:16 -0400 Subject: Windows rework merged ; fresh build necessary on Windows Message-ID: <87pmlr630b.fsf@smart-cactus.org> Hi all, A few minutes ago I merged !7448 and the associated MRs, moving GHC to use the msys2 Clang64 toolchain on Windows. This work improves compilation time, maintainability, and fixes a numerous long-standing bugs affecting Windows and other platforms. However, as a result you may find that in an existing tree `configure` will fail with an error complaining that `clang` can not be found. This is due to the fact that the toolchain tarballs are stale and be fixed with: rm -R _build inplace/mingw win32-tarballs ./boot ./configure --enable-tarballs-autodownload Do let me know if you see any other issues; I'm a bit under the weather at the moment but I'll try to keep an eye on email. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 487 bytes Desc: not available URL: From david.feuer at gmail.com Tue Apr 12 21:02:31 2022 From: david.feuer at gmail.com (David Feuer) Date: Tue, 12 Apr 2022 17:02:31 -0400 Subject: Absence info at run-time Message-ID: Suppose `f` doesn't use its first argument. When forming the thunk (or partial application) `f a`, we don't need to record `a`. What if instead of arity, we store a bitmap used/absent arguments, terminated by a 1 bit? Could we then get rid of "stupid thunks" like `(const a) b`? -------------- next part -------------- An HTML attachment was scrubbed... URL: From klebinger.andreas at gmx.at Wed Apr 13 06:59:06 2022 From: klebinger.andreas at gmx.at (Andreas Klebinger) Date: Wed, 13 Apr 2022 08:59:06 +0200 Subject: Absence info at run-time In-Reply-To: References: Message-ID: W/W should transform such a function into one who takes one less argument removing any runtime overhead at least for fully applied functions. I suppose your suggestion is then if we an expression`f x` where bar takes multiple arguments, but doesn't use the current argument then GHC should: * Inspect f, check if the first argument to f is used * If we can determine it isn't used instead of creating a PAP capturing `f` and `x` instead only capture `f` and record this in the PAP closure somehow. * Once the PAP is fully applied pass a dummy argument instead of `x` to f. If f is a known call that seems doable, although adding a bitmap to paps might require us to increase the size of all PAP closures, making this optimization less useful. If `f` is a unknown function there is currently no way to get absent/used info for it's arguments at runtime. And changing that would be a major change which seems unlikely to pay off. So I think this would be theoretically possible, but it would rarely pay off. Also do you have an example where `(const a) b` leads to stupid thunks? It seems to me const should always be inlined in such a case, avoiding a PAP allocation. Am 12/04/2022 um 23:02 schrieb David Feuer: > Suppose `f` doesn't use its first argument. When forming the thunk (or > partial application) `f a`, we don't need to record `a`. What if > instead of arity, we store a bitmap used/absent arguments, terminated > by a 1 bit? Could we then get rid of "stupid thunks" like `(const a) b`? > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From sgraf1337 at gmail.com Wed Apr 13 08:21:25 2022 From: sgraf1337 at gmail.com (Sebastian Graf) Date: Wed, 13 Apr 2022 08:21:25 +0000 Subject: Markup language/convention for Notes? Message-ID: Hi Devs, When writing Notes, I find myself using markdown-inspired or haddock-inspired features. The reason is that I keep telling myself > In 5 years time, we'll surely have an automated tool that renders Notes referenced under the cursor in a popup in our IDE And I might not be completely wrong about that, after all the strong conventions about Note declaration syntax allow me to do jump-to-definition on Note links in my IDE already (thanks to a shell script written by Zubin!). Still, over the years I kept drifting between markdown and haddock syntax, sometimes used `backticked inline code` or haddock 'ticks' to refer to functions in the compiler (sometimes even 'GHC.Fully.Qualified.ticks') and for code blocks I used all of the following forms: Haddock "code quote" > id :: a -> a > id x = x Markdown triple backticks ```hs id :: a -> a id x = x ``` Indentation by spaces id :: a -> a id x = x And so on. I know that at least Simon was thrown off in the past about my use of "tool-aware markup", perhaps also because I kept switching the targetted tool. I don't like that either. So I wonder Do you think it is worth optimising Notes for post-processing by an external tool?I think it's only reasonable if we decide for a target syntax. Which syntax should it be? Cheers, Sebastian -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben at smart-cactus.org Wed Apr 13 20:44:59 2022 From: ben at smart-cactus.org (Ben Gamari) Date: Wed, 13 Apr 2022 16:44:59 -0400 Subject: Markup language/convention for Notes? In-Reply-To: References: Message-ID: <87wnfs1zo5.fsf@smart-cactus.org> "Sebastian Graf" writes: > Hi Devs, > > When writing Notes, I find myself using markdown-inspired or > haddock-inspired features. The reason is that I keep telling myself > > > In 5 years time, we'll surely have an automated tool that renders > > Notes referenced under the cursor in a popup in our IDE > I tell myself a similar tale. true. In particular, I would like to see Haddock gain support for Note-like documentation. When I wrote the Note linter I was surprised by how simple and robust the parser was despite the rather ad-hoc choice of syntax. This makes me hopeful that this goal can be realized. Concretely, I suspect that something like https://github.com/haskell/haddock/issues/193 might be a reasonable approximation of what we need. > And I might not be completely wrong about that, after all the strong > conventions about Note declaration syntax allow me to do > jump-to-definition on Note links in my IDE already (thanks to a shell > script written by Zubin!). > > Still, over the years I kept drifting between markdown and haddock > syntax, sometimes used `backticked inline code` or haddock 'ticks' to > refer to functions in the compiler (sometimes even > 'GHC.Fully.Qualified.ticks') and for code blocks I used all of the > following forms: > I am quite guilty of the same. > I know that at least Simon was thrown off in the past about my use of > "tool-aware markup", perhaps also because I kept switching the targetted > tool. I don't like that either. So I wonder > Do you think it is worth optimising Notes for post-processing by an > external tool?I think it's only reasonable if we decide for a target > syntax. Which syntax should it be? Yes, we should decide on a direction and document it. My sense is that Haddock is probably the best option when it comes to integrating with "normal" Haskell workflows. Happily, backticks are valid Haddock syntax so at least this particular bit of muscle-memory can be retained [1]. Incidentally, I suspect that ```-style code blocks would be a valuable addition to Haddock for syntax-highlighted blocks of code in languages other than Haskell. On the other hand, there is talk [2] of Haddock gaining a Markdown frontend, so Markdown may be more of a viable option than I'm giving it credit for. Cheers, - Ben [1] https://haskell-haddock.readthedocs.io/en/latest/markup.html#hyperlinked-identifiers [2] https://github.com/haskell/haddock/issues/794#issuecomment-1018884773 -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 487 bytes Desc: not available URL: From david.feuer at gmail.com Wed Apr 13 20:57:49 2022 From: david.feuer at gmail.com (David Feuer) Date: Wed, 13 Apr 2022 16:57:49 -0400 Subject: Run-time absence info In-Reply-To: References: Message-ID: > > Date: Wed, 13 Apr 2022 08:59:06 +0200 > From: Andreas Klebinger > To: ghc-devs at haskell.org > Subject: Re: Absence info at run-time > Message-ID: > Content-Type: text/plain; charset=UTF-8; format=flowed > > W/W should transform such a function into one who takes one less > argument removing any runtime overhead at least for fully applied > functions. > Fully applied functions are definitely not what I'm talking about. I suppose your suggestion is then if we an expression`f x` where bar > takes multiple arguments, but doesn't use the current argument then GHC > should: > > * Inspect f, check if the first argument to f is used > * If we can determine it isn't used instead of creating a PAP capturing > `f` and `x` instead only capture `f` and record this in the PAP closure > somehow. > * Once the PAP is fully applied pass a dummy argument instead of `x` to f. > Yes, that's the idea. The "somehow" is described below. If f is a known call that seems doable, although adding a bitmap to paps > might require us to increase the size of all PAP closures, making this > optimization less useful. > Every PAP has to carry its arity. I just looked it up: typedef struct { StgHeader header; StgHalfWord arity; // number of arguments left to apply, if zero this is an AP closure StgHalfWord n_args; // number of applied arguments StgClosure *fun; // guaranteed to point to a FUN closure StgClosure *payload[]; } StgPAP; On a 64-bit machine, we can combine arity and absence info for functions of up to 31 arguments into half a word. Specifically, set the lowest bit to indicate whether the first argument is used, etc. Then bitwise-or that with 1 `shiftL` arity. Each partial application performed shifts right by the number of arguments applied; if the result is 1, we know it's fully applied. (Any idea why we need the number of arguments that have been applied in the PAP? If that's actually only need for AP, then we might be able to make things a little more compact.) > If `f` is a unknown function there is currently no way to get > absent/used info for it's arguments at runtime. And changing that would > be a major change which seems unlikely to pay off. > I described a mechanism for encoding this concisely above. The same encoding could be used for functions that haven't been partially applied. I don't know where their arities are stashed. In their info tables? > So I think this would be theoretically possible, but it would rarely pay > off. > I'm not sure it's so rare. We end up having to work around this issue in libraries, with varying levels of effort and success. > Also do you have an example where `(const a) b` leads to stupid thunks? > It seems to me const should always be inlined in such a case, avoiding a > PAP allocation. > There won't be a PAP allocation if const inlines. The stupid thunk is a thunk to apply (\ _ -> a) to b. Suppose we define `fmap` for plain arrays (I know; probably not the best example), and let <$ take its default implementation: (<$) a = fmap (const a) If we calculate x <$ arr, that will fill an array with thunks, each of them retaining an element of the original array which will never be used. > Am 12/04/2022 um 23:02 schrieb David Feuer: > > Suppose `f` doesn't use its first argument. When forming the thunk (or > > partial application) `f a`, we don't need to record `a`. What if > > instead of arity, we store a bitmap used/absent arguments, terminated > > by a 1 bit? Could we then get rid of "stupid thunks" like `(const a) b`? > > > > _______________________________________________ > > ghc-devs mailing list > > ghc-devs at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > ------------------------------ > > Message: 3 > Date: Wed, 13 Apr 2022 08:21:25 +0000 > From: "Sebastian Graf" > To: "GHC Devs" > Subject: Markup language/convention for Notes? > Message-ID: > Content-Type: text/plain; charset="utf-8"; Format="flowed" > > Hi Devs, > > When writing Notes, I find myself using markdown-inspired or > haddock-inspired features. The reason is that I keep telling myself > > > In 5 years time, we'll surely have an automated tool that renders > Notes referenced under the cursor in a popup in our IDE > > And I might not be completely wrong about that, after all the strong > conventions about Note declaration syntax allow me to do > jump-to-definition on Note links in my IDE already (thanks to a shell > script written by Zubin!). > Still, over the years I kept drifting between markdown and haddock > syntax, sometimes used `backticked inline code` or haddock 'ticks' to > refer to functions in the compiler (sometimes even > 'GHC.Fully.Qualified.ticks') and for code blocks I used all of the > following forms: > > Haddock "code quote" > > > id :: a -> a > > id x = x > > Markdown triple backticks > > ```hs > id :: a -> a > id x = x > ``` > > Indentation by spaces > > id :: a -> a > id x = x > > And so on. > > I know that at least Simon was thrown off in the past about my use of > "tool-aware markup", perhaps also because I kept switching the targetted > tool. I don't like that either. So I wonder > Do you think it is worth optimising Notes for post-processing by an > external tool?I think it's only reasonable if we decide for a target > syntax. Which syntax should it be? > Cheers, > Sebastian > -------------- next part -------------- > An HTML attachment was scrubbed... > URL: < > http://mail.haskell.org/pipermail/ghc-devs/attachments/20220413/84549293/attachment-0001.html > > > > ------------------------------ > > Subject: Digest Footer > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > ------------------------------ > > End of ghc-devs Digest, Vol 224, Issue 10 > ***************************************** > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simon.peytonjones at gmail.com Wed Apr 13 20:58:45 2022 From: simon.peytonjones at gmail.com (Simon Peyton Jones) Date: Wed, 13 Apr 2022 21:58:45 +0100 Subject: Markup language/convention for Notes? In-Reply-To: <87wnfs1zo5.fsf@smart-cactus.org> References: <87wnfs1zo5.fsf@smart-cactus.org> Message-ID: I'm open-minded, but I *really* want the text to be readily readable *in the original source file*. So * Back-ticks are much better than `@` signs; the latter are too noisy. * For code, backticks add clutter. Maybe just intentend text can be code? (Unless it's part of a bulleted list.) On Wed, 13 Apr 2022 at 21:45, Ben Gamari wrote: > "Sebastian Graf" writes: > > > Hi Devs, > > > > When writing Notes, I find myself using markdown-inspired or > > haddock-inspired features. The reason is that I keep telling myself > > > > > In 5 years time, we'll surely have an automated tool that renders > > > Notes referenced under the cursor in a popup in our IDE > > > > I tell myself a similar tale. true. In particular, I would like to see > Haddock gain support for Note-like documentation. When I wrote the Note > linter I was surprised by how simple and robust the parser was despite > the rather ad-hoc choice of syntax. This makes me hopeful that this goal > can be realized. > > Concretely, I suspect that something like > https://github.com/haskell/haddock/issues/193 might be a reasonable > approximation of what we need. > > > And I might not be completely wrong about that, after all the strong > > conventions about Note declaration syntax allow me to do > > jump-to-definition on Note links in my IDE already (thanks to a shell > > script written by Zubin!). > > > > Still, over the years I kept drifting between markdown and haddock > > syntax, sometimes used `backticked inline code` or haddock 'ticks' to > > refer to functions in the compiler (sometimes even > > 'GHC.Fully.Qualified.ticks') and for code blocks I used all of the > > following forms: > > > I am quite guilty of the same. > > > I know that at least Simon was thrown off in the past about my use of > > "tool-aware markup", perhaps also because I kept switching the targetted > > tool. I don't like that either. So I wonder > > Do you think it is worth optimising Notes for post-processing by an > > external tool?I think it's only reasonable if we decide for a target > > syntax. Which syntax should it be? > > Yes, we should decide on a direction and document it. My sense is that > Haddock is probably the best option when it comes to integrating with > "normal" Haskell workflows. Happily, backticks are valid Haddock syntax > so at least this particular bit of muscle-memory can be retained [1]. > > Incidentally, I suspect that ```-style code blocks would be a > valuable addition to Haddock for syntax-highlighted blocks of code in > languages other than Haskell. > > On the other hand, there is talk [2] of Haddock gaining a Markdown > frontend, so Markdown may be more of a viable option than I'm giving it > credit for. > > Cheers, > > - Ben > > > [1] > https://haskell-haddock.readthedocs.io/en/latest/markup.html#hyperlinked-identifiers > [2] https://github.com/haskell/haddock/issues/794#issuecomment-1018884773 > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben at smart-cactus.org Wed Apr 13 21:15:39 2022 From: ben at smart-cactus.org (Ben Gamari) Date: Wed, 13 Apr 2022 17:15:39 -0400 Subject: Markup language/convention for Notes? In-Reply-To: References: <87wnfs1zo5.fsf@smart-cactus.org> Message-ID: <87sfqg1y8r.fsf@smart-cactus.org> Simon Peyton Jones writes: > I'm open-minded, but I *really* want the text to be readily readable *in > the original source file*. So > * Back-ticks are much better than `@` signs; the latter are too noisy. > * For code, backticks add clutter. Maybe just intentend text can be > code? (Unless it's part of a bulleted list.) > In Markdown region of text indented by at least four spaces denotes a code block element. Unfortunately, Haddock doesn't have a similarly noise-free syntax, requiring that lines of code blocks begin with `>`. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 487 bytes Desc: not available URL: From oleg.grenrus at iki.fi Thu Apr 14 08:46:00 2022 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Thu, 14 Apr 2022 11:46:00 +0300 Subject: Markup language/convention for Notes? In-Reply-To: <87sfqg1y8r.fsf@smart-cactus.org> References: <87wnfs1zo5.fsf@smart-cactus.org> <87sfqg1y8r.fsf@smart-cactus.org> Message-ID: You can write @ code :: With 'Linked' -> Types code = ... @ The linked identifiers are a huge feature of haddock, makes documentation a lot nicer to navigate. Of course general syntax highlighter might also auto-link identifiers in Haskell codeblocks, but none of markdown parsers has a support for such hooks, AFAICT. - Oleg On 14.4.2022 0.15, Ben Gamari wrote: > Simon Peyton Jones writes: > >> I'm open-minded, but I *really* want the text to be readily readable *in >> the original source file*. So >> * Back-ticks are much better than `@` signs; the latter are too noisy. >> * For code, backticks add clutter. Maybe just intentend text can be >> code? (Unless it's part of a bulleted list.) >> > In Markdown region of text indented by at least four spaces denotes a > code block element. Unfortunately, Haddock doesn't have a similarly > noise-free syntax, requiring that lines of code blocks begin with `>`. > > Cheers, > > - Ben > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs On 14.4.2022 0.15, Ben Gamari wrote: > Simon Peyton Jones writes: > >> I'm open-minded, but I *really* want the text to be readily readable *in >> the original source file*. So >> * Back-ticks are much better than `@` signs; the latter are too noisy. >> * For code, backticks add clutter. Maybe just intentend text can be >> code? (Unless it's part of a bulleted list.) >> > In Markdown region of text indented by at least four spaces denotes a > code block element. Unfortunately, Haddock doesn't have a similarly > noise-free syntax, requiring that lines of code blocks begin with `>`. > > Cheers, > > - Ben > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From nr at cs.tufts.edu Thu Apr 14 18:32:25 2022 From: nr at cs.tufts.edu (Norman Ramsey) Date: Thu, 14 Apr 2022 14:32:25 -0400 Subject: how to build Haddock documentation for a single module? Message-ID: <20220414183225.E76D82C1D66@homedog.cs.tufts.edu> I'm fine-tuning the Haddock documentation for just one module that sits in the $GHC/compiler/GHC subtree. Is there a way I can get Hadrian to build the documentation for just that module? Norman From nr at cs.tufts.edu Thu Apr 14 19:30:33 2022 From: nr at cs.tufts.edu (Norman Ramsey) Date: Thu, 14 Apr 2022 15:30:33 -0400 Subject: how to build Haddock documentation for a single module? In-Reply-To: <20220414183225.E76D82C1D66@homedog.cs.tufts.edu> (sfid-H-20220414-143252-+39.31-1@multi.osbf.lua) References: <20220414183225.E76D82C1D66@homedog.cs.tufts.edu> (sfid-H-20220414-143252-+39.31-1@multi.osbf.lua) Message-ID: <20220414193033.085EC2C1AC7@homedog.cs.tufts.edu> > Is there a way I can get Hadrian to build the documentation for > just that module? Here's more detail about what I'm facing. I'm trying to fine-tune the Haddock documentation of a module that I intend to put into an MR for GHC Central. This means I need to be able to re-run Haddock so I can look at the output, with a sensible turnaround time. I've tried ``` ./hadrian/build _build/docs/html/libraries/ghc/GHC-Driver-Backend.html ``` But this attempt results in no action, even when the source code has changed. I've also tried ``` haddock -o /tmp/zzz -h compiler/GHC/Driver/Backend.hs ``` But this attempt results in a slew of error messages, all similar, of which a representative sample looks like this: ``` compiler/GHC/Driver/Backend.hs:104:1: error: Could not load module ‘GHC.Prelude’ It is a member of the hidden package ‘ghc-9.2.2’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v (or `:set -v` in ghci) to see a list of the files searched for. | 104 | import GHC.Prelude | ^^^^^^^^^^^^^^^^^^ ``` Finally, I have had some success with ``` ./hadrian/build -j _build/docs/html/index.html ``` This attempt does rebuild the documentation, but I am sorry to say that the first run took 19 minutes, and subsequent runs take about 3 minutes. On a nice, beefy machine with 8 cores. If it takes 3 minutes to visualize every change in the documentation, I think I will not have the patience to make any more changes. Help? Norman From lexi.lambda at gmail.com Fri Apr 15 00:32:35 2022 From: lexi.lambda at gmail.com (Alexis King) Date: Thu, 14 Apr 2022 19:32:35 -0500 Subject: Seeking RTS experts to review delimited continuations MR Message-ID: Hi all, I have recently opened a draft MR with my initial implementation of first-class delimited continuations in the RTS, available here: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7942 The MR is not entirely finished—it still requires docs and tests, which I am gradually working on. However, barring any bugs I discover after writing those tests, I believe the implementation itself is feature-complete with respect to the proposal. Given that it is a nontrivial patch to a somewhat unloved portion of GHC, and given that there are a couple questions I have about how best to go about testing certain interactions in the first place, I figured I would reach out and see if anyone particularly familiar with the guts of the RTS would be willing to volunteer some time to give it a careful look. The good news is that the patch is not actually very large, and it changes very little existing code: the diffstats currently sit at +1,078 -48. For those interested in taking a look at the patch, I recommend starting with the Notes mentioned in the MR description. I suspect they may be a bit sparse at the moment, so please do not hesitate to ask questions; I will do my best to respond promptly. Many thanks, Alexis -------------- next part -------------- An HTML attachment was scrubbed... URL: From ekmett at gmail.com Fri Apr 15 17:49:35 2022 From: ekmett at gmail.com (Edward Kmett) Date: Fri, 15 Apr 2022 13:49:35 -0400 Subject: Seeking RTS experts to review delimited continuations MR In-Reply-To: References: Message-ID: I'm super excited to see this, as it'll rather drastically improve the performance I can get out of my fancy backtracking search algorithms. -Edward On Thu, Apr 14, 2022 at 8:33 PM Alexis King wrote: > Hi all, > > I have recently opened a draft MR with my initial implementation of > first-class delimited continuations in the RTS, available here: > https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7942 > > The MR is not entirely finished—it still requires docs and tests, which I > am gradually working on. However, barring any bugs I discover after writing > those tests, I believe the implementation itself is feature-complete with > respect to the proposal. Given that it is a nontrivial patch to a somewhat > unloved portion of GHC, and given that there are a couple questions I have > about how best to go about testing certain interactions in the first place, > I figured I would reach out and see if anyone particularly familiar with > the guts of the RTS would be willing to volunteer some time to give it a > careful look. > > The good news is that the patch is not actually very large, and it changes > very little existing code: the diffstats currently sit at +1,078 -48. For > those interested in taking a look at the patch, I recommend starting with > the Notes mentioned in the MR description. I suspect they may be a bit > sparse at the moment, so please do not hesitate to ask questions; I will do > my best to respond promptly. > > Many thanks, > Alexis > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben at smart-cactus.org Fri Apr 15 19:51:31 2022 From: ben at smart-cactus.org (Ben Gamari) Date: Fri, 15 Apr 2022 15:51:31 -0400 Subject: how to build Haddock documentation for a single module? In-Reply-To: <20220414183225.E76D82C1D66@homedog.cs.tufts.edu> References: <20220414183225.E76D82C1D66@homedog.cs.tufts.edu> Message-ID: <87pmli15xv.fsf@smart-cactus.org> Norman Ramsey writes: > I'm fine-tuning the Haddock documentation for just one module > that sits in the $GHC/compiler/GHC subtree. Is there a way I can > get Hadrian to build the documentation for just that module? > I'll admit that this is not something that I have ever attempted. With enough perseverence you might be able to construct a command-line which to invoke Haddock manually but I am skeptical that this would be worth the effort. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 487 bytes Desc: not available URL: From ben at well-typed.com Sun Apr 17 20:09:58 2022 From: ben at well-typed.com (Ben Gamari) Date: Sun, 17 Apr 2022 16:09:58 -0400 Subject: Haskell.org outage Message-ID: <87k0bn1nhx.fsf@smart-cactus.org> Hello everyone, Unfortunately Haskell.org, downloads.haskell.org, and hoogle.haskell.org are currently down. We are currently investigating the cause. Updates will be posted as they are available. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 487 bytes Desc: not available URL: From ben at well-typed.com Mon Apr 18 04:59:13 2022 From: ben at well-typed.com (Ben Gamari) Date: Mon, 18 Apr 2022 00:59:13 -0400 Subject: Haskell.org outage In-Reply-To: <87k0bn1nhx.fsf@smart-cactus.org> References: <87k0bn1nhx.fsf@smart-cactus.org> Message-ID: <87fsmb0yyb.fsf@smart-cactus.org> Ben Gamari writes: > Hello everyone, > > Unfortunately Haskell.org, downloads.haskell.org, and hoogle.haskell.org > are currently down. We are currently investigating the cause. Updates > will be posted as they are available. > A quick update: It sounds as though the outage is due to a hardware issue which our hosting provider is currently investigating but naturally responses are a bit slower than usual due to the holiday. More updates to follow tomorrow. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 487 bytes Desc: not available URL: From ben at smart-cactus.org Mon Apr 18 14:19:21 2022 From: ben at smart-cactus.org (Ben Gamari) Date: Mon, 18 Apr 2022 10:19:21 -0400 Subject: Seeking RTS experts to review delimited continuations MR In-Reply-To: References: Message-ID: <87czhe1nmm.fsf@smart-cactus.org> Alexis King writes: > Hi all, > > I have recently opened a draft MR with my initial implementation of > first-class delimited continuations in the RTS, available here: > https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7942 > Hi Alexis, Just to confirm, I have added this to my queue and started a pass. Thanks for pushing this through! Very excited to see this upstream. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 487 bytes Desc: not available URL: From nr at cs.tufts.edu Tue Apr 19 17:28:08 2022 From: nr at cs.tufts.edu (Norman Ramsey) Date: Tue, 19 Apr 2022 13:28:08 -0400 Subject: How to coordinate Haddock MR with GHC MR? Message-ID: <20220419172808.465F62C1AD2@homedog.cs.tufts.edu> GHC merge request !7442 changes the GHC API in a way that requires a one-line change in `utils/haddock`. What should I do with this? I can create an MR for the Haddock people, but I don't know how to mark it as something that should be applied at exactly the same time that Haddock transitions to GHC 9.6. Please advise. Norman From hecate at glitchbra.in Tue Apr 19 17:32:24 2022 From: hecate at glitchbra.in (=?UTF-8?Q?H=c3=a9cate?=) Date: Tue, 19 Apr 2022 19:32:24 +0200 Subject: How to coordinate Haddock MR with GHC MR? In-Reply-To: <20220419172808.465F62C1AD2@homedog.cs.tufts.edu> References: <20220419172808.465F62C1AD2@homedog.cs.tufts.edu> Message-ID: Hi Norman! The workflow is as follow: * You create an MR for GHC that needs Haddock patched * You open an MR on the Haddock mirror on the Haskell Gitlab, targeting the ghc-head branch * It gets merged * You update the haddock submodule in the GHC git tree * And done. Le 19/04/2022 à 19:28, Norman Ramsey a écrit : > GHC merge request !7442 changes the GHC API in a way that requires > a one-line change in `utils/haddock`. What should I do with this? > I can create an MR for the Haddock people, but I don't know how to > mark it as something that should be applied at exactly the same > time that Haddock transitions to GHC 9.6. Please advise. > > > Norman > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -- Hécate ✨ 🐦: @TechnoEmpress IRC: Hecate WWW: https://glitchbra.in RUN: BSD From nr at cs.tufts.edu Tue Apr 19 21:01:49 2022 From: nr at cs.tufts.edu (Norman Ramsey) Date: Tue, 19 Apr 2022 17:01:49 -0400 Subject: How to coordinate Haddock MR with GHC MR? In-Reply-To: (sfid-H-20220419-133340-+49.41-1@multi.osbf.lua) References: <20220419172808.465F62C1AD2@homedog.cs.tufts.edu> (sfid-H-20220419-133340-+49.41-1@multi.osbf.lua) Message-ID: <20220419210149.3FA512C1EEE@homedog.cs.tufts.edu> > * You create an MR for GHC that needs Haddock patched > * You open an MR on the Haddock mirror on the Haskell Gitlab, targeting > the ghc-head branch > * It gets merged > * You update the haddock submodule in the GHC git tree > * And done. Thank you!! I've created !5 on the Haddock mirror, and it's on the same branch as GHC's !7442 (wip/backend-as-record). Do I need to do anything else to get Gitlab to re-run CI on !7442? (As of 30 minutes ago, CI was failing because Haddock would not compile.) Norman > Le 19/04/2022 à 19:28, Norman Ramsey a écrit : > > GHC merge request !7442 changes the GHC API in a way that requires > > a one-line change in `utils/haddock`. What should I do with this? > > I can create an MR for the Haddock people, but I don't know how to > > mark it as something that should be applied at exactly the same > > time that Haddock transitions to GHC 9.6. Please advise. From gergo at erdi.hu Sat Apr 30 02:39:03 2022 From: gergo at erdi.hu (=?ISO-8859-2?Q?=C9RDI_Gerg=F5?=) Date: Sat, 30 Apr 2022 10:39:03 +0800 (+08) Subject: Extending call_args when specialising DFuns Message-ID: Hi, In GHC.Core.Opt.Specialise.specCalls, when specialising a DFun call, GHC extends the call_args with dummy UnspecArg elements, to make it trivially fully saturated. There's a Note describing this behaviour: """ Note [Specialising DFuns] ~~~~~~~~~~~~~~~~~~~~~~~~~ DFuns have a special sort of unfolding (DFunUnfolding), and these are hard to specialise a DFunUnfolding to give another DFunUnfolding unless the DFun is fully applied (#18120). So, in the case of DFunIds we simply extend the CallKey with trailing UnspecArgs, so we'll generate a rule that completely saturates the DFun. There is an ASSERT that checks this, in the DFunUnfolding case of GHC.Core.Unfold.specUnfolding. """ (note that the reference in the second paragraph is stale; it should point to GHC.Core.Unfold.Make.specUnfolding) So my question is, why UnspecArgs instead of UnspecTypes? Unless I'm missing something, a DFun can't have any term parameters, only type and dictionary ones. Changing the padding from UnspecArg to UnspecType doesn't break validate, which suggests that it is hard to even exercise this code path. I'm bringing this up because on the GHC fork that I'm working on, I have the specializer do more than vanilla GHC: on my fork, specialization of higher-kinded type variables is just as useful as specializing dictionaries. With that change, I can get GHC panics when padding DFun calls with UnspecArgs, but not when padding with UnspecTypes. Yes, this is a very weak argument for this change; what I'm looking for here is a discussion on what the padding should be, in vanilla GHC, from first principles. Thanks, Gergo From hecate at glitchbra.in Sat Apr 30 10:39:34 2022 From: hecate at glitchbra.in (=?UTF-8?Q?H=c3=a9cate?=) Date: Sat, 30 Apr 2022 12:39:34 +0200 Subject: Documenting primtypes, round 1: ByteArray# and Array# Message-ID: Hi everyone, With the sunny days back in this hemisphere, so do the documentation MRs. I have two primtypes for which I'd like some help / review / interesting information: * ByteArray#: This is mostly done, you can observe the current rendered draft documentation here: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/8067#note_425560    Please note that the free-floating "Byte Arrays" section of documentation cannot be exported or re-exported by GHC.Exts, so we're pretty much left with what's in the types' documentation; * Array#:  The ticket is here: https://gitlab.haskell.org/ghc/ghc/-/issues/21462    State of things: In terms of documentation, we have no documentation. Some stuff can be inferred from the SmallArray# haddocks but I doubt that every property / interesting usage / pitfall can be reasonable derived from putting ¬ at the beginning of the SmallArray# documentation. Now, on an unrelated note, I'm also wondering about the fate of GHC.Pack, for a number of reasons. You will find the ticket here: https://gitlab.haskell.org/ghc/ghc/-/issues/21461. My thanks to everyone who's helped me so far, with a special mention to bodigrim and koz ross. Cheers -- Hécate ✨ 🐦: @TechnoEmpress IRC: Hecate WWW: https://glitchbra.in RUN: BSD