From evan at evanrelf.com Thu Jul 1 01:56:07 2021 From: evan at evanrelf.com (Evan Relf) Date: Wed, 30 Jun 2021 18:56:07 -0700 Subject: Writing GHC plugin to modify AST despite failure to type-check Message-ID: <4b8514df-9496-4bde-ac7a-1ae2c5c58454@www.fastmail.com> Hi there, I would like to write a GHC plugin — initially as a learning exercise, and maybe real-world use if it works — that automatically applies `liftIO` to `IO` actions, to get the benefit that libraries like `lifted-base` or `relude` provide, but applied to all libraries, automatically. As a simple example, this program will not type-check by default, but it will if I can write my plugin: ``` program :: MonadIO m => m () program = putStrLn "Hello world!" ``` (That's `putStrLn :: String -> IO ()` from the regular `Prelude`) The idea is roughly, "if you see an `IO a` action where a `MonadIO m => m a` action is expected, add `liftIO` to make the `IO a` action type-check. But how to implement it? A type-checker plugin runs when type-checking fails, which is when I want to take action. But it doesn't seem to allow me to change the AST so I can add the `liftIO` function. So then I tried... A `typeCheckResultAction` plugin (for lack of a better name) does allow me to change the AST, and I can use the types to guide how I do it. But it doesn't seem to run if type-checking fails, which is exactly when I want to be adding the `liftIO`s. Am I missing something about GHC's plugin system that would allow me to do what I want? Whether that be AST manipulation in a type-checking plugin, or running the `typeCheckResultAction` despite type-checking failing. Or is AST manipulation with type information impossible if type-checking fails? This is my first foray into anything GHC-related, so I apologize if this doesn't make sense, or isn't the right place to ask. Thanks, - Evan From Gergo.Erdi at sc.com Thu Jul 1 07:04:14 2021 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Thu, 1 Jul 2021 07:04:14 +0000 Subject: Loading a typechecked module and then using it immediately as a package Message-ID: PUBLIC Unfortunately, that would take quite some extra effort. However, I think I have figured this out in the meantime: it seems it wasn't the FinderCache that needed invalidating, but the ModuleGraph. So now I have the following code for changing the home unit: ``` setHomeUnit :: (GhcMonad m) => UnitId -> m () setHomeUnit unitId = do modifySession $ \env -> env { hsc_dflags = (hsc_dflags env) { homeUnitId = unitId } } invalidateModSummaryCache invalidateModSummaryCache :: (GhcMonad m) => m () invalidateModSummaryCache = modifySession $ \env -> env { hsc_mod_graph = invalidateMG (hsc_mod_graph env) } where invalidateMG = mapMG invalidateMS invalidateMS ms = ms{ ms_hs_date = addUTCTime (-1) (ms_hs_date ms) } ``` Here, `invalidateModSummaryCache` is based on the one in the `GHC` module which doesn't export it. With the addition of `invalidateModSummaryCache` to `setHomeUnit`, I can now import `MyLib` from `Test` without using a package-qualified import. Adding or removing a `flushFinderCaches` call doesn’t seem to change anything. -----Original Message----- From: Matthew Pickering Sent: Wednesday, June 30, 2021 6:11 PM To: Erdi, Gergo Subject: [External] Re: Loading a typechecked module and then using it immediately as a package 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. Could you provide the code which is failing? Then it will be easier to fix. On Tue, Jun 29, 2021 at 12:00 PM Erdi, Gergo wrote: > > PUBLIC > > Should I? OK, I just tried calling `flushFinderCaches` after I change the home unit to `mainUnitId`, but I still get exactly the same behaviour: `findInstalledHomeModule` returns `InstalledFound` and things go downhill from there. > > -----Original Message----- > From: Matthew Pickering > Sent: Tuesday, June 29, 2021 6:34 PM > To: Erdi, Gergo > Cc: ghc-devs at haskell.org > Subject: [External] Re: Loading a typechecked module and then using it immediately as a package > > 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. > > > Are you clearing the FinderCache? > > On Tue, Jun 29, 2021 at 11:14 AM Erdi, Gergo wrote: > > > > PUBLIC > > > > I don't know yet what's going on, but one thing I did notice is that `findInstalledHomeModule` returns `InstalledFound` for `MyLib`, which doesn't sound right to me -- `MyLib` should come from the "fake-uid" unit, and `Test` is typechecked in the `mainUnitId`. > > > > -----Original Message----- > > From: Erdi, Gergo > > Sent: Tuesday, June 29, 2021 5:51 PM > > To: Matthew Pickering > > Subject: Re: Loading a typechecked module and then using it immediately as a package > > > > PUBLIC > > > > I tried moving `MyLib.hs` into a directory different than `Test.sh`, but the error message still refers to its correct location! So this error is not guessing the file name of where `MyLib.hs` could be loaded from; instead, it seems to refer correctly to where the module (previously loaded) was. Hmm. > > > > -----Original Message----- > > From: Matthew Pickering > > Sent: Tuesday, June 29, 2021 5:04 PM > > To: Erdi, Gergo > > Subject: [External] Re: Loading a typechecked module and then using it immediately as a package > > > > > > Do you have a `MyLib.hs` source file? If you move that somewhere else (another folder) then things might work? > > > > On Tue, Jun 29, 2021 at 9:41 AM Erdi, Gergo wrote: > > > > > > PUBLIC > > > > > > What's weird about it is that if I print the `moduleNameProvidersMap`, I can see `MyLib` inside, and it looks no different than any other module from e.g. `ghc-prim` that I can import into `Test.hs` without any package qualification. Also, why does the error message refer to the file name `input/MyLib.hs`? Why does GHC even know that that is where it would have to be loaded from, if it weren't to be used from an already loaded package? > > > > > > > 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. 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 zubin at well-typed.com Thu Jul 1 08:24:00 2021 From: zubin at well-typed.com (Zubin Duggal) Date: Thu, 1 Jul 2021 13:54:00 +0530 Subject: Writing GHC plugin to modify AST despite failure to type-check In-Reply-To: <4b8514df-9496-4bde-ac7a-1ae2c5c58454@www.fastmail.com> References: <4b8514df-9496-4bde-ac7a-1ae2c5c58454@www.fastmail.com> Message-ID: <20210701082400.5naohk44gcexk7g4@zubin-msi> You could set `-fdefer-type-errors` on the file, possibly using `dynflagsPlugin`. This will give your `typeCheckResultAction` an AST with all nodes containing type errors wrapped in an `evDelayedError` term. See Note [Deferring coercion errors to runtime] for more details. You can walk through the AST and replace these wrappers with `liftIO` (with the correct type and dictionary arguments) and things should work as you want. Of course, this will defer all type errors in the program, not just the ones that your plugin can solve. You could work around this by setting `log_action` to "upgrade" any type error warnings you didn't handle and arose as a result of `Reason Opt_DeferTypeErrors :: WarnReason` back to proper errors. From christiaan.baaij at gmail.com Thu Jul 1 08:54:12 2021 From: christiaan.baaij at gmail.com (Christiaan Baaij) Date: Thu, 1 Jul 2021 10:54:12 +0200 Subject: Writing GHC plugin to modify AST despite failure to type-check In-Reply-To: <20210701082400.5naohk44gcexk7g4@zubin-msi> References: <4b8514df-9496-4bde-ac7a-1ae2c5c58454@www.fastmail.com> <20210701082400.5naohk44gcexk7g4@zubin-msi> Message-ID: Another option is to use a constraint solver plugin to "tag" the locations with a coercion, and then use a CorePlugin [1] to replace the corresponding cast by a call to liftIO. I've created a constraint solver plugin to tag all the locations here: https://gist.github.com/christiaanb/5e2412bffce0fefb076d05198f94f2d8 As you can see, for: > {-# OPTIONS_GHC -fplugin=LiftIOPlugin -ddump-ds -ddump-tc -ddump-to-file #-} > module Test where > > import Control.Monad.IO.Class > > program :: MonadIO m => m () > program = putStrLn "Hello world!" it results in the following desugar output > program > = \ (@(m_a9Ky :: * -> *)) _ [Occ=Dead] -> > (break<0>() putStrLn (GHC.CString.unpackCString# "Hello world!"#)) > `cast` (Univ(representational plugin "tag_lift_io" > :: IO, m_a9Ky) <()>_N > :: IO () ~R# m_a9Ky ()) So now you'll need to make a CorePlugin to recognize that cast and replace it with an application with `liftIO`. Hopefully someone else can help you with suggestions on how to conjure a proper `liftIO` out of thin air at that point in the compiler pipeline. [1] https://downloads.haskell.org/ghc/9.0.1/docs/html/libraries/ghc-9.0.1/GHC-Driver-Plugins.html#t:CorePlugin On Thu, 1 Jul 2021 at 10:24, Zubin Duggal wrote: > You could set `-fdefer-type-errors` on the file, possibly using > `dynflagsPlugin`. This will give your `typeCheckResultAction` an AST > with all nodes containing type errors wrapped in an `evDelayedError` > term. See Note [Deferring coercion errors to runtime] for more details. > You can walk through the AST and replace these wrappers with `liftIO` > (with the correct type and dictionary arguments) and things should > work as you want. > > Of course, this will defer all type errors in the program, not just the > ones that your plugin can solve. You could work around this by setting > `log_action` to "upgrade" any type error warnings you didn't handle and > arose as a result of `Reason Opt_DeferTypeErrors :: WarnReason` back to > proper errors. > _______________________________________________ > 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 Thu Jul 1 12:37:27 2021 From: zubin at well-typed.com (Zubin Duggal) Date: Thu, 1 Jul 2021 18:07:27 +0530 Subject: Writing GHC plugin to modify AST despite failure to type-check In-Reply-To: References: <4b8514df-9496-4bde-ac7a-1ae2c5c58454@www.fastmail.com> <20210701082400.5naohk44gcexk7g4@zubin-msi> Message-ID: <20210701123727.y5iqvr5g3wa3vifb@zubin-msi> An issue with this approach is that it fails if you have a concrete monad instead of an mtl-style function. For example, with newtype MyIO a = MyIO (IO a) deriving newtype (Functor, Applicative, Monad, MonadIO) program :: MyIO () program = putStrLn "Hello world!" GHC will reject the program because it can't unify `IO` and `MyIO` before it can even get to the constraint solver plugin. In general, implementing a plugin like this is a nice way to understand and familiarise yourself with plugins and the GHC API, but for practical purposes it would be best to use something like the `lifted-base` or `unliftio` libraries to access lifted version of common IO operations. On 21/07/01 10:54, Christiaan Baaij wrote: >Another option is to use a constraint solver plugin to "tag" the locations >with a coercion, and then use a CorePlugin [1] to replace the corresponding >cast by a call to liftIO. >I've created a constraint solver plugin to tag all the locations here: >https://gist.github.com/christiaanb/5e2412bffce0fefb076d05198f94f2d8 > >As you can see, for: > >> {-# OPTIONS_GHC -fplugin=LiftIOPlugin -ddump-ds -ddump-tc -ddump-to-file >#-} >> module Test where >> >> import Control.Monad.IO.Class >> >> program :: MonadIO m => m () >> program = putStrLn "Hello world!" > >it results in the following desugar output > >> program >> = \ (@(m_a9Ky :: * -> *)) _ [Occ=Dead] -> >> (break<0>() putStrLn (GHC.CString.unpackCString# "Hello world!"#)) >> `cast` (Univ(representational plugin "tag_lift_io" >> :: IO, m_a9Ky) <()>_N >> :: IO () ~R# m_a9Ky ()) > >So now you'll need to make a CorePlugin to recognize that cast and replace >it with an application with `liftIO`. >Hopefully someone else can help you with suggestions on how to conjure a >proper `liftIO` out of thin air at that point in the compiler pipeline. > >[1] >https://downloads.haskell.org/ghc/9.0.1/docs/html/libraries/ghc-9.0.1/GHC-Driver-Plugins.html#t:CorePlugin > >On Thu, 1 Jul 2021 at 10:24, Zubin Duggal wrote: > >> You could set `-fdefer-type-errors` on the file, possibly using >> `dynflagsPlugin`. This will give your `typeCheckResultAction` an AST >> with all nodes containing type errors wrapped in an `evDelayedError` >> term. See Note [Deferring coercion errors to runtime] for more details. >> You can walk through the AST and replace these wrappers with `liftIO` >> (with the correct type and dictionary arguments) and things should >> work as you want. >> >> Of course, this will defer all type errors in the program, not just the >> ones that your plugin can solve. You could work around this by setting >> `log_action` to "upgrade" any type error warnings you didn't handle and >> arose as a result of `Reason Opt_DeferTypeErrors :: WarnReason` back to >> proper errors. >> _______________________________________________ >> 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 zubin at well-typed.com Thu Jul 1 12:57:20 2021 From: zubin at well-typed.com (Zubin Duggal) Date: Thu, 1 Jul 2021 18:27:20 +0530 Subject: Writing GHC plugin to modify AST despite failure to type-check In-Reply-To: <20210701123727.y5iqvr5g3wa3vifb@zubin-msi> References: <4b8514df-9496-4bde-ac7a-1ae2c5c58454@www.fastmail.com> <20210701082400.5naohk44gcexk7g4@zubin-msi> <20210701123727.y5iqvr5g3wa3vifb@zubin-msi> Message-ID: <20210701125720.ct4rvtc35y2g7x4q@zubin-msi> I was wrong, the constraint solver plugin is in fact called upon to solve constraints like `MyIO () ~ IO ()`, so Christiaan's method would work with suitable modifications to the plugin. On 21/07/01 18:07, Zubin Duggal wrote: >An issue with this approach is that it fails if you have a concrete >monad instead of an mtl-style function. > >For example, with > >newtype MyIO a = MyIO (IO a) > deriving newtype (Functor, Applicative, Monad, MonadIO) > >program :: MyIO () >program = putStrLn "Hello world!" > >GHC will reject the program because it can't unify `IO` and `MyIO` >before it can even get to the constraint solver plugin. > >In general, implementing a plugin like this is a nice way to understand >and familiarise yourself with plugins and the GHC API, but for practical >purposes it would be best to use something like the `lifted-base` or >`unliftio` libraries to access lifted version of common IO operations. > >On 21/07/01 10:54, Christiaan Baaij wrote: >>Another option is to use a constraint solver plugin to "tag" the locations >>with a coercion, and then use a CorePlugin [1] to replace the corresponding >>cast by a call to liftIO. >>I've created a constraint solver plugin to tag all the locations here: >>https://gist.github.com/christiaanb/5e2412bffce0fefb076d05198f94f2d8 >> >>As you can see, for: >> >>>{-# OPTIONS_GHC -fplugin=LiftIOPlugin -ddump-ds -ddump-tc -ddump-to-file >>#-} >>>module Test where >>> >>>import Control.Monad.IO.Class >>> >>>program :: MonadIO m => m () >>>program = putStrLn "Hello world!" >> >>it results in the following desugar output >> >>>program >>> = \ (@(m_a9Ky :: * -> *)) _ [Occ=Dead] -> >>> (break<0>() putStrLn (GHC.CString.unpackCString# "Hello world!"#)) >>> `cast` (Univ(representational plugin "tag_lift_io" >>> :: IO, m_a9Ky) <()>_N >>> :: IO () ~R# m_a9Ky ()) >> >>So now you'll need to make a CorePlugin to recognize that cast and replace >>it with an application with `liftIO`. >>Hopefully someone else can help you with suggestions on how to conjure a >>proper `liftIO` out of thin air at that point in the compiler pipeline. >> >>[1] >>https://downloads.haskell.org/ghc/9.0.1/docs/html/libraries/ghc-9.0.1/GHC-Driver-Plugins.html#t:CorePlugin >> >>On Thu, 1 Jul 2021 at 10:24, Zubin Duggal wrote: >> >>>You could set `-fdefer-type-errors` on the file, possibly using >>>`dynflagsPlugin`. This will give your `typeCheckResultAction` an AST >>>with all nodes containing type errors wrapped in an `evDelayedError` >>>term. See Note [Deferring coercion errors to runtime] for more details. >>>You can walk through the AST and replace these wrappers with `liftIO` >>>(with the correct type and dictionary arguments) and things should >>>work as you want. >>> >>>Of course, this will defer all type errors in the program, not just the >>>ones that your plugin can solve. You could work around this by setting >>>`log_action` to "upgrade" any type error warnings you didn't handle and >>>arose as a result of `Reason Opt_DeferTypeErrors :: WarnReason` back to >>>proper errors. >>>_______________________________________________ >>>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 From jeff.young at tweag.io Fri Jul 2 01:36:20 2021 From: jeff.young at tweag.io (Young, Jeff) Date: Thu, 1 Jul 2021 18:36:20 -0700 Subject: Trying to speedup GHC compile times...Help! Message-ID: Hi ghc devs, I'm a long-time Haskeller but am just getting into GHC development. I started a 12 week internship at Tweag I/O under Richard Eisenberg this week with the singular goal to speedup GHC compile times. I'm specifically looking to contribute to ghc issues 18541 and 18535 . So I thought I would reach out to the community to get some direction on issues/features/problems to tackle in the pursuit of faster compilation times. This is a full time internship and so I think there is a real opportunity to nail down a deliverable for the community, but I want to get some guidance from the experts (you fine people!) before going down a rabbit hole. To be specific I'm looking for lingering items such as: 1. It would be great if we had but no one has time. 2. Primop foo is half complete but is the right type for . 3. Swap to an array-like type *non-incrementally*, that is, establish a patch that rips out the previous type and replaces it with the array-like across the entire compiler, rather than module-by-module. Point 2 is a specific reference to MR 3571 but I'm unsure of the status and etiquette around MRs, and I'm unsure exactly how fulfilling the todos at the end of that MR would aid in faster compilation times (and if there is evidence to that effect somewhere). Thanks for the help! - Jeff -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben at smart-cactus.org Fri Jul 2 02:15:37 2021 From: ben at smart-cactus.org (Ben Gamari) Date: Thu, 01 Jul 2021 22:15:37 -0400 Subject: Trying to speedup GHC compile times...Help! In-Reply-To: References: Message-ID: <87v95txxzl.fsf@smart-cactus.org> "Young, Jeff" writes: > Hi ghc devs, > > I'm a long-time Haskeller but am just getting into GHC development. I > started a 12 week internship at Tweag I/O under Richard Eisenberg this week > with the singular goal to speedup GHC compile times. I'm specifically > looking to contribute to ghc issues 18541 > and 18535 > . So I thought I would > reach out to the community to get some direction on > issues/features/problems to tackle in the pursuit of faster compilation > times. This is a full time internship and so I think there is a real > opportunity to nail down a deliverable for the community, but I want to get > some guidance from the experts (you fine people!) before going down a > rabbit hole. > > To be specific I'm looking for lingering items such as: > 1. It would be great if we had but no one has time. > 2. Primop foo is half complete but is the right type for > . > 3. Swap to an array-like type *non-incrementally*, that is, > establish a patch that rips out the previous type and replaces it with the > array-like across the entire compiler, rather than module-by-module. > > Point 2 is a specific reference to MR 3571 > but I'm unsure > of the status and etiquette around MRs, and I'm unsure exactly how > fulfilling the todos at the end of that MR would aid in faster compilation > times (and if there is evidence to that effect somewhere). > Hi Jeff, Indeed I'm a bit skeptical that (2) will produce a meaningful compile-time improvement on typical programs. I would likely not prioritise this if the goal is compile-time in particular. A few people (namely Sebastian Graf and Andreas Klebinger) have thought about (3) in the past (e.g. for the arguments of TyConApps); preliminary experiments suggest that it's not as clear a win as one might expect, although AFAIK no one has tried to optimise pattern matching on the head, which may help matters (Sebastian has thought about this). One thing area where I feel a bit of attention may be useful is in the performance of substitution. In particular, tracking "taintedness" of the substitution result (as suggested in #19537) will help reduce garbage produced by substitution and potentially reduce compiler residency. Another related class of ideas can be found in #19538, which suggests that we try deferring substitution (or, alternatively, annotation expressions with free variable sets). The payoff here is far less certain that the taintedness idea and consequently I would only explore it after doing the former. This is all that comes to mind at the moment. I'll continue pondering other ideas, however. 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 simonpj at microsoft.com Fri Jul 2 08:08:39 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Fri, 2 Jul 2021 08:08:39 +0000 Subject: Trying to speedup GHC compile times...Help! In-Reply-To: References: Message-ID: Jeff Great stuff! Welcome. I strongly urge you to keep a constantly-update status wiki page, which lists the ideas you are working on, and points to relevant resources and tickets. An email thread like this is a good way to gather ideas, but NOT a good way to organise and track them. Looking carefully at profiles is a good plan. That's the hard data! I think that some careful investigation of IntMap (at least the bits that GHC uses heavily) would be a good idea. Clearly we spend a lot of time in these maps, so speedups here will yield a lot of benefit. Look at the heavy hitters from the profile, stare at the Core code and see if it's s good as it can be. For example, Sebastian discovered a strange infelicity in IntMap.lookup, which I've documented in a new ticket https://gitlab.haskell.org/ghc/ghc/-/issues/20069 I think it'd also be worth measuring how unbalanced our IntMap trees get. See https://gitlab.haskell.org/ghc/ghc/-/issues/19820 The speculation there is that we are getting very unbalanced trees. So measure it! If it's true, we could improve matters by using a different IntMap; or maybe by scrambling the key a bit --- see the ticket. Simon From: ghc-devs On Behalf Of Young, Jeff Sent: 02 July 2021 02:36 To: ghc-devs at haskell.org Subject: Trying to speedup GHC compile times...Help! Hi ghc devs, I'm a long-time Haskeller but am just getting into GHC development. I started a 12 week internship at Tweag I/O under Richard Eisenberg this week with the singular goal to speedup GHC compile times. I'm specifically looking to contribute to ghc issues 18541 and 18535. So I thought I would reach out to the community to get some direction on issues/features/problems to tackle in the pursuit of faster compilation times. This is a full time internship and so I think there is a real opportunity to nail down a deliverable for the community, but I want to get some guidance from the experts (you fine people!) before going down a rabbit hole. To be specific I'm looking for lingering items such as: 1. It would be great if we had but no one has time. 2. Primop foo is half complete but is the right type for . 3. Swap to an array-like type non-incrementally, that is, establish a patch that rips out the previous type and replaces it with the array-like across the entire compiler, rather than module-by-module. Point 2 is a specific reference to MR 3571 but I'm unsure of the status and etiquette around MRs, and I'm unsure exactly how fulfilling the todos at the end of that MR would aid in faster compilation times (and if there is evidence to that effect somewhere). Thanks for the help! - Jeff -------------- next part -------------- An HTML attachment was scrubbed... URL: From lists at richarde.dev Fri Jul 2 13:26:21 2021 From: lists at richarde.dev (Richard Eisenberg) Date: Fri, 2 Jul 2021 13:26:21 +0000 Subject: Trying to speedup GHC compile times...Help! In-Reply-To: References: Message-ID: <010f017a67661517-ec66b203-b4f2-45ba-8481-0f9088c78367-000000@us-east-2.amazonses.com> One piece I'm curious about, reading this thread: why do we have so many IntMaps and operations on them? Name lookup is a fundamental operation a compiler must do, and that would use an IntMap: good. But maybe there are other IntMaps used that are less necessary. A key example: whenever we do substitution, we track an InScopeSet, which is really just an IntMap. This InScopeSet remembers the name of all variables in scope, useful when we need to create a new variable name (this is done by uniqAway). Yet perhaps the tracking of these in-scope variables is very expensive and comprises much of the IntMap time. Might it be better just to always work in a monad capable of giving fresh names? We actually don't even need a monad, if that's too annoying. Instead, we could just pass around an infinite list of fresh uniques. This would still be clutterful, but if it grants us a big speed improvement, the clutter might be worth it. The high-level piece here is that there may be good things that come from understanding where these IntMaps arise. Richard > On Jul 2, 2021, at 4:08 AM, Simon Peyton Jones via ghc-devs wrote: > > Jeff > > Great stuff! Welcome. > > I strongly urge you to keep a constantly-update status wiki page, which lists the ideas you are working on, and points to relevant resources and tickets. An email thread like this is a good way to gather ideas, but NOT a good way to organise and track them. > > Looking carefully at profiles is a good plan. That’s the hard data! > > I think that some careful investigation of IntMap (at least the bits that GHC uses heavily) would be a good idea. Clearly we spend a lot of time in these maps, so speedups here will yield a lot of benefit. Look at the heavy hitters from the profile, stare at the Core code and see if it’s s good as it can be. > > For example, Sebastian discovered a strange infelicity in IntMap.lookup, which I’ve documented in a new ticket > https://gitlab.haskell.org/ghc/ghc/-/issues/20069 > > I think it’d also be worth measuring how unbalanced our IntMap trees get. See > https://gitlab.haskell.org/ghc/ghc/-/issues/19820 > The speculation there is that we are getting very unbalanced trees. So measure it! If it’s true, we could improve matters by using a different IntMap; or maybe by scrambling the key a bit --- see the ticket. > > Simon > > From: ghc-devs On Behalf Of Young, Jeff > Sent: 02 July 2021 02:36 > To: ghc-devs at haskell.org > Subject: Trying to speedup GHC compile times...Help! > > Hi ghc devs, > > > > I'm a long-time Haskeller but am just getting into GHC development. I started a 12 week internship at Tweag I/O under Richard Eisenberg this week with the singular goal to speedup GHC compile times. I'm specifically looking to contribute to ghc issues 18541 and 18535 . So I thought I would reach out to the community to get some direction on issues/features/problems to tackle in the pursuit of faster compilation times. This is a full time internship and so I think there is a real opportunity to nail down a deliverable for the community, but I want to get some guidance from the experts (you fine people!) before going down a rabbit hole. > > > > To be specific I'm looking for lingering items such as: > > 1. It would be great if we had but no one has time. > > 2. Primop foo is half complete but is the right type for . > > 3. Swap to an array-like type non-incrementally, that is, establish a patch that rips out the previous type and replaces it with the array-like across the entire compiler, rather than module-by-module. > > > > Point 2 is a specific reference to MR 3571 but I'm unsure of the status and etiquette around MRs, and I'm unsure exactly how fulfilling the todos at the end of that MR would aid in faster compilation times (and if there is evidence to that effect somewhere). > > > > Thanks for the help! > > > > - Jeff > > > > > > > > _______________________________________________ > 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 simonpj at microsoft.com Fri Jul 2 14:10:24 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Fri, 2 Jul 2021 14:10:24 +0000 Subject: Trying to speedup GHC compile times...Help! In-Reply-To: <010f017a67661517-ec66b203-b4f2-45ba-8481-0f9088c78367-000000@us-east-2.amazonses.com> References: <010f017a67661517-ec66b203-b4f2-45ba-8481-0f9088c78367-000000@us-east-2.amazonses.com> Message-ID: There are lot of places where it would be pretty tiresome to plumb a unique supply guaranteed unique from every other. I think the current setup works pretty well - but I bet we can squeeze cycles out of its implementation. Simon From: Richard Eisenberg Sent: 02 July 2021 14:26 To: Simon Peyton Jones Cc: Young, Jeff ; ghc-devs at haskell.org Subject: Re: Trying to speedup GHC compile times...Help! One piece I'm curious about, reading this thread: why do we have so many IntMaps and operations on them? Name lookup is a fundamental operation a compiler must do, and that would use an IntMap: good. But maybe there are other IntMaps used that are less necessary. A key example: whenever we do substitution, we track an InScopeSet, which is really just an IntMap. This InScopeSet remembers the name of all variables in scope, useful when we need to create a new variable name (this is done by uniqAway). Yet perhaps the tracking of these in-scope variables is very expensive and comprises much of the IntMap time. Might it be better just to always work in a monad capable of giving fresh names? We actually don't even need a monad, if that's too annoying. Instead, we could just pass around an infinite list of fresh uniques. This would still be clutterful, but if it grants us a big speed improvement, the clutter might be worth it. The high-level piece here is that there may be good things that come from understanding where these IntMaps arise. Richard On Jul 2, 2021, at 4:08 AM, Simon Peyton Jones via ghc-devs > wrote: Jeff Great stuff! Welcome. I strongly urge you to keep a constantly-update status wiki page, which lists the ideas you are working on, and points to relevant resources and tickets. An email thread like this is a good way to gather ideas, but NOT a good way to organise and track them. Looking carefully at profiles is a good plan. That's the hard data! I think that some careful investigation of IntMap (at least the bits that GHC uses heavily) would be a good idea. Clearly we spend a lot of time in these maps, so speedups here will yield a lot of benefit. Look at the heavy hitters from the profile, stare at the Core code and see if it's s good as it can be. For example, Sebastian discovered a strange infelicity in IntMap.lookup, which I've documented in a new ticket https://gitlab.haskell.org/ghc/ghc/-/issues/20069 I think it'd also be worth measuring how unbalanced our IntMap trees get. See https://gitlab.haskell.org/ghc/ghc/-/issues/19820 The speculation there is that we are getting very unbalanced trees. So measure it! If it's true, we could improve matters by using a different IntMap; or maybe by scrambling the key a bit --- see the ticket. Simon From: ghc-devs > On Behalf Of Young, Jeff Sent: 02 July 2021 02:36 To: ghc-devs at haskell.org Subject: Trying to speedup GHC compile times...Help! Hi ghc devs, I'm a long-time Haskeller but am just getting into GHC development. I started a 12 week internship at Tweag I/O under Richard Eisenberg this week with the singular goal to speedup GHC compile times. I'm specifically looking to contribute to ghc issues 18541and 18535. So I thought I would reach out to the community to get some direction on issues/features/problems to tackle in the pursuit of faster compilation times. This is a full time internship and so I think there is a real opportunity to nail down a deliverable for the community, but I want to get some guidance from the experts (you fine people!) before going down a rabbit hole. To be specific I'm looking for lingering items such as: 1. It would be great if we had but no one has time. 2. Primop foo is half complete but is the right type for . 3. Swap to an array-like type non-incrementally, that is, establish a patch that rips out the previous type and replaces it with the array-like across the entire compiler, rather than module-by-module. Point 2 is a specific reference to MR 3571 but I'm unsure of the status and etiquette around MRs, and I'm unsure exactly how fulfilling the todos at the end of that MR would aid in faster compilation times (and if there is evidence to that effect somewhere). Thanks for the help! - Jeff _______________________________________________ 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 ietf-dane at dukhovni.org Fri Jul 2 14:30:26 2021 From: ietf-dane at dukhovni.org (Viktor Dukhovni) Date: Fri, 2 Jul 2021 10:30:26 -0400 Subject: Trying to speedup GHC compile times...Help! In-Reply-To: References: Message-ID: On Fri, Jul 02, 2021 at 08:08:39AM +0000, Simon Peyton Jones via ghc-devs wrote: > I strongly urge you to keep a constantly-update status wiki page, > which lists the ideas you are working on, and points to relevant > resources and tickets. An email thread like this is a good way to > gather ideas, but NOT a good way to organise and track them. I remain curious as to whether "Scrap your type applications" is worth a second look. There are edge cases in which compile time blowup is a result of type blowup (as opposed to code blowup via inlining). Might GHC have changed enough in the last ~5 years to make it now "another compiler": https://www.microsoft.com/en-us/research/wp-content/uploads/2016/07/if.pdf (Section 4.4): Overall, allocation decreased by a mere 0.1%. The largest reduction was 4%, and the largest increase was 12%, but 120 of the 130 modules showed a change of less than 1%. Presumably, the reduction in work that arises from smaller types is balanced by the additional overheads of SystemIF. On this evidence, the additional complexity introduced by the new reduction rules does not pay its way. Nevertheless, these are matters that are dominated by nitty-gritty representation details, and the balance might well be different in another compiler. Could it be that some of the more compile time intensive packages on hackage (aeson, vector, ...) would benefit more than the various modules in base? Wild speculation aside, of course finding and fixing inefficiencies in the implementation of existing common primitive should be a win across the board, and should not require changing major compiler design features, just leaner code. -- Viktor. From christiaan.baaij at gmail.com Fri Jul 2 14:38:22 2021 From: christiaan.baaij at gmail.com (Christiaan Baaij) Date: Fri, 2 Jul 2021 16:38:22 +0200 Subject: Trying to speedup GHC compile times...Help! In-Reply-To: References: <010f017a67661517-ec66b203-b4f2-45ba-8481-0f9088c78367-000000@us-east-2.amazonses.com> Message-ID: Somewhat off-topic: does GHC no longer use "the rapier"? I thought the InScopeSet was needed to check that we can safely skip on extending the substitution as you go under binders when the binder is not in the InScopeSet (naively you would always have to rename binders, and thus extend the substitution, in order to avoid capture as you go under binders). i.e. the IntMap is not just used to generate new variable names, but to ensure the compiler does less work in the form of doing fewer substitutions. On Fri, 2 Jul 2021 at 16:12, Simon Peyton Jones via ghc-devs < ghc-devs at haskell.org> wrote: > There are lot of places where it would be pretty tiresome to plumb a > unique supply guaranteed unique from every other. I think the current > setup works pretty well – but I bet we can squeeze cycles out of its > implementation. > > > > Simon > > > > *From:* Richard Eisenberg > *Sent:* 02 July 2021 14:26 > *To:* Simon Peyton Jones > *Cc:* Young, Jeff ; ghc-devs at haskell.org > *Subject:* Re: Trying to speedup GHC compile times...Help! > > > > One piece I'm curious about, reading this thread: why do we have so many > IntMaps and operations on them? Name lookup is a fundamental operation a > compiler must do, and that would use an IntMap: good. But maybe there are > other IntMaps used that are less necessary. A key example: whenever we do > substitution, we track an InScopeSet, which is really just an IntMap. This > InScopeSet remembers the name of all variables in scope, useful when we > need to create a new variable name (this is done by uniqAway). Yet perhaps > the tracking of these in-scope variables is very expensive and comprises > much of the IntMap time. Might it be better just to always work in a monad > capable of giving fresh names? We actually don't even need a monad, if > that's too annoying. Instead, we could just pass around an infinite list of > fresh uniques. This would still be clutterful, but if it grants us a big > speed improvement, the clutter might be worth it. > > > > The high-level piece here is that there may be good things that come from > understanding where these IntMaps arise. > > > > Richard > > > > On Jul 2, 2021, at 4:08 AM, Simon Peyton Jones via ghc-devs < > ghc-devs at haskell.org> wrote: > > > > Jeff > > > > Great stuff! Welcome. > > > > I strongly urge you to keep a constantly-update status wiki page, which > lists the ideas you are working on, and points to relevant resources and > tickets. An email thread like this is a good way to gather ideas, but NOT > a good way to organise and track them. > > > > Looking carefully at profiles is a good plan. That’s the hard data! > > > > I think that some careful investigation of IntMap (at least the bits that > GHC uses heavily) would be a good idea. Clearly we spend a lot of time in > these maps, so speedups here will yield a lot of benefit. Look at the > heavy hitters from the profile, stare at the Core code and see if it’s s > good as it can be. > > > > For example, Sebastian discovered a strange infelicity in IntMap.lookup, > which I’ve documented in a new ticket > > https://gitlab.haskell.org/ghc/ghc/-/issues/20069 > > > > > I think it’d also be worth measuring how unbalanced our IntMap trees get. > See > > https://gitlab.haskell.org/ghc/ghc/-/issues/19820 > > > The speculation there is that we are getting very unbalanced trees. So > measure it! If it’s true, we could improve matters by using a different > IntMap; or maybe by scrambling the key a bit --- see the ticket. > > > > Simon > > > > *From:* ghc-devs *On Behalf Of *Young, Jeff > *Sent:* 02 July 2021 02:36 > *To:* ghc-devs at haskell.org > *Subject:* Trying to speedup GHC compile times...Help! > > > > Hi ghc devs, > > > > I'm a long-time Haskeller but am just getting into GHC development. I > started a 12 week internship at Tweag I/O under Richard Eisenberg this week > with the singular goal to speedup GHC compile times. I'm specifically > looking to contribute to ghc issues 18541 > > and 18535 > . > So I thought I would reach out to the community to get some direction on > issues/features/problems to tackle in the pursuit of faster compilation > times. This is a full time internship and so I think there is a real > opportunity to nail down a deliverable for the community, but I want to get > some guidance from the experts (you fine people!) before going down a > rabbit hole. > > > > To be specific I'm looking for lingering items such as: > > 1. It would be great if we had but no one has time. > > 2. Primop foo is half complete but is the right type for > . > > 3. Swap to an array-like type *non-incrementally*, that is, > establish a patch that rips out the previous type and replaces it with the > array-like across the entire compiler, rather than module-by-module. > > > > Point 2 is a specific reference to MR 3571 > > but I'm unsure of the status and etiquette around MRs, and I'm unsure > exactly how fulfilling the todos at the end of that MR would aid in faster > compilation times (and if there is evidence to that effect somewhere). > > > > Thanks for the help! > > > > - Jeff > > > > > > > > _______________________________________________ > 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 simonpj at microsoft.com Fri Jul 2 15:03:27 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Fri, 2 Jul 2021 15:03:27 +0000 Subject: Trying to speedup GHC compile times...Help! In-Reply-To: References: <010f017a67661517-ec66b203-b4f2-45ba-8481-0f9088c78367-000000@us-east-2.amazonses.com> Message-ID: GHC precisely use "the rapier". S From: Christiaan Baaij Sent: 02 July 2021 15:38 To: Simon Peyton Jones Cc: Richard Eisenberg ; Young, Jeff ; ghc-devs at haskell.org Subject: Re: Trying to speedup GHC compile times...Help! Somewhat off-topic: does GHC no longer use "the rapier"? I thought the InScopeSet was needed to check that we can safely skip on extending the substitution as you go under binders when the binder is not in the InScopeSet (naively you would always have to rename binders, and thus extend the substitution, in order to avoid capture as you go under binders). i.e. the IntMap is not just used to generate new variable names, but to ensure the compiler does less work in the form of doing fewer substitutions. On Fri, 2 Jul 2021 at 16:12, Simon Peyton Jones via ghc-devs > wrote: There are lot of places where it would be pretty tiresome to plumb a unique supply guaranteed unique from every other. I think the current setup works pretty well - but I bet we can squeeze cycles out of its implementation. Simon From: Richard Eisenberg > Sent: 02 July 2021 14:26 To: Simon Peyton Jones > Cc: Young, Jeff >; ghc-devs at haskell.org Subject: Re: Trying to speedup GHC compile times...Help! One piece I'm curious about, reading this thread: why do we have so many IntMaps and operations on them? Name lookup is a fundamental operation a compiler must do, and that would use an IntMap: good. But maybe there are other IntMaps used that are less necessary. A key example: whenever we do substitution, we track an InScopeSet, which is really just an IntMap. This InScopeSet remembers the name of all variables in scope, useful when we need to create a new variable name (this is done by uniqAway). Yet perhaps the tracking of these in-scope variables is very expensive and comprises much of the IntMap time. Might it be better just to always work in a monad capable of giving fresh names? We actually don't even need a monad, if that's too annoying. Instead, we could just pass around an infinite list of fresh uniques. This would still be clutterful, but if it grants us a big speed improvement, the clutter might be worth it. The high-level piece here is that there may be good things that come from understanding where these IntMaps arise. Richard On Jul 2, 2021, at 4:08 AM, Simon Peyton Jones via ghc-devs > wrote: Jeff Great stuff! Welcome. I strongly urge you to keep a constantly-update status wiki page, which lists the ideas you are working on, and points to relevant resources and tickets. An email thread like this is a good way to gather ideas, but NOT a good way to organise and track them. Looking carefully at profiles is a good plan. That's the hard data! I think that some careful investigation of IntMap (at least the bits that GHC uses heavily) would be a good idea. Clearly we spend a lot of time in these maps, so speedups here will yield a lot of benefit. Look at the heavy hitters from the profile, stare at the Core code and see if it's s good as it can be. For example, Sebastian discovered a strange infelicity in IntMap.lookup, which I've documented in a new ticket https://gitlab.haskell.org/ghc/ghc/-/issues/20069 I think it'd also be worth measuring how unbalanced our IntMap trees get. See https://gitlab.haskell.org/ghc/ghc/-/issues/19820 The speculation there is that we are getting very unbalanced trees. So measure it! If it's true, we could improve matters by using a different IntMap; or maybe by scrambling the key a bit --- see the ticket. Simon From: ghc-devs > On Behalf Of Young, Jeff Sent: 02 July 2021 02:36 To: ghc-devs at haskell.org Subject: Trying to speedup GHC compile times...Help! Hi ghc devs, I'm a long-time Haskeller but am just getting into GHC development. I started a 12 week internship at Tweag I/O under Richard Eisenberg this week with the singular goal to speedup GHC compile times. I'm specifically looking to contribute to ghc issues 18541and 18535. So I thought I would reach out to the community to get some direction on issues/features/problems to tackle in the pursuit of faster compilation times. This is a full time internship and so I think there is a real opportunity to nail down a deliverable for the community, but I want to get some guidance from the experts (you fine people!) before going down a rabbit hole. To be specific I'm looking for lingering items such as: 1. It would be great if we had but no one has time. 2. Primop foo is half complete but is the right type for . 3. Swap to an array-like type non-incrementally, that is, establish a patch that rips out the previous type and replaces it with the array-like across the entire compiler, rather than module-by-module. Point 2 is a specific reference to MR 3571 but I'm unsure of the status and etiquette around MRs, and I'm unsure exactly how fulfilling the todos at the end of that MR would aid in faster compilation times (and if there is evidence to that effect somewhere). Thanks for the help! - Jeff _______________________________________________ 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 lists at richarde.dev Sat Jul 3 20:22:04 2021 From: lists at richarde.dev (Richard Eisenberg) Date: Sat, 3 Jul 2021 20:22:04 +0000 Subject: Breaking changes to the base library In-Reply-To: References: <87zgvkyd6e.fsf@smart-cactus.org> Message-ID: <010f017a6e090ab3-2c4b9a5d-9090-47b7-a6bc-9d6218f385bc-000000@us-east-2.amazonses.com> > On Jun 20, 2021, at 10:57 AM, Edward Kmett wrote: > > We definitely need to do more to communicate that this is changing and how users should adjust their code to suit. Yes, I agree! Who is responsible for actually doing this communication, though? I don't think it should just be tucked into the release notes. This will be a major source of breakage in the next release. Richard -------------- next part -------------- An HTML attachment was scrubbed... URL: From zubin at well-typed.com Sat Jul 3 20:28:23 2021 From: zubin at well-typed.com (Zubin Duggal) Date: Sun, 4 Jul 2021 01:58:23 +0530 Subject: Breaking changes to the base library In-Reply-To: <010f017a6e090ab3-2c4b9a5d-9090-47b7-a6bc-9d6218f385bc-000000@us-east-2.amazonses.com> References: <87zgvkyd6e.fsf@smart-cactus.org> <010f017a6e090ab3-2c4b9a5d-9090-47b7-a6bc-9d6218f385bc-000000@us-east-2.amazonses.com> Message-ID: <20210703202823.4rtuqd66vdv6l27r@zubin-msi> See https://gitlab.haskell.org/ghc/ghc/-/issues/20025 for further discussion. On 21/07/03 20:22, Richard Eisenberg wrote: > > >> On Jun 20, 2021, at 10:57 AM, Edward Kmett wrote: >> >> We definitely need to do more to communicate that this is changing and how users should adjust their code to suit. > >Yes, I agree! Who is responsible for actually doing this communication, though? I don't think it should just be tucked into the release notes. This will be a major source of breakage in the next release. > >Richard >_______________________________________________ >ghc-devs mailing list >ghc-devs at haskell.org >http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From matthewtpickering at gmail.com Mon Jul 5 07:47:21 2021 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Mon, 5 Jul 2021 08:47:21 +0100 Subject: Trying to speedup GHC compile times...Help! In-Reply-To: References: <010f017a67661517-ec66b203-b4f2-45ba-8481-0f9088c78367-000000@us-east-2.amazonses.com> Message-ID: Hi Jeff, Welcome to ghc-devs and looking forward to seeing you around. If you are not already aware, there are a set of grafana dashboards for tracking compiler performance. Ones of particular interest might be the `head.hackage` and `Cabal test` dashboards. * Head.hackage (https://grafana.gitlab.haskell.org/d/7T7oEMlMz/head-hackage-performance?orgId=2&from=now-30d&to=now) * Cabal test (https://grafana.gitlab.haskell.org/d/Zf4HCvz7z/cabal-test?orgId=2) Looking at the data it's clear that simplification and code generation are the two expensive phases in compilation. So I think some useful things to look at would be: 1. Avoiding pointless work when substituting as suggested by Ben could reduce allocations significantly in the simplifier. 2. Looking into optimising the pretty printing during code generation. Ticky profiles indicate that certain pretty printer functions are called many times and allocate a lot. (I don't have a ticky profile to hand) 3. Modify the `perf` and `head.hackage` pipeline stages to fetch recent perf stats from the database and print a comparison to the baseline. Cheers, Matt On Fri, Jul 2, 2021 at 4:05 PM Simon Peyton Jones via ghc-devs wrote: > > GHC precisely use “the rapier”. > > > > S > > > > From: Christiaan Baaij > Sent: 02 July 2021 15:38 > To: Simon Peyton Jones > Cc: Richard Eisenberg ; Young, Jeff ; ghc-devs at haskell.org > Subject: Re: Trying to speedup GHC compile times...Help! > > > > Somewhat off-topic: does GHC no longer use "the rapier"? I thought the InScopeSet was needed to check that we can safely skip on extending the substitution as you go under binders when the binder is not in the InScopeSet (naively you would always have to rename binders, and thus extend the substitution, in order to avoid capture as you go under binders). i.e. the IntMap is not just used to generate new variable names, but to ensure the compiler does less work in the form of doing fewer substitutions. > > > > On Fri, 2 Jul 2021 at 16:12, Simon Peyton Jones via ghc-devs wrote: > > There are lot of places where it would be pretty tiresome to plumb a unique supply guaranteed unique from every other. I think the current setup works pretty well – but I bet we can squeeze cycles out of its implementation. > > > > Simon > > > > From: Richard Eisenberg > Sent: 02 July 2021 14:26 > To: Simon Peyton Jones > Cc: Young, Jeff ; ghc-devs at haskell.org > Subject: Re: Trying to speedup GHC compile times...Help! > > > > One piece I'm curious about, reading this thread: why do we have so many IntMaps and operations on them? Name lookup is a fundamental operation a compiler must do, and that would use an IntMap: good. But maybe there are other IntMaps used that are less necessary. A key example: whenever we do substitution, we track an InScopeSet, which is really just an IntMap. This InScopeSet remembers the name of all variables in scope, useful when we need to create a new variable name (this is done by uniqAway). Yet perhaps the tracking of these in-scope variables is very expensive and comprises much of the IntMap time. Might it be better just to always work in a monad capable of giving fresh names? We actually don't even need a monad, if that's too annoying. Instead, we could just pass around an infinite list of fresh uniques. This would still be clutterful, but if it grants us a big speed improvement, the clutter might be worth it. > > > > The high-level piece here is that there may be good things that come from understanding where these IntMaps arise. > > > > Richard > > > > On Jul 2, 2021, at 4:08 AM, Simon Peyton Jones via ghc-devs wrote: > > > > Jeff > > > > Great stuff! Welcome. > > > > I strongly urge you to keep a constantly-update status wiki page, which lists the ideas you are working on, and points to relevant resources and tickets. An email thread like this is a good way to gather ideas, but NOT a good way to organise and track them. > > > > Looking carefully at profiles is a good plan. That’s the hard data! > > > > I think that some careful investigation of IntMap (at least the bits that GHC uses heavily) would be a good idea. Clearly we spend a lot of time in these maps, so speedups here will yield a lot of benefit. Look at the heavy hitters from the profile, stare at the Core code and see if it’s s good as it can be. > > > > For example, Sebastian discovered a strange infelicity in IntMap.lookup, which I’ve documented in a new ticket > > https://gitlab.haskell.org/ghc/ghc/-/issues/20069 > > > > I think it’d also be worth measuring how unbalanced our IntMap trees get. See > > https://gitlab.haskell.org/ghc/ghc/-/issues/19820 > > The speculation there is that we are getting very unbalanced trees. So measure it! If it’s true, we could improve matters by using a different IntMap; or maybe by scrambling the key a bit --- see the ticket. > > > > Simon > > > > From: ghc-devs On Behalf Of Young, Jeff > Sent: 02 July 2021 02:36 > To: ghc-devs at haskell.org > Subject: Trying to speedup GHC compile times...Help! > > > > Hi ghc devs, > > > > I'm a long-time Haskeller but am just getting into GHC development. I started a 12 week internship at Tweag I/O under Richard Eisenberg this week with the singular goal to speedup GHC compile times. I'm specifically looking to contribute to ghc issues 18541and 18535. So I thought I would reach out to the community to get some direction on issues/features/problems to tackle in the pursuit of faster compilation times. This is a full time internship and so I think there is a real opportunity to nail down a deliverable for the community, but I want to get some guidance from the experts (you fine people!) before going down a rabbit hole. > > > > To be specific I'm looking for lingering items such as: > > 1. It would be great if we had but no one has time. > > 2. Primop foo is half complete but is the right type for . > > 3. Swap to an array-like type non-incrementally, that is, establish a patch that rips out the previous type and replaces it with the array-like across the entire compiler, rather than module-by-module. > > > > Point 2 is a specific reference to MR 3571 but I'm unsure of the status and etiquette around MRs, and I'm unsure exactly how fulfilling the todos at the end of that MR would aid in faster compilation times (and if there is evidence to that effect somewhere). > > > > Thanks for the help! > > > > - Jeff > > > > > > > > _______________________________________________ > 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 From sam.derbyshire at gmail.com Mon Jul 5 18:23:42 2021 From: sam.derbyshire at gmail.com (Sam Derbyshire) Date: Mon, 5 Jul 2021 20:23:42 +0200 Subject: Rewriting plugins: request for feedback In-Reply-To: References: Message-ID: Hello everyone, I'm happy to report that I have implemented a compatibility layer in the ghc-tcplugin-api library which provides type-family rewriting functionality on GHC 9.0 and 9.2. This means that plugin authors should now be able to use the exact same API from GHC 9.0 onwards (and in particular, without waiting for a version of GHC containing the new implementation of type-family rewriting plugins). To refresh your memory, writing a type-checking plugin with this library currently consists of the provision of a record data TcPlugin = forall s. TcPlugin { tcPluginInit :: TcPluginM Init s , tcPluginSolve :: s -> TcPluginSolver , tcPluginRewrite :: s -> UniqFM TyCon TcPluginRewriter , tcPluginStop :: s -> TcPluginM Stop () } with the following type synonyms: type TcPluginSolver = [GHC.Ct] -- ^ Givens -> [GHC.Ct] -- ^ Wanteds -> TcPluginM Solve TcPluginSolveResult Note that Deriveds are no longer passed explicitly. (It is possible to retrieve the Derived constraints from the TcPluginM Solve monad; as they are not commonly used, it made sense to make them less conspicuous.) type TcPluginRewriter = [GHC.Ct] -- ^ Givens -> [GHC.Type] -- ^ Type family arguments (saturated) -> TcPluginM Rewrite TcPluginRewriteResult On GHC 9.0 and 9.2, the tcPluginRewrite function will get hooked in as a pre-pass of the user-supplied tcPluginSolve function. There are small differences in behaviour that arise from solver plugins not always getting a chance to run when GHC can solve the wanteds on its own, but I expect this to have minimal impact. On top of this, I expect (but have not measured) a performance degradation compared to the "native" plugin type-family rewriting functionality, as the solver plugin must traverse all constraints to find type-family applications. I have not tested this compatibility layer extensively, so I welcome all feedback from plugin authors. Note that I have also reduced the amount of re-exported datatype constructors and accessors in an attempt to improve cross compatibility. Please let me know of any difficulties that you encounter as a consequence, and I will endeavour to re-export cross-compatible non-internal definitions. Thanks, Sam -------------- next part -------------- An HTML attachment was scrubbed... URL: From Gergo.Erdi at sc.com Tue Jul 6 08:07:50 2021 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Tue, 6 Jul 2021 08:07:50 +0000 Subject: Marking ParsedModule fragments as non-user-originating Message-ID: PUBLIC Hi, I'd like to hijack some syntax (like string literals or list patterns) for my own use, and I thought a low-tech way of doing that is to transform the ParsedModule before typechecking. For example, if I have a function `uncons :: Array a -> Maybe (a, Array a)`, I can rewrite the pattern `[x1, x2, x3]` into the view pattern `(uncons -> Just (x1, (uncons -> Just (x2, (uncons -> Just (x3, (uncons -> Nothing)))))))` and let the normal GHC type checker take over from here. This is working for me so far, except for one problem: the typechecker now complains that the `ViewPatterns` language extension is not turned on. I would like to make the view patterns coming from my ParsedModule rewriter to be exempt from this check (but of course still require the `ViewPatterns` extension for user-originating code). Is there a way to do that? Or would I be better off checking for user-originating view patterns myself before the rewrite and then changing the `DynFlags` to always enable view patterns for typechecking? Thanks, Gergo 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 simonpj at microsoft.com Tue Jul 6 09:08:25 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 6 Jul 2021 09:08:25 +0000 Subject: Marking ParsedModule fragments as non-user-originating In-Reply-To: References: Message-ID: The typechecker now complains that the `ViewPatterns` language extension is not turned on I think it's the renamer: rnPatAndThen mk p@(ViewPat _ expr pat) = do { liftCps $ do { vp_flag <- xoptM LangExt.ViewPatterns ; checkErr vp_flag (badViewPat p) } More generally, don't you just want OverloadedStrings or OverloadedLists? You might want to read Note [Handling overloaded and rebindable constructs] in GHC.Rename.Expr, and Note [Rebindable syntax and HsExpansion] in GCH.Hs.Expr. These Notes describe how GHC already does something similar to what you want. Maybe you can use the same mechanism in your plugin. Simon From: ghc-devs On Behalf Of Erdi, Gergo via ghc-devs Sent: 06 July 2021 09:08 To: ghc-devs at haskell.org Subject: Marking ParsedModule fragments as non-user-originating PUBLIC Hi, I'd like to hijack some syntax (like string literals or list patterns) for my own use, and I thought a low-tech way of doing that is to transform the ParsedModule before typechecking. For example, if I have a function `uncons :: Array a -> Maybe (a, Array a)`, I can rewrite the pattern `[x1, x2, x3]` into the view pattern `(uncons -> Just (x1, (uncons -> Just (x2, (uncons -> Just (x3, (uncons -> Nothing)))))))` and let the normal GHC type checker take over from here. This is working for me so far, except for one problem: the typechecker now complains that the `ViewPatterns` language extension is not turned on. I would like to make the view patterns coming from my ParsedModule rewriter to be exempt from this check (but of course still require the `ViewPatterns` extension for user-originating code). Is there a way to do that? Or would I be better off checking for user-originating view patterns myself before the rewrite and then changing the `DynFlags` to always enable view patterns for typechecking? Thanks, Gergo -------------- next part -------------- An HTML attachment was scrubbed... URL: From alfredo.dinapoli at gmail.com Tue Jul 6 09:14:07 2021 From: alfredo.dinapoli at gmail.com (Alfredo Di Napoli) Date: Tue, 6 Jul 2021 11:14:07 +0200 Subject: Can NamedFieldPuns be added to `GHC.LanguageExtensions.Types.Extension`? Message-ID: Dear all, As some of you might know, for the past few months I have been working on changing GHC's diagnostic messages from plain SDocs to richer Haskell types. As part of this work, I have added a mechanism to embed hints into diagnostics, defined in `GHC.Types.Hint` in `HEAD`. One of the main workhorse of this `GhcHint` type is the `SuggestExtension LangExt.Extension` constructor, which embeds the extension to enable to use a particular feature. The `LangExt.Extension` type comes from `GHC.LanguageExtensions.Types`, and up until now there has always been a 1:1 mapping between the language pragma for the extension and the type itself. Today I was working on turning this error into a proper Haskell type: badPun :: Located RdrName -> TcRnMessage badPun fld = TcRnUnknownMessage $ mkPlainError noHints $ vcat [text "Illegal use of punning for field" <+> quotes (ppr fld), text "Use NamedFieldPuns to permit this"] I was ready to yield a `SuggestExtension LangExt.NamedFieldPuns` when I discovered that there is no `NamedFieldPuns` constructor. Rather, there is a `RecordPuns` , which refer to a deprecated flag, and we simply map `NamedFieldPuns` back to it in `GHC.Driver.Session`: ... depFlagSpec' "RecordPuns" LangExt.RecordPuns (deprecatedForExtension "NamedFieldPuns"), ... flagSpec "NamedFieldPuns" LangExt.RecordPuns, ... This is problematic for the `GhcHint` type, because now if I was to yield `SuggestExtension LangExt.RecordPuns` to the user, I could still pretty-print the suggestion to turn `RecordPuns` into `NamedFieldPuns`, but this means that IDEs or third-party library would have access to the "raw" Haskell datatype, and at that point they will be stuck with a suggestion to enable a deprecated extension! (or best case scenario they will have to transform the suggestion into something more sensible, which partially defeats the point of this refactoring work I have been doing). I am not sure this behaviour is unique for just `NamedFieldPuns`, but my question is: 1. What prevents us from adding `NamedFieldPuns` as a proper constructor for the `Extension` type and in principle remove `RecordPuns`? Backward compatibility I assume? Many thanks, Alfredo -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Tue Jul 6 09:15:53 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 6 Jul 2021 09:15:53 +0000 Subject: Trying to speedup GHC compile times...Help! In-Reply-To: References: Message-ID: I love "Scrap Your Type Applications" (SYTA) too, although I'm a little biased since I'm a co-author. But SYTA is a change that has a pretty pervasive effect on the way GHC manipulates types. Since then we've added TypeInType, from which a lot of consequences flowed. I simply don't know how hard it'd be to do a "scrap your type applications" job on GHC today. I agree that the cost/benefit tradeoff could have shifted. We can only find out by trying it. But trying it would take quite a lot of work. On the other hand, SYTA is the only principled approach that I know of that solves the type blow-up we get with deeply-nested data types (notoriously, tuples). It's a problem we have known of for decades, but is still essentially unsolved. Simon | -----Original Message----- | From: ghc-devs On Behalf Of Viktor Dukhovni | Sent: 02 July 2021 15:30 | To: ghc-devs at haskell.org | Subject: Re: Trying to speedup GHC compile times...Help! | | On Fri, Jul 02, 2021 at 08:08:39AM +0000, Simon Peyton Jones via ghc-devs | wrote: | | > I strongly urge you to keep a constantly-update status wiki page, | > which lists the ideas you are working on, and points to relevant | > resources and tickets. An email thread like this is a good way to | > gather ideas, but NOT a good way to organise and track them. | | I remain curious as to whether "Scrap your type applications" is worth a | second look. There are edge cases in which compile time blowup is a result | of type blowup (as opposed to code blowup via inlining). Might GHC have | changed enough in the last ~5 years to make it now "another | compiler": | | | https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fwww.micros | oft.com%2Fen-us%2Fresearch%2Fwp- | content%2Fuploads%2F2016%2F07%2Fif.pdf&data=04%7C01%7Csimonpj%40microsof | t.com%7C7effa9c7dd004554fdf408d93d6626f0%7C72f988bf86f141af91ab2d7cd011db47% | 7C1%7C0%7C637608331663562915%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJ | QIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000&sdata=brNlPRnQgHqbTSO | AOs9hbZOdC84VZfhfnO8g%2BtwSKOQ%3D&reserved=0 | | (Section 4.4): | | Overall, allocation decreased by a mere 0.1%. The largest reduction was | 4%, and the largest increase was 12%, but 120 of the 130 modules showed | a | change of less than 1%. Presumably, the reduction in work that arises | from smaller types is balanced by the additional overheads of SystemIF. | On this evidence, the additional complexity introduced by the new | reduction rules does not pay its way. Nevertheless, these are matters | that are dominated by nitty-gritty representation details, and the | balance might well be different in another compiler. | | Could it be that some of the more compile time intensive packages on hackage | (aeson, vector, ...) would benefit more than the various modules in base? | | Wild speculation aside, of course finding and fixing inefficiencies in the | implementation of existing common primitive should be a win across the | board, and should not require changing major compiler design features, just | leaner code. | | -- | Viktor. | _______________________________________________ | ghc-devs mailing list | ghc-devs at haskell.org | https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.haskel | l.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc- | devs&data=04%7C01%7Csimonpj%40microsoft.com%7C7effa9c7dd004554fdf408d93d | 6626f0%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637608331663562915%7CUnk | nown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXV | CI6Mn0%3D%7C3000&sdata=OYuQV%2FP3Sgly62Ex5m1kwv5ciHLchWEXq7XvvPYJCJ4%3D& | amp;reserved=0 From simonpj at microsoft.com Tue Jul 6 09:19:33 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 6 Jul 2021 09:19:33 +0000 Subject: Can NamedFieldPuns be added to `GHC.LanguageExtensions.Types.Extension`? In-Reply-To: References: Message-ID: 1. What prevents us from adding `NamedFieldPuns` as a proper constructor for the `Extension` type and in principle remove `RecordPuns`? Backward compatibility I assume? You mean, essentially, rename `LangExt.RecordPuns` to `NamedFieldPuns`. I’d be fine with that. There might be back-compat issues, but only with other plugins, and probably with vanishingly few of them. Grep in Hackage! Simon From: ghc-devs On Behalf Of Alfredo Di Napoli Sent: 06 July 2021 10:14 To: Simon Peyton Jones via ghc-devs Subject: Can NamedFieldPuns be added to `GHC.LanguageExtensions.Types.Extension`? Dear all, As some of you might know, for the past few months I have been working on changing GHC's diagnostic messages from plain SDocs to richer Haskell types. As part of this work, I have added a mechanism to embed hints into diagnostics, defined in `GHC.Types.Hint` in `HEAD`. One of the main workhorse of this `GhcHint` type is the `SuggestExtension LangExt.Extension` constructor, which embeds the extension to enable to use a particular feature. The `LangExt.Extension` type comes from `GHC.LanguageExtensions.Types`, and up until now there has always been a 1:1 mapping between the language pragma for the extension and the type itself. Today I was working on turning this error into a proper Haskell type: badPun :: Located RdrName -> TcRnMessage badPun fld = TcRnUnknownMessage $ mkPlainError noHints $ vcat [text "Illegal use of punning for field" <+> quotes (ppr fld), text "Use NamedFieldPuns to permit this"] I was ready to yield a `SuggestExtension LangExt.NamedFieldPuns` when I discovered that there is no `NamedFieldPuns` constructor. Rather, there is a `RecordPuns` , which refer to a deprecated flag, and we simply map `NamedFieldPuns` back to it in `GHC.Driver.Session`: ... depFlagSpec' "RecordPuns" LangExt.RecordPuns (deprecatedForExtension "NamedFieldPuns"), ... flagSpec "NamedFieldPuns" LangExt.RecordPuns, ... This is problematic for the `GhcHint` type, because now if I was to yield `SuggestExtension LangExt.RecordPuns` to the user, I could still pretty-print the suggestion to turn `RecordPuns` into `NamedFieldPuns`, but this means that IDEs or third-party library would have access to the "raw" Haskell datatype, and at that point they will be stuck with a suggestion to enable a deprecated extension! (or best case scenario they will have to transform the suggestion into something more sensible, which partially defeats the point of this refactoring work I have been doing). I am not sure this behaviour is unique for just `NamedFieldPuns`, but my question is: 1. What prevents us from adding `NamedFieldPuns` as a proper constructor for the `Extension` type and in principle remove `RecordPuns`? Backward compatibility I assume? Many thanks, Alfredo -------------- next part -------------- An HTML attachment was scrubbed... URL: From Gergo.Erdi at sc.com Tue Jul 6 09:38:55 2021 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Tue, 6 Jul 2021 09:38:55 +0000 Subject: Marking ParsedModule fragments as non-user-originating In-Reply-To: References: Message-ID: PUBLIC Thanks Simon! Of course, you're right, it's the renamer, not the typechecker - I didn't really check, just saw that "it happens during `typecheckModule`. I'll look at the rebindable syntax stuff in detail, but at least for OverloadedStrings, I already know that the problem will be that ultimately they do go through the `String` type from `base`, and I need to use GHC baselessly. This is a problem for two reasons: * I can't implement `IsString` for `MyString`, because `IsString` is in `base` * Even if I made my own fake `base` with a fake `IsString` class, there is nothing to put in the codomain of `fromString`: I *only* have `MyString`, not `String`. And renaming `MyString to `String` in my fake `base` is not going to cut it, since `String` is wired into GHC to be a type synonym for `[Char]` (which `MyString` is not). I foresee similar problems for OverloadedLists :/ Thanks, Gergo From: Simon Peyton Jones Sent: Tuesday, July 6, 2021 5:08 PM To: Erdi, Gergo Cc: GHC Subject: [External] RE: Marking ParsedModule fragments as non-user-originating The typechecker now complains that the `ViewPatterns` language extension is not turned on I think it's the renamer: rnPatAndThen mk p@(ViewPat _ expr pat) = do { liftCps $ do { vp_flag <- xoptM LangExt.ViewPatterns ; checkErr vp_flag (badViewPat p) } More generally, don't you just want OverloadedStrings or OverloadedLists? You might want to read Note [Handling overloaded and rebindable constructs] in GHC.Rename.Expr, and Note [Rebindable syntax and HsExpansion] in GCH.Hs.Expr. These Notes describe how GHC already does something similar to what you want. Maybe you can use the same mechanism in your plugin. Simon From: ghc-devs > On Behalf Of Erdi, Gergo via ghc-devs Sent: 06 July 2021 09:08 To: ghc-devs at haskell.org Subject: Marking ParsedModule fragments as non-user-originating PUBLIC Hi, I'd like to hijack some syntax (like string literals or list patterns) for my own use, and I thought a low-tech way of doing that is to transform the ParsedModule before typechecking. For example, if I have a function `uncons :: Array a -> Maybe (a, Array a)`, I can rewrite the pattern `[x1, x2, x3]` into the view pattern `(uncons -> Just (x1, (uncons -> Just (x2, (uncons -> Just (x3, (uncons -> Nothing)))))))` and let the normal GHC type checker take over from here. This is working for me so far, except for one problem: the typechecker now complains that the `ViewPatterns` language extension is not turned on. I would like to make the view patterns coming from my ParsedModule rewriter to be exempt from this check (but of course still require the `ViewPatterns` extension for user-originating code). Is there a way to do that? Or would I be better off checking for user-originating view patterns myself before the rewrite and then changing the `DynFlags` to always enable view patterns for typechecking? Thanks, Gergo 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 alfredo.dinapoli at gmail.com Tue Jul 6 09:59:56 2021 From: alfredo.dinapoli at gmail.com (Alfredo Di Napoli) Date: Tue, 6 Jul 2021 11:59:56 +0200 Subject: Can NamedFieldPuns be added to `GHC.LanguageExtensions.Types.Extension`? In-Reply-To: References: Message-ID: Hello Simon, Yes, renaming and perhaps keeping `RecordPuns` as a pattern synonym to not break backward-compat, if that's feasible to define as we are in `ghc-boot-th` here. Not sure if `PatternSynonyms` and `COMPLETE` would be available there. I am not sure how many libs that depend on the ghc API would break (I haven't grepped on Hackage yet), but that might tip the benefits/troubles ratio towards keeping the status quo. This is not a "problem" I have to solve today, and it might not be considered a problem by others (just an inconsistency I guess): as a colleague of mine pointed out, GHC is not necessarily "lying" here. It's still the same underlying extension, it just happens that there are two names that refer to it. Perhaps I could think about adding to `GhcHint` some kind of mapping which would give to IDEs or third-party libs the correct extension name given an input `LangExt.Extension`, the problem then becomes making sure that we keep this mapping in sync with the information contained in `GHC.Driver.Session`. I will let it simmer. Thanks! A. On Tue, 6 Jul 2021 at 11:19, Simon Peyton Jones wrote: > 1. What prevents us from adding `NamedFieldPuns` as a proper constructor > for the `Extension` type and in principle remove `RecordPuns`? Backward > compatibility I assume? > > You mean, essentially, rename `LangExt.RecordPuns` to `NamedFieldPuns`. > > > > I’d be fine with that. There might be back-compat issues, but only with > other plugins, and probably with vanishingly few of them. Grep in Hackage! > > > > Simon > > > > *From:* ghc-devs *On Behalf Of *Alfredo Di > Napoli > *Sent:* 06 July 2021 10:14 > *To:* Simon Peyton Jones via ghc-devs > *Subject:* Can NamedFieldPuns be added to > `GHC.LanguageExtensions.Types.Extension`? > > > > Dear all, > > > > As some of you might know, for the past few months I have been working on > changing GHC's diagnostic messages from plain SDocs to richer Haskell types. > > > > As part of this work, I have added a mechanism to embed hints into > diagnostics, defined in `GHC.Types.Hint` in `HEAD`. One of the main > workhorse of this `GhcHint` type is the `SuggestExtension > LangExt.Extension` constructor, which embeds the extension to enable to use > a particular feature. The `LangExt.Extension` type comes from > `GHC.LanguageExtensions.Types`, and up until now there has always been a > 1:1 mapping between the language pragma for the extension and the type > itself. > > > > Today I was working on turning this error into a proper Haskell type: > > > > badPun :: Located RdrName -> TcRnMessage > > badPun fld = TcRnUnknownMessage $ mkPlainError noHints $ > > vcat [text "Illegal use of punning for field" <+> quotes (ppr fld), > > text "Use NamedFieldPuns to permit this"] > > > > I was ready to yield a `SuggestExtension LangExt.NamedFieldPuns` when I > discovered that there is no `NamedFieldPuns` constructor. Rather, there is > a `RecordPuns` , which refer to a deprecated flag, and we simply map > `NamedFieldPuns` back to it in `GHC.Driver.Session`: > > > > ... > > depFlagSpec' "RecordPuns" LangExt.RecordPuns > > (deprecatedForExtension "NamedFieldPuns"), > > ... > > flagSpec "NamedFieldPuns" LangExt.RecordPuns, > > ... > > > > This is problematic for the `GhcHint` type, because now if I was to yield > `SuggestExtension LangExt.RecordPuns` to the user, I could still > pretty-print the suggestion to turn `RecordPuns` into `NamedFieldPuns`, but > this means that IDEs or third-party library would have access to the > > "raw" Haskell datatype, and at that point they will be stuck with a > suggestion to enable a deprecated extension! (or best case scenario they > will have to transform the suggestion into something more sensible, which > partially defeats the point of this refactoring work I have been doing). > > > > I am not sure this behaviour is unique for just `NamedFieldPuns`, but my > question is: > > > > 1. What prevents us from adding `NamedFieldPuns` as a proper constructor > for the `Extension` type and in principle remove `RecordPuns`? Backward > compatibility I assume? > > > > > > Many thanks, > > > > Alfredo > > > > > > > > > > > > > > > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From oleg.grenrus at iki.fi Wed Jul 7 15:11:41 2021 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Wed, 7 Jul 2021 18:11:41 +0300 Subject: Why base library changes are only discussed on GHC issue tracker and not on the libraries@ list? Message-ID: For example - https://gitlab.haskell.org/ghc/ghc/-/issues/20044 ByteArray migration from primitive to base - https://gitlab.haskell.org/ghc/ghc/-/issues/20027 Changing Show String behavior Why they are discussed "in private", I thought libraries@ list is where such changes should be discussed. - Oleg From carter.schonwald at gmail.com Wed Jul 7 15:42:26 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Wed, 7 Jul 2021 11:42:26 -0400 Subject: Why base library changes are only discussed on GHC issue tracker and not on the libraries@ list? In-Reply-To: References: Message-ID: Agreed. This is a problem. I’ve tried to help make current clc folks aware of this privately a time or two this past year :( The only private part should be public coms on their discussion group to record voting on stuff that isn’t unanimous. Anything beyond that fails to align with healthy collaborative discourse norms More concerningly, only ~2-3 members of the current clc seem to be actively involved in public discussions on the library list or GitHub. And a deep misunderstanding that they need be maintainers of stuff that falls under the umbrella of core libraries now. Which is a fiction invented only on the past two years. Clc was formed to help guide decisions on base and be a suport for core libraries authors/maintainers. Not as an authority over those maintainers. There’s def problems with stuff and a lot of folks have privately expressed a lot of frustration about this over the past 12 months. On Wed, Jul 7, 2021 at 11:12 AM Oleg Grenrus wrote: > For example > > - https://gitlab.haskell.org/ghc/ghc/-/issues/20044 ByteArray migration > from primitive to base > - https://gitlab.haskell.org/ghc/ghc/-/issues/20027 Changing Show String > behavior > > Why they are discussed "in private", I thought libraries@ list is where > such changes should be discussed. > > - Oleg > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From chessai1996 at gmail.com Wed Jul 7 17:52:24 2021 From: chessai1996 at gmail.com (chessai) Date: Wed, 7 Jul 2021 12:52:24 -0500 Subject: Why base library changes are only discussed on GHC issue tracker and not on the libraries@ list? In-Reply-To: References: Message-ID: FWIW, I do believe that changing Show @String needs to be discussed on the list and I pinged the proposer to do so. The ByteArray change was in my/Andrew Martin's opinion that it was straightforward and sensible enough to not need the mailing list. As has been pointed out by Oleg, on the library submissions page, not all changes to any core library need to be discussed on the mailing list, as that would be a gross inefficiency and waste of time. Issue trackers are better, with escalation when necessary. On Wed, Jul 7, 2021, 10:12 Oleg Grenrus wrote: > For example > > - https://gitlab.haskell.org/ghc/ghc/-/issues/20044 ByteArray migration > from primitive to base > - https://gitlab.haskell.org/ghc/ghc/-/issues/20027 Changing Show String > behavior > > Why they are discussed "in private", I thought libraries@ list is where > such changes should be discussed. > > - Oleg > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jeff.young at tweag.io Thu Jul 8 20:04:48 2021 From: jeff.young at tweag.io (Jeffrey Young) Date: Thu, 8 Jul 2021 13:04:48 -0700 Subject: Trying to speedup GHC compile times...Help! Message-ID: <931b340b-d9ec-5702-823c-92b56f01f6a2@tweag.io> Hi everyone, I've created a wiki page here that collected your suggestions and tracks my work. I'll be regularly updating it. Any comments welcome. - Jeff -------------- next part -------------- An HTML attachment was scrubbed... URL: From jaro.reinders at gmail.com Thu Jul 8 20:53:26 2021 From: jaro.reinders at gmail.com (Jaro Reinders) Date: Thu, 8 Jul 2021 22:53:26 +0200 Subject: Trying to speedup GHC compile times...Help! In-Reply-To: <931b340b-d9ec-5702-823c-92b56f01f6a2@tweag.io> References: <931b340b-d9ec-5702-823c-92b56f01f6a2@tweag.io> Message-ID: <231de15b-ae77-77ec-14f9-2a0e4e3c8609@gmail.com> Hi Jeff, For some reason none of the links in the table of contents work for me in Firefox. It seems some other pages use [[_TOC_]] to generate it automatically. Cheers, Jaro On 08-07-2021 22:04, Jeffrey Young wrote: > Hi everyone, > > > I've created a wiki page here > > that collected your suggestions and tracks my work. I'll be regularly updating > it. Any comments welcome. > > > - Jeff > > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > From allbery.b at gmail.com Thu Jul 8 20:55:59 2021 From: allbery.b at gmail.com (Brandon Allbery) Date: Thu, 8 Jul 2021 16:55:59 -0400 Subject: Trying to speedup GHC compile times...Help! In-Reply-To: <231de15b-ae77-77ec-14f9-2a0e4e3c8609@gmail.com> References: <931b340b-d9ec-5702-823c-92b56f01f6a2@tweag.io> <231de15b-ae77-77ec-14f9-2a0e4e3c8609@gmail.com> Message-ID: They don't work in Chrome either. A quick inspection of the links indicates that the ones in the TOC have anchors of the form "#org-NNNNNN" while their targets have forms derived from the heading strings. On Thu, Jul 8, 2021 at 4:53 PM Jaro Reinders wrote: > Hi Jeff, > > For some reason none of the links in the table of contents work for me in > Firefox. > > It seems some other pages use [[_TOC_]] to generate it automatically. > > Cheers, > > Jaro > > On 08-07-2021 22:04, Jeffrey Young wrote: > > Hi everyone, > > > > > > I've created a wiki page here > > < > https://gitlab.haskell.org/ghc/ghc/-/wikis/Adventures-in-GHC-compile-times> > > > that collected your suggestions and tracks my work. I'll be regularly > updating > > it. Any comments welcome. > > > > > > - Jeff > > > > > > > > _______________________________________________ > > 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 > -- brandon s allbery kf8nh allbery.b at gmail.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From jeff.young at tweag.io Fri Jul 9 21:14:56 2021 From: jeff.young at tweag.io (Jeffrey Young) Date: Fri, 9 Jul 2021 14:14:56 -0700 Subject: Trying to speedup GHC compile times...Help! In-Reply-To: References: Message-ID: Thanks for pointing out the linking issue. Looks like the table of content references get clobbered by gitlab. Unfortunately, pandoc doesn't generate the table of contents, and the gitlab org parser ignores #+OPTION: toc:3. So I've opted to just remove the table of contents entirely. - Jeff On 7/9/21 5:00 AM, ghc-devs-request at haskell.org wrote: > Send ghc-devs mailing list submissions to > ghc-devs at haskell.org > > To subscribe or unsubscribe via the World Wide Web, visit > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > or, via email, send a message with subject or body 'help' to > ghc-devs-request at haskell.org > > You can reach the person managing the list at > ghc-devs-owner at haskell.org > > When replying, please edit your Subject line so it is more specific > than "Re: Contents of ghc-devs digest..." > > > Today's Topics: > > 1. Re: Trying to speedup GHC compile times...Help! (Jeffrey Young) > 2. Re: Trying to speedup GHC compile times...Help! (Jaro Reinders) > 3. Re: Trying to speedup GHC compile times...Help! (Brandon Allbery) > > > ---------------------------------------------------------------------- > > Message: 1 > Date: Thu, 8 Jul 2021 13:04:48 -0700 > From: Jeffrey Young > To: ghc-devs at haskell.org > Subject: Re: Trying to speedup GHC compile times...Help! > Message-ID: <931b340b-d9ec-5702-823c-92b56f01f6a2 at tweag.io> > Content-Type: text/plain; charset="utf-8"; Format="flowed" > > Hi everyone, > > > I've created a wiki page here > > that collected your suggestions and tracks my work. I'll be regularly > updating it. Any comments welcome. > > > - Jeff > > -------------- next part -------------- > An HTML attachment was scrubbed... > URL: > > ------------------------------ > > Message: 2 > Date: Thu, 8 Jul 2021 22:53:26 +0200 > From: Jaro Reinders > To: ghc-devs at haskell.org > Subject: Re: Trying to speedup GHC compile times...Help! > Message-ID: <231de15b-ae77-77ec-14f9-2a0e4e3c8609 at gmail.com> > Content-Type: text/plain; charset=utf-8; format=flowed > > Hi Jeff, > > For some reason none of the links in the table of contents work for me in Firefox. > > It seems some other pages use [[_TOC_]] to generate it automatically. > > Cheers, > > Jaro > > On 08-07-2021 22:04, Jeffrey Young wrote: >> Hi everyone, >> >> >> I've created a wiki page here >> >> that collected your suggestions and tracks my work. I'll be regularly updating >> it. Any comments welcome. >> >> >> - Jeff >> >> >> >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >> > > ------------------------------ > > Message: 3 > Date: Thu, 8 Jul 2021 16:55:59 -0400 > From: Brandon Allbery > To: Jaro Reinders > Cc: "ghc-devs at haskell.org Devs" > Subject: Re: Trying to speedup GHC compile times...Help! > Message-ID: > > Content-Type: text/plain; charset="utf-8" > > They don't work in Chrome either. A quick inspection of the links indicates > that the ones in the TOC have anchors of the form "#org-NNNNNN" while their > targets have forms derived from the heading strings. > > On Thu, Jul 8, 2021 at 4:53 PM Jaro Reinders > wrote: > >> Hi Jeff, >> >> For some reason none of the links in the table of contents work for me in >> Firefox. >> >> It seems some other pages use [[_TOC_]] to generate it automatically. >> >> Cheers, >> >> Jaro >> >> On 08-07-2021 22:04, Jeffrey Young wrote: >>> Hi everyone, >>> >>> >>> I've created a wiki page here >>> < >> https://gitlab.haskell.org/ghc/ghc/-/wikis/Adventures-in-GHC-compile-times> >> >>> that collected your suggestions and tracks my work. I'll be regularly >> updating >>> it. Any comments welcome. >>> >>> >>> - Jeff >>> >>> >>> >>> _______________________________________________ >>> 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 sam.derbyshire at gmail.com Fri Jul 9 22:55:16 2021 From: sam.derbyshire at gmail.com (Sam Derbyshire) Date: Sat, 10 Jul 2021 00:55:16 +0200 Subject: Rewriting plugins: request for feedback In-Reply-To: References: Message-ID: Hi all, I have now written a much more substantial type-checking plugin, which I used to typecheck an intrinsically typed implementation of System F. I've added the example to the repository ( https://github.com/sheaf/ghc-tcplugin-api), see the readme. This uncovered several bugs in the implementation of the aforementioned compatibility layer for GHC 9.0 and 9.2, which have all been fixed. I can now in good conscience recommend that type-checking plugin authors try it out for themselves! There are slight inconsistencies in behaviour around emitting additional constraints when rewriting a type-family application (which I hope to iron out soon), but I expect the impact of this to be very minimal. Other than that, you can expect feature and behaviour parity with the native implementation. Please let me know how you get on, and which pain points you would like to see addressed. My current ideas for improvement are as follows: - Functionality that would perform all the name resolution necessary in the plugin initialisation. The user would provide a record of the types to look up (a TyCon named ... in module ..., a Class named ... in module ...), and the library would look up everything. This would be quite straightforward with a library such as barbies, but I don't necessarily want to impose that cognitive overhead on users who are not familiar with it. - An interface for handling type family rewritings that provides a type system that kind checks everything. For instance, instead of manually calling splitTyConAppMaybe, we could feasibly instead use a pattern with existential variables (matching on this pattern would introduce the kinds), and then use a smart constructor instead of mkTyConApp (which would kind-check the application). I certainly would have appreciated something like this when writing my System F plugin, as handling all the kinds explicitly was rather tiresome and error prone. - Functionality for recognising that a type has a certain form, making use of Givens. For example, it can be quite annoying to find out whether a given type is a type family application, as one needs to look through the Givens to go through levels of indirection. For instance, one might come across a variable "x" (ostensibly not a type family application), but have Givens [G] y ~ x, [G] F a ~ y. (This happens often with flattening skolems.) Please let me know if you have any other ideas, or suggestions on how to tackle the above. Thanks. Best, Sam -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Sat Jul 10 00:42:49 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 9 Jul 2021 20:42:49 -0400 Subject: Rewriting plugins: request for feedback In-Reply-To: References: Message-ID: This sounds very cool! FYI the Inria paper link in the readme seems to not be correct? On Fri, Jul 9, 2021 at 6:56 PM Sam Derbyshire wrote: > Hi all, > > I have now written a much more substantial type-checking plugin, which I > used to typecheck an intrinsically typed implementation of System F. I've > added the example to the repository ( > https://github.com/sheaf/ghc-tcplugin-api), see the readme. > > This uncovered several bugs in the implementation of the aforementioned > compatibility layer for GHC 9.0 and 9.2, which have all been fixed. I can > now in good conscience recommend that type-checking plugin authors try it > out for themselves! > There are slight inconsistencies in behaviour around emitting additional > constraints when rewriting a type-family application (which I hope to iron > out soon), but I expect the impact of this to be very minimal. Other than > that, you can expect feature and behaviour parity with the native > implementation. > > Please let me know how you get on, and which pain points you would like to > see addressed. My current ideas for improvement are as follows: > > - Functionality that would perform all the name resolution necessary in > the plugin initialisation. The user would provide a record of the types to > look up (a TyCon named ... in module ..., a Class named ... in module ...), > and the library would look up everything. This would be quite > straightforward with a library such as barbies, but I don't necessarily > want to impose that cognitive overhead on users who are not familiar with > it. > - An interface for handling type family rewritings that provides a type > system that kind checks everything. For instance, instead of manually > calling splitTyConAppMaybe, we could feasibly instead use a pattern with > existential variables (matching on this pattern would introduce the kinds), > and then use a smart constructor instead of mkTyConApp (which would > kind-check the application). I certainly would have appreciated something > like this when writing my System F plugin, as handling all the kinds > explicitly was rather tiresome and error prone. > - Functionality for recognising that a type has a certain form, making > use of Givens. For example, it can be quite annoying to find out whether a > given type is a type family application, as one needs to look through the > Givens to go through levels of indirection. For instance, one might come > across a variable "x" (ostensibly not a type family application), but have > Givens [G] y ~ x, [G] F a ~ y. (This happens often with flattening skolems.) > > Please let me know if you have any other ideas, or suggestions on how to > tackle the above. Thanks. > > Best, > > Sam > > _______________________________________________ > 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 sam.derbyshire at gmail.com Sat Jul 10 10:46:19 2021 From: sam.derbyshire at gmail.com (Sam Derbyshire) Date: Sat, 10 Jul 2021 12:46:19 +0200 Subject: Rewriting plugins: request for feedback In-Reply-To: References: Message-ID: > > FYI the Inria paper link in the readme seems to not be correct? > The HAL-Inria server seems to be down at the moment. -------------- next part -------------- An HTML attachment was scrubbed... URL: From Gergo.Erdi at sc.com Mon Jul 12 07:13:13 2021 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Mon, 12 Jul 2021 07:13:13 +0000 Subject: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating) Message-ID: PUBLIC OK so I tried out OverloadedStrings and it basically went as bad as I expected. The documentation on `HsOverLit` is very promising: it points to the Note [Overloaded literal witnesses], which states: Note [Overloaded literal witnesses] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ *Before* type checking, the HsExpr in an HsOverLit is the name of the coercion function, 'fromInteger' or 'fromRational'. So that sounds great, right? It sounds like just before renaming, I should be able to replace `HsLit _ (HsString _ fs)` with `HsOverLit _ (OverLit _ (HsIsString _ fs) unpack` with my own `unpack` function coming from my own package, and everything would work out. Unfortunately, this is not what happens: if I try getting this through the renamer, I get this error: Failed to load interface for 'Data.String' no unit id matching 'base' was found Can't find interface-file declaration for variable fromString Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error So even though I am specifying my own coercion function, it is still looking for `Data.String.fromString` which is not going to work, since I don't have `base`. So either I am misunderstanding that Note, or it is simply out of date, but in either case, this isn't going to be a viable route to going base-less. Gergo From: Erdi, Gergo Sent: Tuesday, July 6, 2021 5:39 PM To: Simon Peyton Jones Cc: GHC Subject: RE: Marking ParsedModule fragments as non-user-originating PUBLIC Thanks Simon! Of course, you're right, it's the renamer, not the typechecker - I didn't really check, just saw that "it happens during `typecheckModule`. I'll look at the rebindable syntax stuff in detail, but at least for OverloadedStrings, I already know that the problem will be that ultimately they do go through the `String` type from `base`, and I need to use GHC baselessly. This is a problem for two reasons: * I can't implement `IsString` for `MyString`, because `IsString` is in `base` * Even if I made my own fake `base` with a fake `IsString` class, there is nothing to put in the codomain of `fromString`: I *only* have `MyString`, not `String`. And renaming `MyString to `String` in my fake `base` is not going to cut it, since `String` is wired into GHC to be a type synonym for `[Char]` (which `MyString` is not). I foresee similar problems for OverloadedLists :/ Thanks, Gergo From: Simon Peyton Jones > Sent: Tuesday, July 6, 2021 5:08 PM To: Erdi, Gergo > Cc: GHC > Subject: [External] RE: Marking ParsedModule fragments as non-user-originating The typechecker now complains that the `ViewPatterns` language extension is not turned on I think it's the renamer: rnPatAndThen mk p@(ViewPat _ expr pat) = do { liftCps $ do { vp_flag <- xoptM LangExt.ViewPatterns ; checkErr vp_flag (badViewPat p) } More generally, don't you just want OverloadedStrings or OverloadedLists? You might want to read Note [Handling overloaded and rebindable constructs] in GHC.Rename.Expr, and Note [Rebindable syntax and HsExpansion] in GCH.Hs.Expr. These Notes describe how GHC already does something similar to what you want. Maybe you can use the same mechanism in your plugin. Simon From: ghc-devs > On Behalf Of Erdi, Gergo via ghc-devs Sent: 06 July 2021 09:08 To: ghc-devs at haskell.org Subject: Marking ParsedModule fragments as non-user-originating PUBLIC Hi, I'd like to hijack some syntax (like string literals or list patterns) for my own use, and I thought a low-tech way of doing that is to transform the ParsedModule before typechecking. For example, if I have a function `uncons :: Array a -> Maybe (a, Array a)`, I can rewrite the pattern `[x1, x2, x3]` into the view pattern `(uncons -> Just (x1, (uncons -> Just (x2, (uncons -> Just (x3, (uncons -> Nothing)))))))` and let the normal GHC type checker take over from here. This is working for me so far, except for one problem: the typechecker now complains that the `ViewPatterns` language extension is not turned on. I would like to make the view patterns coming from my ParsedModule rewriter to be exempt from this check (but of course still require the `ViewPatterns` extension for user-originating code). Is there a way to do that? Or would I be better off checking for user-originating view patterns myself before the rewrite and then changing the `DynFlags` to always enable view patterns for typechecking? Thanks, Gergo 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 simonpj at microsoft.com Mon Jul 12 07:32:02 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 12 Jul 2021 07:32:02 +0000 Subject: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating) In-Reply-To: References: Message-ID: Gergo, If you think you have uncovered a bug, could you submit a bug report on the issue tracker, with a way to reproduce it? It's a bit hard to decode exactly what is happening from what you say. The user manual documentation doesn't say this in so many words (that's a bug), but with OverloadedStrings, the literal "foo" is replaced by Data.String.fromString "foo" Guessing a bit, that is probably why GHC complains that it can't load Data.String.fromString. If in addition you want to use your own fromString, not the built-in one, then you need to add RebindableSyntax. Simon From: Erdi, Gergo Sent: 12 July 2021 08:13 To: Simon Peyton Jones Cc: 'GHC' Subject: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating) PUBLIC OK so I tried out OverloadedStrings and it basically went as bad as I expected. The documentation on `HsOverLit` is very promising: it points to the Note [Overloaded literal witnesses], which states: Note [Overloaded literal witnesses] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ *Before* type checking, the HsExpr in an HsOverLit is the name of the coercion function, 'fromInteger' or 'fromRational'. So that sounds great, right? It sounds like just before renaming, I should be able to replace `HsLit _ (HsString _ fs)` with `HsOverLit _ (OverLit _ (HsIsString _ fs) unpack` with my own `unpack` function coming from my own package, and everything would work out. Unfortunately, this is not what happens: if I try getting this through the renamer, I get this error: Failed to load interface for 'Data.String' no unit id matching 'base' was found Can't find interface-file declaration for variable fromString Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error So even though I am specifying my own coercion function, it is still looking for `Data.String.fromString` which is not going to work, since I don't have `base`. So either I am misunderstanding that Note, or it is simply out of date, but in either case, this isn't going to be a viable route to going base-less. Gergo From: Erdi, Gergo Sent: Tuesday, July 6, 2021 5:39 PM To: Simon Peyton Jones > Cc: GHC > Subject: RE: Marking ParsedModule fragments as non-user-originating PUBLIC Thanks Simon! Of course, you're right, it's the renamer, not the typechecker - I didn't really check, just saw that "it happens during `typecheckModule`. I'll look at the rebindable syntax stuff in detail, but at least for OverloadedStrings, I already know that the problem will be that ultimately they do go through the `String` type from `base`, and I need to use GHC baselessly. This is a problem for two reasons: * I can't implement `IsString` for `MyString`, because `IsString` is in `base` * Even if I made my own fake `base` with a fake `IsString` class, there is nothing to put in the codomain of `fromString`: I *only* have `MyString`, not `String`. And renaming `MyString to `String` in my fake `base` is not going to cut it, since `String` is wired into GHC to be a type synonym for `[Char]` (which `MyString` is not). I foresee similar problems for OverloadedLists :/ Thanks, Gergo From: Simon Peyton Jones > Sent: Tuesday, July 6, 2021 5:08 PM To: Erdi, Gergo > Cc: GHC > Subject: [External] RE: Marking ParsedModule fragments as non-user-originating The typechecker now complains that the `ViewPatterns` language extension is not turned on I think it's the renamer: rnPatAndThen mk p@(ViewPat _ expr pat) = do { liftCps $ do { vp_flag <- xoptM LangExt.ViewPatterns ; checkErr vp_flag (badViewPat p) } More generally, don't you just want OverloadedStrings or OverloadedLists? You might want to read Note [Handling overloaded and rebindable constructs] in GHC.Rename.Expr, and Note [Rebindable syntax and HsExpansion] in GCH.Hs.Expr. These Notes describe how GHC already does something similar to what you want. Maybe you can use the same mechanism in your plugin. Simon From: ghc-devs > On Behalf Of Erdi, Gergo via ghc-devs Sent: 06 July 2021 09:08 To: ghc-devs at haskell.org Subject: Marking ParsedModule fragments as non-user-originating PUBLIC Hi, I'd like to hijack some syntax (like string literals or list patterns) for my own use, and I thought a low-tech way of doing that is to transform the ParsedModule before typechecking. For example, if I have a function `uncons :: Array a -> Maybe (a, Array a)`, I can rewrite the pattern `[x1, x2, x3]` into the view pattern `(uncons -> Just (x1, (uncons -> Just (x2, (uncons -> Just (x3, (uncons -> Nothing)))))))` and let the normal GHC type checker take over from here. This is working for me so far, except for one problem: the typechecker now complains that the `ViewPatterns` language extension is not turned on. I would like to make the view patterns coming from my ParsedModule rewriter to be exempt from this check (but of course still require the `ViewPatterns` extension for user-originating code). Is there a way to do that? Or would I be better off checking for user-originating view patterns myself before the rewrite and then changing the `DynFlags` to always enable view patterns for typechecking? Thanks, Gergo 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 Mon Jul 12 08:21:19 2021 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Mon, 12 Jul 2021 08:21:19 +0000 Subject: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating) In-Reply-To: References: Message-ID: PUBLIC I don't really understand how my question fits into the 'bug report' bucket. The quoted passage is not from the user manual, but rather, from a GHC Note. My reading of that note was that if I write a string literal in a Haskell program, and compile it with OverloadedStrings, it would parse into `HsLit _ (HsString _ fs)` with `HsOverLit _ (OverLit _ (HsIsString _ fs) "Data.String.fromString"`, and then the renamer and the type checker would work from that. If this understanding were correct, then I could generate parsed (and not yet renamed/typechecked) code that is, instead, `HsOverLit _ (OverLit _ (HsIsString _ fs) "myStringLitUnpackerFunction"`, and there would be no `fromString` dependency. Yet, that's not what seems to happen. Can you (or anyone else) go into more detail about how rebindable syntax resolution and OverloadedStrings interacts in this particular case? I am not interested in end-to-end behaviour, but what actually happens GHC phase by GHC phase. When is the reference to `fromString` introduced, when is it resolved (by default to `Data.String.fromString`), does `RebindableSyntax` allo me to replace not just `fromString`, but also `unpackCString#`? From: Simon Peyton Jones Sent: Monday, July 12, 2021 3:32 PM To: Erdi, Gergo Cc: 'GHC' Subject: [External] RE: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating) Gergo, If you think you have uncovered a bug, could you submit a bug report on the issue tracker, with a way to reproduce it? It's a bit hard to decode exactly what is happening from what you say. The user manual documentation doesn't say this in so many words (that's a bug), but with OverloadedStrings, the literal "foo" is replaced by Data.String.fromString "foo" Guessing a bit, that is probably why GHC complains that it can't load Data.String.fromString. If in addition you want to use your own fromString, not the built-in one, then you need to add RebindableSyntax. Simon From: Erdi, Gergo > Sent: 12 July 2021 08:13 To: Simon Peyton Jones > Cc: 'GHC' > Subject: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating) PUBLIC OK so I tried out OverloadedStrings and it basically went as bad as I expected. The documentation on `HsOverLit` is very promising: it points to the Note [Overloaded literal witnesses], which states: Note [Overloaded literal witnesses] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ *Before* type checking, the HsExpr in an HsOverLit is the name of the coercion function, 'fromInteger' or 'fromRational'. So that sounds great, right? It sounds like just before renaming, I should be able to replace `HsLit _ (HsString _ fs)` with `HsOverLit _ (OverLit _ (HsIsString _ fs) unpack` with my own `unpack` function coming from my own package, and everything would work out. Unfortunately, this is not what happens: if I try getting this through the renamer, I get this error: Failed to load interface for 'Data.String' no unit id matching 'base' was found Can't find interface-file declaration for variable fromString Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error So even though I am specifying my own coercion function, it is still looking for `Data.String.fromString` which is not going to work, since I don't have `base`. So either I am misunderstanding that Note, or it is simply out of date, but in either case, this isn't going to be a viable route to going base-less. Gergo From: Erdi, Gergo Sent: Tuesday, July 6, 2021 5:39 PM To: Simon Peyton Jones > Cc: GHC > Subject: RE: Marking ParsedModule fragments as non-user-originating PUBLIC Thanks Simon! Of course, you're right, it's the renamer, not the typechecker - I didn't really check, just saw that "it happens during `typecheckModule`. I'll look at the rebindable syntax stuff in detail, but at least for OverloadedStrings, I already know that the problem will be that ultimately they do go through the `String` type from `base`, and I need to use GHC baselessly. This is a problem for two reasons: * I can't implement `IsString` for `MyString`, because `IsString` is in `base` * Even if I made my own fake `base` with a fake `IsString` class, there is nothing to put in the codomain of `fromString`: I *only* have `MyString`, not `String`. And renaming `MyString to `String` in my fake `base` is not going to cut it, since `String` is wired into GHC to be a type synonym for `[Char]` (which `MyString` is not). I foresee similar problems for OverloadedLists :/ Thanks, Gergo From: Simon Peyton Jones > Sent: Tuesday, July 6, 2021 5:08 PM To: Erdi, Gergo > Cc: GHC > Subject: [External] RE: Marking ParsedModule fragments as non-user-originating The typechecker now complains that the `ViewPatterns` language extension is not turned on I think it's the renamer: rnPatAndThen mk p@(ViewPat _ expr pat) = do { liftCps $ do { vp_flag <- xoptM LangExt.ViewPatterns ; checkErr vp_flag (badViewPat p) } More generally, don't you just want OverloadedStrings or OverloadedLists? You might want to read Note [Handling overloaded and rebindable constructs] in GHC.Rename.Expr, and Note [Rebindable syntax and HsExpansion] in GCH.Hs.Expr. These Notes describe how GHC already does something similar to what you want. Maybe you can use the same mechanism in your plugin. Simon From: ghc-devs > On Behalf Of Erdi, Gergo via ghc-devs Sent: 06 July 2021 09:08 To: ghc-devs at haskell.org Subject: Marking ParsedModule fragments as non-user-originating PUBLIC Hi, I'd like to hijack some syntax (like string literals or list patterns) for my own use, and I thought a low-tech way of doing that is to transform the ParsedModule before typechecking. For example, if I have a function `uncons :: Array a -> Maybe (a, Array a)`, I can rewrite the pattern `[x1, x2, x3]` into the view pattern `(uncons -> Just (x1, (uncons -> Just (x2, (uncons -> Just (x3, (uncons -> Nothing)))))))` and let the normal GHC type checker take over from here. This is working for me so far, except for one problem: the typechecker now complains that the `ViewPatterns` language extension is not turned on. I would like to make the view patterns coming from my ParsedModule rewriter to be exempt from this check (but of course still require the `ViewPatterns` extension for user-originating code). Is there a way to do that? Or would I be better off checking for user-originating view patterns myself before the rewrite and then changing the `DynFlags` to always enable view patterns for typechecking? Thanks, Gergo 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 simonpj at microsoft.com Mon Jul 12 08:37:25 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 12 Jul 2021 08:37:25 +0000 Subject: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating) In-Reply-To: References: Message-ID: I don't really understand how my question fits into the 'bug report' bucket. The quoted passage is not from the user manual, but rather, from a GHC Note Only that GHC is doing something that you think is wrong - or at least not as documented. If so, that's a bug. If not, the conversation is illuminating, and more easily rediscovered later in the bug tracker. I am not interested in end-to-end behaviour, but what actually happens GHC phase by GHC phase. When is the reference to `fromString` introduced, when is it resolved (by default to `Data.String.fromString`), does `RebindableSyntax` allo me to replace not just `fromString`, but also `unpackCString#`? I'm happy to help - but can I ask that when you think you understand, can you submit a patch that clarifies the relevant Note(s), or adds one, so that the Gergos of the future will find the answer laid out right where you tried to find it? In GHC.Rename.Pat rnOverLit origLit = do { opt_NumDecimals <- xoptM LangExt.NumDecimals ; let { lit@(OverLit {ol_val=val}) | opt_NumDecimals = origLit {ol_val = generalizeOverLitVal (ol_val origLit)} | otherwise = origLit } ; let std_name = hsOverLitName val ; (from_thing_name, fvs1) <- lookupSyntaxName std_name * hsOverLitName returns Data.String.fromString for string literals. That is where fromString first appears. * Then lookupSyntaxName just returns Data.String.fromString when RebindableSyntax is off; or looks up "fromString" when RebindableSyntax is on. When I say "Data.String.fromString" here, I mean the original name i.e. the fromString defined in Data.String - not some possibly different entity that happens to be in scope with the qualified name "Data.String.fromString". Does that help? From: Erdi, Gergo Sent: 12 July 2021 09:21 To: Simon Peyton Jones Cc: 'GHC' Subject: RE: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating) PUBLIC I don't really understand how my question fits into the 'bug report' bucket. The quoted passage is not from the user manual, but rather, from a GHC Note. My reading of that note was that if I write a string literal in a Haskell program, and compile it with OverloadedStrings, it would parse into `HsLit _ (HsString _ fs)` with `HsOverLit _ (OverLit _ (HsIsString _ fs) "Data.String.fromString"`, and then the renamer and the type checker would work from that. If this understanding were correct, then I could generate parsed (and not yet renamed/typechecked) code that is, instead, `HsOverLit _ (OverLit _ (HsIsString _ fs) "myStringLitUnpackerFunction"`, and there would be no `fromString` dependency. Yet, that's not what seems to happen. Can you (or anyone else) go into more detail about how rebindable syntax resolution and OverloadedStrings interacts in this particular case? I am not interested in end-to-end behaviour, but what actually happens GHC phase by GHC phase. When is the reference to `fromString` introduced, when is it resolved (by default to `Data.String.fromString`), does `RebindableSyntax` allo me to replace not just `fromString`, but also `unpackCString#`? From: Simon Peyton Jones > Sent: Monday, July 12, 2021 3:32 PM To: Erdi, Gergo > Cc: 'GHC' > Subject: [External] RE: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating) Gergo, If you think you have uncovered a bug, could you submit a bug report on the issue tracker, with a way to reproduce it? It's a bit hard to decode exactly what is happening from what you say. The user manual documentation doesn't say this in so many words (that's a bug), but with OverloadedStrings, the literal "foo" is replaced by Data.String.fromString "foo" Guessing a bit, that is probably why GHC complains that it can't load Data.String.fromString. If in addition you want to use your own fromString, not the built-in one, then you need to add RebindableSyntax. Simon From: Erdi, Gergo > Sent: 12 July 2021 08:13 To: Simon Peyton Jones > Cc: 'GHC' > Subject: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating) PUBLIC OK so I tried out OverloadedStrings and it basically went as bad as I expected. The documentation on `HsOverLit` is very promising: it points to the Note [Overloaded literal witnesses], which states: Note [Overloaded literal witnesses] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ *Before* type checking, the HsExpr in an HsOverLit is the name of the coercion function, 'fromInteger' or 'fromRational'. So that sounds great, right? It sounds like just before renaming, I should be able to replace `HsLit _ (HsString _ fs)` with `HsOverLit _ (OverLit _ (HsIsString _ fs) unpack` with my own `unpack` function coming from my own package, and everything would work out. Unfortunately, this is not what happens: if I try getting this through the renamer, I get this error: Failed to load interface for 'Data.String' no unit id matching 'base' was found Can't find interface-file declaration for variable fromString Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error So even though I am specifying my own coercion function, it is still looking for `Data.String.fromString` which is not going to work, since I don't have `base`. So either I am misunderstanding that Note, or it is simply out of date, but in either case, this isn't going to be a viable route to going base-less. Gergo From: Erdi, Gergo Sent: Tuesday, July 6, 2021 5:39 PM To: Simon Peyton Jones > Cc: GHC > Subject: RE: Marking ParsedModule fragments as non-user-originating PUBLIC Thanks Simon! Of course, you're right, it's the renamer, not the typechecker - I didn't really check, just saw that "it happens during `typecheckModule`. I'll look at the rebindable syntax stuff in detail, but at least for OverloadedStrings, I already know that the problem will be that ultimately they do go through the `String` type from `base`, and I need to use GHC baselessly. This is a problem for two reasons: * I can't implement `IsString` for `MyString`, because `IsString` is in `base` * Even if I made my own fake `base` with a fake `IsString` class, there is nothing to put in the codomain of `fromString`: I *only* have `MyString`, not `String`. And renaming `MyString to `String` in my fake `base` is not going to cut it, since `String` is wired into GHC to be a type synonym for `[Char]` (which `MyString` is not). I foresee similar problems for OverloadedLists :/ Thanks, Gergo From: Simon Peyton Jones > Sent: Tuesday, July 6, 2021 5:08 PM To: Erdi, Gergo > Cc: GHC > Subject: [External] RE: Marking ParsedModule fragments as non-user-originating The typechecker now complains that the `ViewPatterns` language extension is not turned on I think it's the renamer: rnPatAndThen mk p@(ViewPat _ expr pat) = do { liftCps $ do { vp_flag <- xoptM LangExt.ViewPatterns ; checkErr vp_flag (badViewPat p) } More generally, don't you just want OverloadedStrings or OverloadedLists? You might want to read Note [Handling overloaded and rebindable constructs] in GHC.Rename.Expr, and Note [Rebindable syntax and HsExpansion] in GCH.Hs.Expr. These Notes describe how GHC already does something similar to what you want. Maybe you can use the same mechanism in your plugin. Simon From: ghc-devs > On Behalf Of Erdi, Gergo via ghc-devs Sent: 06 July 2021 09:08 To: ghc-devs at haskell.org Subject: Marking ParsedModule fragments as non-user-originating PUBLIC Hi, I'd like to hijack some syntax (like string literals or list patterns) for my own use, and I thought a low-tech way of doing that is to transform the ParsedModule before typechecking. For example, if I have a function `uncons :: Array a -> Maybe (a, Array a)`, I can rewrite the pattern `[x1, x2, x3]` into the view pattern `(uncons -> Just (x1, (uncons -> Just (x2, (uncons -> Just (x3, (uncons -> Nothing)))))))` and let the normal GHC type checker take over from here. This is working for me so far, except for one problem: the typechecker now complains that the `ViewPatterns` language extension is not turned on. I would like to make the view patterns coming from my ParsedModule rewriter to be exempt from this check (but of course still require the `ViewPatterns` extension for user-originating code). Is there a way to do that? Or would I be better off checking for user-originating view patterns myself before the rewrite and then changing the `DynFlags` to always enable view patterns for typechecking? Thanks, Gergo 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 Gergo.Erdi at sc.com Mon Jul 12 08:58:43 2021 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Mon, 12 Jul 2021 08:58:43 +0000 Subject: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating) In-Reply-To: References: Message-ID: PUBLIC Thanks, this is useful and it is starting to convince myself that there *is* a documentation bug here. It seems the big thing I was missing was the existence of `hsOverLitName`. That's what returns `Data.String.fromString` for overloaded string literals. But then, does that mean that the `ol_witness` field of the `OverLit` is not used by the renamer at all? This contradicts the Note, or maybe I am reading it too wishfully - maybe the intention of `ol_witness` is to be for "entertainment purposes only", i.e. something provided by the parser for third-party tools but not consumed by the renamer. Or maybe `ol_witness` is only to be used in getting information *from* the renamer to the typechecker (note that the code you pasted below doesn't use the input's `ol_witness` field for anything at all), in which case instead of just fixing the docs, we should move `ol_witness` from `HsOverLit` to `XOverLit GhcRn` and `XOverLit GhcTc`. I'm happy to prepare a patch for this (code + Note) if you agree this is the correct reading of the current code. Thanks, Gergo From: Simon Peyton Jones Sent: Monday, July 12, 2021 4:37 PM To: Erdi, Gergo Cc: 'GHC' Subject: [External] RE: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating) I don't really understand how my question fits into the 'bug report' bucket. The quoted passage is not from the user manual, but rather, from a GHC Note Only that GHC is doing something that you think is wrong - or at least not as documented. If so, that's a bug. If not, the conversation is illuminating, and more easily rediscovered later in the bug tracker. I am not interested in end-to-end behaviour, but what actually happens GHC phase by GHC phase. When is the reference to `fromString` introduced, when is it resolved (by default to `Data.String.fromString`), does `RebindableSyntax` allo me to replace not just `fromString`, but also `unpackCString#`? I'm happy to help - but can I ask that when you think you understand, can you submit a patch that clarifies the relevant Note(s), or adds one, so that the Gergos of the future will find the answer laid out right where you tried to find it? In GHC.Rename.Pat rnOverLit origLit = do { opt_NumDecimals <- xoptM LangExt.NumDecimals ; let { lit@(OverLit {ol_val=val}) | opt_NumDecimals = origLit {ol_val = generalizeOverLitVal (ol_val origLit)} | otherwise = origLit } ; let std_name = hsOverLitName val ; (from_thing_name, fvs1) <- lookupSyntaxName std_name * hsOverLitName returns Data.String.fromString for string literals. That is where fromString first appears. * Then lookupSyntaxName just returns Data.String.fromString when RebindableSyntax is off; or looks up "fromString" when RebindableSyntax is on. When I say "Data.String.fromString" here, I mean the original name i.e. the fromString defined in Data.String - not some possibly different entity that happens to be in scope with the qualified name "Data.String.fromString". Does that help? From: Erdi, Gergo > Sent: 12 July 2021 09:21 To: Simon Peyton Jones > Cc: 'GHC' > Subject: RE: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating) PUBLIC I don't really understand how my question fits into the 'bug report' bucket. The quoted passage is not from the user manual, but rather, from a GHC Note. My reading of that note was that if I write a string literal in a Haskell program, and compile it with OverloadedStrings, it would parse into `HsLit _ (HsString _ fs)` with `HsOverLit _ (OverLit _ (HsIsString _ fs) "Data.String.fromString"`, and then the renamer and the type checker would work from that. If this understanding were correct, then I could generate parsed (and not yet renamed/typechecked) code that is, instead, `HsOverLit _ (OverLit _ (HsIsString _ fs) "myStringLitUnpackerFunction"`, and there would be no `fromString` dependency. Yet, that's not what seems to happen. Can you (or anyone else) go into more detail about how rebindable syntax resolution and OverloadedStrings interacts in this particular case? I am not interested in end-to-end behaviour, but what actually happens GHC phase by GHC phase. When is the reference to `fromString` introduced, when is it resolved (by default to `Data.String.fromString`), does `RebindableSyntax` allo me to replace not just `fromString`, but also `unpackCString#`? From: Simon Peyton Jones > Sent: Monday, July 12, 2021 3:32 PM To: Erdi, Gergo > Cc: 'GHC' > Subject: [External] RE: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating) Gergo, If you think you have uncovered a bug, could you submit a bug report on the issue tracker, with a way to reproduce it? It's a bit hard to decode exactly what is happening from what you say. The user manual documentation doesn't say this in so many words (that's a bug), but with OverloadedStrings, the literal "foo" is replaced by Data.String.fromString "foo" Guessing a bit, that is probably why GHC complains that it can't load Data.String.fromString. If in addition you want to use your own fromString, not the built-in one, then you need to add RebindableSyntax. Simon From: Erdi, Gergo > Sent: 12 July 2021 08:13 To: Simon Peyton Jones > Cc: 'GHC' > Subject: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating) PUBLIC OK so I tried out OverloadedStrings and it basically went as bad as I expected. The documentation on `HsOverLit` is very promising: it points to the Note [Overloaded literal witnesses], which states: Note [Overloaded literal witnesses] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ *Before* type checking, the HsExpr in an HsOverLit is the name of the coercion function, 'fromInteger' or 'fromRational'. So that sounds great, right? It sounds like just before renaming, I should be able to replace `HsLit _ (HsString _ fs)` with `HsOverLit _ (OverLit _ (HsIsString _ fs) unpack` with my own `unpack` function coming from my own package, and everything would work out. Unfortunately, this is not what happens: if I try getting this through the renamer, I get this error: Failed to load interface for 'Data.String' no unit id matching 'base' was found Can't find interface-file declaration for variable fromString Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error So even though I am specifying my own coercion function, it is still looking for `Data.String.fromString` which is not going to work, since I don't have `base`. So either I am misunderstanding that Note, or it is simply out of date, but in either case, this isn't going to be a viable route to going base-less. Gergo From: Erdi, Gergo Sent: Tuesday, July 6, 2021 5:39 PM To: Simon Peyton Jones > Cc: GHC > Subject: RE: Marking ParsedModule fragments as non-user-originating PUBLIC Thanks Simon! Of course, you're right, it's the renamer, not the typechecker - I didn't really check, just saw that "it happens during `typecheckModule`. I'll look at the rebindable syntax stuff in detail, but at least for OverloadedStrings, I already know that the problem will be that ultimately they do go through the `String` type from `base`, and I need to use GHC baselessly. This is a problem for two reasons: * I can't implement `IsString` for `MyString`, because `IsString` is in `base` * Even if I made my own fake `base` with a fake `IsString` class, there is nothing to put in the codomain of `fromString`: I *only* have `MyString`, not `String`. And renaming `MyString to `String` in my fake `base` is not going to cut it, since `String` is wired into GHC to be a type synonym for `[Char]` (which `MyString` is not). I foresee similar problems for OverloadedLists :/ Thanks, Gergo From: Simon Peyton Jones > Sent: Tuesday, July 6, 2021 5:08 PM To: Erdi, Gergo > Cc: GHC > Subject: [External] RE: Marking ParsedModule fragments as non-user-originating The typechecker now complains that the `ViewPatterns` language extension is not turned on I think it's the renamer: rnPatAndThen mk p@(ViewPat _ expr pat) = do { liftCps $ do { vp_flag <- xoptM LangExt.ViewPatterns ; checkErr vp_flag (badViewPat p) } More generally, don't you just want OverloadedStrings or OverloadedLists? You might want to read Note [Handling overloaded and rebindable constructs] in GHC.Rename.Expr, and Note [Rebindable syntax and HsExpansion] in GCH.Hs.Expr. These Notes describe how GHC already does something similar to what you want. Maybe you can use the same mechanism in your plugin. Simon From: ghc-devs > On Behalf Of Erdi, Gergo via ghc-devs Sent: 06 July 2021 09:08 To: ghc-devs at haskell.org Subject: Marking ParsedModule fragments as non-user-originating PUBLIC Hi, I'd like to hijack some syntax (like string literals or list patterns) for my own use, and I thought a low-tech way of doing that is to transform the ParsedModule before typechecking. For example, if I have a function `uncons :: Array a -> Maybe (a, Array a)`, I can rewrite the pattern `[x1, x2, x3]` into the view pattern `(uncons -> Just (x1, (uncons -> Just (x2, (uncons -> Just (x3, (uncons -> Nothing)))))))` and let the normal GHC type checker take over from here. This is working for me so far, except for one problem: the typechecker now complains that the `ViewPatterns` language extension is not turned on. I would like to make the view patterns coming from my ParsedModule rewriter to be exempt from this check (but of course still require the `ViewPatterns` extension for user-originating code). Is there a way to do that? Or would I be better off checking for user-originating view patterns myself before the rewrite and then changing the `DynFlags` to always enable view patterns for typechecking? Thanks, Gergo 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. 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 lists at richarde.dev Mon Jul 12 13:41:53 2021 From: lists at richarde.dev (Richard Eisenberg) Date: Mon, 12 Jul 2021 13:41:53 +0000 Subject: Can NamedFieldPuns be added to `GHC.LanguageExtensions.Types.Extension`? In-Reply-To: References: Message-ID: <010f017a9af3e62c-04941688-b4e7-4457-9073-25907bf53eed-000000@us-east-2.amazonses.com> I think we just go ahead and rename the constructor. We don't have back-compat guarantees at this level. Simplicity is a virtue, too! Thanks, Richard > On Jul 6, 2021, at 5:59 AM, Alfredo Di Napoli wrote: > > > Hello Simon, > > Yes, renaming and perhaps keeping `RecordPuns` as a pattern synonym to not break backward-compat, if that's feasible to define as we are in `ghc-boot-th` here. Not sure if `PatternSynonyms` and `COMPLETE` would be available there. > > I am not sure how many libs that depend on the ghc API would break (I haven't grepped on Hackage yet), but that might tip the benefits/troubles ratio towards keeping the status quo. > > This is not a "problem" I have to solve today, and it might not be considered a problem by others (just an inconsistency I guess): as a colleague of mine pointed out, GHC is not necessarily "lying" here. It's still the same underlying extension, it just happens that there are two names that refer to it. > > Perhaps I could think about adding to `GhcHint` some kind of mapping which would give to IDEs or third-party libs the correct extension name given an input `LangExt.Extension`, the problem then becomes making sure that we keep this mapping in sync with the information contained in `GHC.Driver.Session`. > > I will let it simmer. > > Thanks! > > A. > > On Tue, 6 Jul 2021 at 11:19, Simon Peyton Jones > wrote: > 1. What prevents us from adding `NamedFieldPuns` as a proper constructor for the `Extension` type and in principle remove `RecordPuns`? Backward compatibility I assume? > > You mean, essentially, rename `LangExt.RecordPuns` to `NamedFieldPuns`. > > > > I’d be fine with that. There might be back-compat issues, but only with other plugins, and probably with vanishingly few of them. Grep in Hackage! > > > > Simon > > > > From: ghc-devs > On Behalf Of Alfredo Di Napoli > Sent: 06 July 2021 10:14 > To: Simon Peyton Jones via ghc-devs > > Subject: Can NamedFieldPuns be added to `GHC.LanguageExtensions.Types.Extension`? > > > > Dear all, > > > > As some of you might know, for the past few months I have been working on changing GHC's diagnostic messages from plain SDocs to richer Haskell types. > > > > As part of this work, I have added a mechanism to embed hints into diagnostics, defined in `GHC.Types.Hint` in `HEAD`. One of the main workhorse of this `GhcHint` type is the `SuggestExtension LangExt.Extension` constructor, which embeds the extension to enable to use a particular feature. The `LangExt.Extension` type comes from `GHC.LanguageExtensions.Types`, and up until now there has always been a 1:1 mapping between the language pragma for the extension and the type itself. > > > > Today I was working on turning this error into a proper Haskell type: > > > > badPun :: Located RdrName -> TcRnMessage > > badPun fld = TcRnUnknownMessage $ mkPlainError noHints $ > > vcat [text "Illegal use of punning for field" <+> quotes (ppr fld), > > text "Use NamedFieldPuns to permit this"] > > > > I was ready to yield a `SuggestExtension LangExt.NamedFieldPuns` when I discovered that there is no `NamedFieldPuns` constructor. Rather, there is a `RecordPuns` , which refer to a deprecated flag, and we simply map `NamedFieldPuns` back to it in `GHC.Driver.Session`: > > > > ... > > depFlagSpec' "RecordPuns" LangExt.RecordPuns > > (deprecatedForExtension "NamedFieldPuns"), > > ... > > flagSpec "NamedFieldPuns" LangExt.RecordPuns, > > ... > > > > This is problematic for the `GhcHint` type, because now if I was to yield `SuggestExtension LangExt.RecordPuns` to the user, I could still pretty-print the suggestion to turn `RecordPuns` into `NamedFieldPuns`, but this means that IDEs or third-party library would have access to the > > "raw" Haskell datatype, and at that point they will be stuck with a suggestion to enable a deprecated extension! (or best case scenario they will have to transform the suggestion into something more sensible, which partially defeats the point of this refactoring work I have been doing). > > > > I am not sure this behaviour is unique for just `NamedFieldPuns`, but my question is: > > > > 1. What prevents us from adding `NamedFieldPuns` as a proper constructor for the `Extension` type and in principle remove `RecordPuns`? Backward compatibility I assume? > > > > > > Many thanks, > > > > Alfredo > > > > > > > > > > > > > > > > > > _______________________________________________ > 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 ekmett at gmail.com Mon Jul 12 15:07:50 2021 From: ekmett at gmail.com (Edward Kmett) Date: Mon, 12 Jul 2021 08:07:50 -0700 Subject: Can NamedFieldPuns be added to `GHC.LanguageExtensions.Types.Extension`? In-Reply-To: References: Message-ID: There's always pattern synonyms as an option for cases like this, free of backwards compat issues. -Edward On Tue, Jul 6, 2021 at 3:00 AM Alfredo Di Napoli wrote: > > Hello Simon, > > Yes, renaming and perhaps keeping `RecordPuns` as a pattern synonym to not > break backward-compat, if that's feasible to define as we are in > `ghc-boot-th` here. Not sure if `PatternSynonyms` and `COMPLETE` would be > available there. > > I am not sure how many libs that depend on the ghc API would break (I > haven't grepped on Hackage yet), but that might tip the benefits/troubles > ratio towards keeping the status quo. > > This is not a "problem" I have to solve today, and it might not be > considered a problem by others (just an inconsistency I guess): as a > colleague of mine pointed out, GHC is not necessarily "lying" here. It's > still the same underlying extension, it just happens that there are two > names that refer to it. > > Perhaps I could think about adding to `GhcHint` some kind of mapping which > would give to IDEs or third-party libs the correct extension name given an > input `LangExt.Extension`, the problem then becomes making sure that we > keep this mapping in sync with the information contained in > `GHC.Driver.Session`. > > I will let it simmer. > > Thanks! > > A. > > On Tue, 6 Jul 2021 at 11:19, Simon Peyton Jones > wrote: > >> 1. What prevents us from adding `NamedFieldPuns` as a proper constructor >> for the `Extension` type and in principle remove `RecordPuns`? Backward >> compatibility I assume? >> >> You mean, essentially, rename `LangExt.RecordPuns` to `NamedFieldPuns`. >> >> >> >> I’d be fine with that. There might be back-compat issues, but only with >> other plugins, and probably with vanishingly few of them. Grep in Hackage! >> >> >> >> Simon >> >> >> >> *From:* ghc-devs *On Behalf Of *Alfredo >> Di Napoli >> *Sent:* 06 July 2021 10:14 >> *To:* Simon Peyton Jones via ghc-devs >> *Subject:* Can NamedFieldPuns be added to >> `GHC.LanguageExtensions.Types.Extension`? >> >> >> >> Dear all, >> >> >> >> As some of you might know, for the past few months I have been working on >> changing GHC's diagnostic messages from plain SDocs to richer Haskell types. >> >> >> >> As part of this work, I have added a mechanism to embed hints into >> diagnostics, defined in `GHC.Types.Hint` in `HEAD`. One of the main >> workhorse of this `GhcHint` type is the `SuggestExtension >> LangExt.Extension` constructor, which embeds the extension to enable to use >> a particular feature. The `LangExt.Extension` type comes from >> `GHC.LanguageExtensions.Types`, and up until now there has always been a >> 1:1 mapping between the language pragma for the extension and the type >> itself. >> >> >> >> Today I was working on turning this error into a proper Haskell type: >> >> >> >> badPun :: Located RdrName -> TcRnMessage >> >> badPun fld = TcRnUnknownMessage $ mkPlainError noHints $ >> >> vcat [text "Illegal use of punning for field" <+> quotes (ppr fld), >> >> text "Use NamedFieldPuns to permit this"] >> >> >> >> I was ready to yield a `SuggestExtension LangExt.NamedFieldPuns` when I >> discovered that there is no `NamedFieldPuns` constructor. Rather, there is >> a `RecordPuns` , which refer to a deprecated flag, and we simply map >> `NamedFieldPuns` back to it in `GHC.Driver.Session`: >> >> >> >> ... >> >> depFlagSpec' "RecordPuns" LangExt.RecordPuns >> >> (deprecatedForExtension "NamedFieldPuns"), >> >> ... >> >> flagSpec "NamedFieldPuns" LangExt.RecordPuns, >> >> ... >> >> >> >> This is problematic for the `GhcHint` type, because now if I was to yield >> `SuggestExtension LangExt.RecordPuns` to the user, I could still >> pretty-print the suggestion to turn `RecordPuns` into `NamedFieldPuns`, but >> this means that IDEs or third-party library would have access to the >> >> "raw" Haskell datatype, and at that point they will be stuck with a >> suggestion to enable a deprecated extension! (or best case scenario they >> will have to transform the suggestion into something more sensible, which >> partially defeats the point of this refactoring work I have been doing). >> >> >> >> I am not sure this behaviour is unique for just `NamedFieldPuns`, but my >> question is: >> >> >> >> 1. What prevents us from adding `NamedFieldPuns` as a proper constructor >> for the `Extension` type and in principle remove `RecordPuns`? Backward >> compatibility I assume? >> >> >> >> >> >> Many thanks, >> >> >> >> Alfredo >> >> >> >> >> >> >> >> >> >> >> >> >> >> >> >> >> > _______________________________________________ > 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 alfredo.dinapoli at gmail.com Tue Jul 13 07:08:20 2021 From: alfredo.dinapoli at gmail.com (Alfredo Di Napoli) Date: Tue, 13 Jul 2021 09:08:20 +0200 Subject: Can NamedFieldPuns be added to `GHC.LanguageExtensions.Types.Extension`? In-Reply-To: References: Message-ID: Hello all, I am happy to see engagement on this issue. I didn't read Ed's and Richard's replies until now, but I have indeed explored the pattern synonym solution, which I have materialised in a MR here: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/6156 As I say in the MR description, the only small downside is the beefy `COMPLETE` pragma, but we gain the possibility of deprecating the extension a bit more explicitly, which is nice. Feedback welcome! :) Thanks, Alfredo On Mon, 12 Jul 2021 at 17:08, Edward Kmett wrote: > There's always pattern synonyms as an option for cases like this, free of > backwards compat issues. > > -Edward > > On Tue, Jul 6, 2021 at 3:00 AM Alfredo Di Napoli < > alfredo.dinapoli at gmail.com> wrote: > >> >> Hello Simon, >> >> Yes, renaming and perhaps keeping `RecordPuns` as a pattern synonym to >> not break backward-compat, if that's feasible to define as we are in >> `ghc-boot-th` here. Not sure if `PatternSynonyms` and `COMPLETE` would be >> available there. >> >> I am not sure how many libs that depend on the ghc API would break (I >> haven't grepped on Hackage yet), but that might tip the benefits/troubles >> ratio towards keeping the status quo. >> >> This is not a "problem" I have to solve today, and it might not be >> considered a problem by others (just an inconsistency I guess): as a >> colleague of mine pointed out, GHC is not necessarily "lying" here. It's >> still the same underlying extension, it just happens that there are two >> names that refer to it. >> >> Perhaps I could think about adding to `GhcHint` some kind of mapping >> which would give to IDEs or third-party libs the correct extension name >> given an input `LangExt.Extension`, the problem then becomes making sure >> that we keep this mapping in sync with the information contained in >> `GHC.Driver.Session`. >> >> I will let it simmer. >> >> Thanks! >> >> A. >> >> On Tue, 6 Jul 2021 at 11:19, Simon Peyton Jones >> wrote: >> >>> 1. What prevents us from adding `NamedFieldPuns` as a proper constructor >>> for the `Extension` type and in principle remove `RecordPuns`? Backward >>> compatibility I assume? >>> >>> You mean, essentially, rename `LangExt.RecordPuns` to `NamedFieldPuns`. >>> >>> >>> >>> I’d be fine with that. There might be back-compat issues, but only with >>> other plugins, and probably with vanishingly few of them. Grep in Hackage! >>> >>> >>> >>> Simon >>> >>> >>> >>> *From:* ghc-devs *On Behalf Of *Alfredo >>> Di Napoli >>> *Sent:* 06 July 2021 10:14 >>> *To:* Simon Peyton Jones via ghc-devs >>> *Subject:* Can NamedFieldPuns be added to >>> `GHC.LanguageExtensions.Types.Extension`? >>> >>> >>> >>> Dear all, >>> >>> >>> >>> As some of you might know, for the past few months I have been working >>> on changing GHC's diagnostic messages from plain SDocs to richer Haskell >>> types. >>> >>> >>> >>> As part of this work, I have added a mechanism to embed hints into >>> diagnostics, defined in `GHC.Types.Hint` in `HEAD`. One of the main >>> workhorse of this `GhcHint` type is the `SuggestExtension >>> LangExt.Extension` constructor, which embeds the extension to enable to use >>> a particular feature. The `LangExt.Extension` type comes from >>> `GHC.LanguageExtensions.Types`, and up until now there has always been a >>> 1:1 mapping between the language pragma for the extension and the type >>> itself. >>> >>> >>> >>> Today I was working on turning this error into a proper Haskell type: >>> >>> >>> >>> badPun :: Located RdrName -> TcRnMessage >>> >>> badPun fld = TcRnUnknownMessage $ mkPlainError noHints $ >>> >>> vcat [text "Illegal use of punning for field" <+> quotes (ppr fld), >>> >>> text "Use NamedFieldPuns to permit this"] >>> >>> >>> >>> I was ready to yield a `SuggestExtension LangExt.NamedFieldPuns` when I >>> discovered that there is no `NamedFieldPuns` constructor. Rather, there is >>> a `RecordPuns` , which refer to a deprecated flag, and we simply map >>> `NamedFieldPuns` back to it in `GHC.Driver.Session`: >>> >>> >>> >>> ... >>> >>> depFlagSpec' "RecordPuns" LangExt.RecordPuns >>> >>> (deprecatedForExtension "NamedFieldPuns"), >>> >>> ... >>> >>> flagSpec "NamedFieldPuns" LangExt.RecordPuns, >>> >>> ... >>> >>> >>> >>> This is problematic for the `GhcHint` type, because now if I was to >>> yield `SuggestExtension LangExt.RecordPuns` to the user, I could still >>> pretty-print the suggestion to turn `RecordPuns` into `NamedFieldPuns`, but >>> this means that IDEs or third-party library would have access to the >>> >>> "raw" Haskell datatype, and at that point they will be stuck with a >>> suggestion to enable a deprecated extension! (or best case scenario they >>> will have to transform the suggestion into something more sensible, which >>> partially defeats the point of this refactoring work I have been doing). >>> >>> >>> >>> I am not sure this behaviour is unique for just `NamedFieldPuns`, but my >>> question is: >>> >>> >>> >>> 1. What prevents us from adding `NamedFieldPuns` as a proper constructor >>> for the `Extension` type and in principle remove `RecordPuns`? Backward >>> compatibility I assume? >>> >>> >>> >>> >>> >>> Many thanks, >>> >>> >>> >>> Alfredo >>> >>> >>> >>> >>> >>> >>> >>> >>> >>> >>> >>> >>> >>> >>> >>> >>> >> _______________________________________________ >> 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.Erdi at sc.com Tue Jul 13 08:02:09 2021 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Tue, 13 Jul 2021 08:02:09 +0000 Subject: mkIfaceTc panics with "lookupVers1" Message-ID: PUBLIC Hi, I'm trying to use `mkIfaceTc` to make a ModIface from the results of typechecking. Everything goes well until it gets to `makeFullIface`, where it fails to find some imported fingerprints: hello: hello: panic! (the 'impossible' happened) (GHC version 9.0.1: lookupVers1 MyPrim Foo Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/GHC/Utils/Outputable.hs:1230:37 in ghc-lib-9.0.1.20210623-3xx7a2u7IkN9vKAnkscROb:GHC.Utils.Outputable pprPanic, called at compiler/GHC/Iface/Recomp.hs:1455:19 in ghc-lib-9.0.1.20210623-3xx7a2u7IkN9vKAnkscROb:GHC.Iface.Recomp I am using the GHC API to load my modules differently than what GHC itself does; I am attaching the full code, but perhaps to note is that I am creating ModSummarys one by one and then typechecking and adding them to the moduleNameProviderMap in dependency order. Also, I am using `downsweep` directly instead of `depanal`, because the latter's `flushFinderCaches` was breaking my inter-unit imports. Because the attached code is a minimized version of something larger, some parts of it may seem to be doing things in a roundabout way but that's because in the real program all those degrees of freedom are used. In case that matters, the only packages in my package DB are rts, ghc-prim-0.7.0 and ghc-bignum-1.0. So my question is basically, what am I doing wrong? Why is fingerprinting failing on `Top.hs`'s import of `MyPrim.hs`, and how do I fix that, while still keeping this total control over when and how modules are typechecked and loaded? Thanks, Gergo 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: -------------- next part -------------- A non-text attachment was scrubbed... Name: Top.hs Type: application/octet-stream Size: 83 bytes Desc: Top.hs URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: Main.hs Type: application/octet-stream Size: 4236 bytes Desc: Main.hs URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: MyPrim.hs Type: application/octet-stream Size: 89 bytes Desc: MyPrim.hs URL: From omeragacan at gmail.com Wed Jul 14 06:27:11 2021 From: omeragacan at gmail.com (=?UTF-8?Q?=C3=96mer_Sinan_A=C4=9Facan?=) Date: Wed, 14 Jul 2021 09:27:11 +0300 Subject: Potential improvement in compacting GC In-Reply-To: References: Message-ID: Two other ideas that should improve GHC's compacting GC much more significantly. I've implemented both of these in another project and the results were great. In a GC benchmark (mutator does almost no work other than allocating data using a bump allocator), first one reduced Wasm instructions executed by 14%, second one 19.8%. Both of these ideas require pushing object headers to the mark stack with the objects, which means larger mark stacks. This is the only downside of these algorithms. - Instead of marking and then threading in the next pass, mark phase threads all fields when pushing the fields to the mark stack. We still need two other passes: one to unthread headers, another to move the objects. (we can't do both in one pass, let me know if you're curious and I can elaborate) This has the same number of passes as the current implementation, but it only visits object fields once. Currently, we visit fields once when marking, to mark fields, then again in `update_fwd`. This implementation does both in one pass over the fields. `update_fwd` does not visit fields. This reduced Wasm instructions executed by 14% in my benchmark. - Marking phase threads backwards pointers (ignores forwards pointers). Then we do one pass instead of two: for a marked object, unthread it (update forwards pointers to the object's new location), move it to its new location, then thread its forwards pointers. This completely eliminates one of the 3 passes, but fields need to be visited twice as before (unlike the algorithm above). I think this one is originally described in "An Efficient Garbage Compaction Algorithm", but I found that paper to be difficult to follow. A short description of the same algorithm exists in "High-Performance Garbage Collection for Memory-Constrained Environments" in section 5.1.2. This reduced Wasm instructions executed by 19.8% in my benchmark. In this algorithm, fields that won't be moved can be threaded any time before the second pass (pointed objects need to be marked and pushed to the mark stack with headers before threading a field). For example, in GHC, mut list entries can be threaded before or after marking (but before the second pass) as IIRC mut lists are not moved. Same for fields of large objects. As far as I can see, mark-compact GC is still the default when max heap size is specified and the oldest generation size is (by default) more than 30% of the max heap size. I'm not sure if max heap size is specified often (it's off by default), so not sure what would be the impact of these improvements be, but if anyone would be interested in funding me to implement these ideas (second algorithm above, and the bitmap iteration in the previous email) I could try to allocate one or two days a week to finish in a few months. Normally these are simple changes, but it's difficult to test and debug GHC's RTS as we don't have a test suite readily available and the code is not easily testable. In my previous implementations of these algorithms I had unit tests for the GC where I could easily generate arbitrary graphs (with cycles, backwards ptrs, forwards ptrs, ptrs from/to roots etc.) and test GC in isolation. Implementation of (2) took less than a day, and I didn't have to debug it more once the tests passed. It's really unfortunate that GHC's RTS makes this kind of thing difficult.. Ömer Ömer Sinan Ağacan , 7 Oca 2021 Per, 20:42 tarihinde şunu yazdı: > > Hello, > > I recently implemented the algorithm used by GHC's compacting GC in another > project. The algorithm (after marking) makes two passes over the heap > /generation. In GHC, these passes are implemented in [1] and in the next > function. > > In my implementation I tried 3 ways of implementing these passes, one of which > is the same as GHC's code, and benchmarked each version. I found that the > fastest implementation is not what's used in GHC, but it could easily be used. > > I should mention that my code targets Wasm, and I benchmarked Wasm instructions > executed. Not CPU cycles, CPU instructions, or anything like that. It's very > likely that the results will be different when benchmarking code running on > actual hardware. > > Secondly, in my case the heap is mostly dead (residency is low). In GHC, > compaction for the oldest generation is enabled when residency passes a > threshold, so the assumption is the heap is mostly live. I'm guessing this > should also make some difference. > > Anyway, the first implementation I tried was similar to GHC's scan, but I did > > scan += object_size(scan); > > instead of bumping scan by one, as GHC does in [2]. This was the slowest > version. > > Second implementation did the same as GHC (bumped scan by one). This was > faster, but still slower than the next version. > > What I found to be the best is scanning the bitmap, not the heap. The bitmap > iterator reads one word at a time. In each iteration it checks if the bitmap > word is 0. In GHC, in the best case this can skip 16 words on heap on 32-bit > systems, and 32 words on 64-bit. Reminder: we need two bits per object in the > bitmap, see [3]. (this is not the case in my implementation so the payoff is > better) > > When the bitmap word is not 0 I use "count trailing zeros" (or "count leading > zeros" depending on the bitmap implementation) to get the number of words to > skip. This is a single instruction on Wasm and x86 (TZCNT or LZCNT, available > via __builtin_ctzl and __builtin_clzl in gcc). > > So instead of skipping one word at a time, this can potentially skip 16 words > (or 32 on 64-bit architectures). When that's not possible, it can still skip > multiple words by using ctz/clz. > > Ömer > > [1]: https://github.com/ghc/ghc/blob/bd877edd9499a351db947cd51ed583872b2facdf/rts/sm/Compact.c#L824-L879 > [2]: https://github.com/ghc/ghc/blob/bd877edd9499a351db947cd51ed583872b2facdf/rts/sm/Compact.c#L838 > [3]: https://github.com/ghc/ghc/blob/bd877edd9499a351db947cd51ed583872b2facdf/rts/sm/Compact.h#L18-L55 From simonpj at microsoft.com Wed Jul 14 08:12:08 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 14 Jul 2021 08:12:08 +0000 Subject: Potential improvement in compacting GC In-Reply-To: References: Message-ID: Thanks Omer I had an interesting conversation with Steve Blackburn, the brains behind the MMTk memory management toolkit recently https://www.mmtk.io/ MMTk is designed to be a re-usable, open-source garbage collector, specifically designed to be usable with lots of languages. In principle this is a great idea: GC is such a big field that no runtime (GHC's included) can ever devote enough effort to GC to do a really state of the art job. It makes sense for one bunch of people to stellar GC and another bunch to simply reuse their work. Of course, the interface between the GC and the mutator, scheduler, etc is particularly intimate. Teasing them apart in GHC would be a significant task, and success would not be guaranteed. But Steve is interested in working on this, with help from our end, perhaps initially with a student (or volunteer) project or two. If it worked, it'd be cool. Here's a talk about MMTk: https://www.youtube.com/watch?v=3L6XEVaYAmU Simon | -----Original Message----- | From: ghc-devs On Behalf Of Ömer Sinan | Agacan | Sent: 14 July 2021 07:27 | To: ghc-devs | Subject: Re: Potential improvement in compacting GC | | Two other ideas that should improve GHC's compacting GC much more | significantly. I've implemented both of these in another project and | the results were great. In a GC benchmark (mutator does almost no work | other than allocating data using a bump allocator), first one reduced | Wasm instructions executed by 14%, second one 19.8%. | | Both of these ideas require pushing object headers to the mark stack | with the objects, which means larger mark stacks. This is the only | downside of these algorithms. | | - Instead of marking and then threading in the next pass, mark phase | threads | all fields when pushing the fields to the mark stack. We still need | two other | passes: one to unthread headers, another to move the objects. (we | can't do | both in one pass, let me know if you're curious and I can elaborate) | | This has the same number of passes as the current implementation, | but it only | visits object fields once. Currently, we visit fields once when | marking, to | mark fields, then again in `update_fwd`. This implementation does | both in one | pass over the fields. `update_fwd` does not visit fields. | | This reduced Wasm instructions executed by 14% in my benchmark. | | - Marking phase threads backwards pointers (ignores forwards | pointers). Then we | do one pass instead of two: for a marked object, unthread it (update | forwards pointers to the object's new location), move it to its new | location, | then thread its forwards pointers. This completely eliminates one of | the 3 | passes, but fields need to be visited twice as before (unlike the | algorithm | above). | | I think this one is originally described in "An Efficient Garbage | Compaction | Algorithm", but I found that paper to be difficult to follow. A | short | description of the same algorithm exists in "High-Performance | Garbage | Collection for Memory-Constrained Environments" in section 5.1.2. | | This reduced Wasm instructions executed by 19.8% in my benchmark. | | In this algorithm, fields that won't be moved can be threaded any | time before | the second pass (pointed objects need to be marked and pushed to the | mark | stack with headers before threading a field). For example, in GHC, | mut list | entries can be threaded before or after marking (but before the | second pass) | as IIRC mut lists are not moved. Same for fields of large objects. | | As far as I can see, mark-compact GC is still the default when max | heap size is specified and the oldest generation size is (by default) | more than 30% of the max heap size. I'm not sure if max heap size is | specified often (it's off by default), so not sure what would be the | impact of these improvements be, but if anyone would be interested in | funding me to implement these ideas (second algorithm above, and the | bitmap iteration in the previous email) I could try to allocate one or | two days a week to finish in a few months. | | Normally these are simple changes, but it's difficult to test and | debug GHC's RTS as we don't have a test suite readily available and | the code is not easily testable. In my previous implementations of | these algorithms I had unit tests for the GC where I could easily | generate arbitrary graphs (with cycles, backwards ptrs, forwards ptrs, | ptrs from/to roots etc.) and test GC in isolation. Implementation of | (2) took less than a day, and I didn't have to debug it more once the | tests passed. It's really unfortunate that GHC's RTS makes this kind | of thing difficult.. | | Ömer | | Ömer Sinan Ağacan , 7 Oca 2021 Per, 20:42 | tarihinde şunu yazdı: | > | > Hello, | > | > I recently implemented the algorithm used by GHC's compacting GC in | > another project. The algorithm (after marking) makes two passes over | > the heap /generation. In GHC, these passes are implemented in [1] | and | > in the next function. | > | > In my implementation I tried 3 ways of implementing these passes, | one | > of which is the same as GHC's code, and benchmarked each version. I | > found that the fastest implementation is not what's used in GHC, but | it could easily be used. | > | > I should mention that my code targets Wasm, and I benchmarked Wasm | > instructions executed. Not CPU cycles, CPU instructions, or anything | > like that. It's very likely that the results will be different when | > benchmarking code running on actual hardware. | > | > Secondly, in my case the heap is mostly dead (residency is low). In | > GHC, compaction for the oldest generation is enabled when residency | > passes a threshold, so the assumption is the heap is mostly live. | I'm | > guessing this should also make some difference. | > | > Anyway, the first implementation I tried was similar to GHC's scan, | > but I did | > | > scan += object_size(scan); | > | > instead of bumping scan by one, as GHC does in [2]. This was the | > slowest version. | > | > Second implementation did the same as GHC (bumped scan by one). This | > was faster, but still slower than the next version. | > | > What I found to be the best is scanning the bitmap, not the heap. | The | > bitmap iterator reads one word at a time. In each iteration it | checks | > if the bitmap word is 0. In GHC, in the best case this can skip 16 | > words on heap on 32-bit systems, and 32 words on 64-bit. Reminder: | we | > need two bits per object in the bitmap, see [3]. (this is not the | case | > in my implementation so the payoff is | > better) | > | > When the bitmap word is not 0 I use "count trailing zeros" (or | "count | > leading zeros" depending on the bitmap implementation) to get the | > number of words to skip. This is a single instruction on Wasm and | x86 | > (TZCNT or LZCNT, available via __builtin_ctzl and __builtin_clzl in | gcc). | > | > So instead of skipping one word at a time, this can potentially skip | > 16 words (or 32 on 64-bit architectures). When that's not possible, | it | > can still skip multiple words by using ctz/clz. | > | > Ömer | > | > [1]: | > | https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgith | > | ub.com%2Fghc%2Fghc%2Fblob%2Fbd877edd9499a351db947cd51ed583872b2facdf%2 | > Frts%2Fsm%2FCompact.c%23L824- | L879&data=04%7C01%7Csimonpj%40microso | > | ft.com%7C58ade0545503419b747d08d9469092de%7C72f988bf86f141af91ab2d7cd0 | > | 11db47%7C1%7C0%7C637618409054020073%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC | > | 4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000&sd | > ata=H3RvKMPjE%2BvQExIgu5HRudVAZ20YWcPonrLFKnMbTYI%3D&reserved=0 | > [2]: | > | https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgith | > | ub.com%2Fghc%2Fghc%2Fblob%2Fbd877edd9499a351db947cd51ed583872b2facdf%2 | > | Frts%2Fsm%2FCompact.c%23L838&data=04%7C01%7Csimonpj%40microsoft.co | > | m%7C58ade0545503419b747d08d9469092de%7C72f988bf86f141af91ab2d7cd011db4 | > | 7%7C1%7C0%7C637618409054020073%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjA | > | wMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000&sdata=t | > VqznK82Q9rs%2F2jpONLFbzhfVmUQ2sr4mIsCH2cxKAc%3D&reserved=0 | > [3]: | > | https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgith | > | ub.com%2Fghc%2Fghc%2Fblob%2Fbd877edd9499a351db947cd51ed583872b2facdf%2 | > Frts%2Fsm%2FCompact.h%23L18- | L55&data=04%7C01%7Csimonpj%40microsoft | > | .com%7C58ade0545503419b747d08d9469092de%7C72f988bf86f141af91ab2d7cd011 | > | db47%7C1%7C0%7C637618409054020073%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4w | > | LjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000&sdat | > a=uHwS5OpCRIF7UZd92i05SKnl0y1ZK2UojgATLxm7WHc%3D&reserved=0 | _______________________________________________ | ghc-devs mailing list | ghc-devs at haskell.org | https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail. | haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc- | devs&data=04%7C01%7Csimonpj%40microsoft.com%7C58ade0545503419b747d | 08d9469092de%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637618409054 | 020073%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJ | BTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000&sdata=xCUxl2w2wsIsKDenizmmNh6pE | LHCQhbdhJIn%2B5tTDps%3D&reserved=0 From compl.yue at icloud.com Wed Jul 14 09:28:48 2021 From: compl.yue at icloud.com (YueCompl) Date: Wed, 14 Jul 2021 17:28:48 +0800 Subject: Potential improvement in compacting GC In-Reply-To: References: Message-ID: <0433C73B-001E-4CE0-94BA-9C48FC8EF9FF@icloud.com> Greetings! I'd like to take this opportunity to ask you experts about feasibility / technology-readiness of distributed GC, that I've recently been pondering with the idea to have a distributed GC managing shared heap across multiple server nodes, those inter-connected through fast ethernet. I'm implementing an array database system for internal use, each array is constrained to flat address space so no GC is required within one. But the number of arrays are unexpectedly large as my use cases becoming more apparent. Managing relations between those arrays (i.e. meta data) has appeared as far beyond the computational capacity of a single physical PC server (even powerful ones in today's market). We are working around this limitation by restricting meta data to be mappable to directory structure of underlying filesystem, but it's quite limiting from business perspective. We use FUSE filesystem driver to handle fine grained data coherence control over these many small arrays, to be accessed by many concurrent client machines, by exposing a large virtual file for mmap on each client, to efficiently leverage os kernel pages as good shared cache storage, backing multiple processes running on each client os. I'd imagine shared heap with https://hackage.haskell.org/package/compact and a GC to have structural meta data managed likewise, so each client can mmap the entire shared heap, but only load relevant kernel pages on demand of the data nodes as it explores the information graph. This way the native programming language assumes the role of Data Manipulation Language as well, and Query Language can be simply some optimized data structures wrapped with accessing lib functions, more importantly the database system will have great horizontal scalability. And the whole architecture will have little technical debt as it seems so far. So how feasible it is that you see? I'm aware that [compact] is still some experimental, and not even portable across GHC compilations yet, but it seems solvable with enough effort put in. Thanks, Compl > On 2021-07-14, at 16:12, Simon Peyton Jones via ghc-devs wrote: > > Thanks Omer > > I had an interesting conversation with Steve Blackburn, the brains behind > the MMTk memory management toolkit recently > https://www.mmtk.io/ > > MMTk is designed to be a re-usable, open-source garbage collector, specifically > designed to be usable with lots of languages. In principle this is a great > idea: GC is such a big field that no runtime (GHC's included) can ever devote > enough effort to GC to do a really state of the art job. It makes sense for > one bunch of people to stellar GC and another bunch to simply reuse their > work. > > Of course, the interface between the GC and the mutator, scheduler, etc > is particularly intimate. Teasing them apart in GHC would be a significant > task, and success would not be guaranteed. > > But Steve is interested in working on this, with help from our end, perhaps > initially with a student (or volunteer) project or two. > > If it worked, it'd be cool. > > Here's a talk about MMTk: https://www.youtube.com/watch?v=3L6XEVaYAmU > > Simon > > > | -----Original Message----- > | From: ghc-devs On Behalf Of Ömer Sinan > | Agacan > | Sent: 14 July 2021 07:27 > | To: ghc-devs > | Subject: Re: Potential improvement in compacting GC > | > | Two other ideas that should improve GHC's compacting GC much more > | significantly. I've implemented both of these in another project and > | the results were great. In a GC benchmark (mutator does almost no work > | other than allocating data using a bump allocator), first one reduced > | Wasm instructions executed by 14%, second one 19.8%. > | > | Both of these ideas require pushing object headers to the mark stack > | with the objects, which means larger mark stacks. This is the only > | downside of these algorithms. > | > | - Instead of marking and then threading in the next pass, mark phase > | threads > | all fields when pushing the fields to the mark stack. We still need > | two other > | passes: one to unthread headers, another to move the objects. (we > | can't do > | both in one pass, let me know if you're curious and I can elaborate) > | > | This has the same number of passes as the current implementation, > | but it only > | visits object fields once. Currently, we visit fields once when > | marking, to > | mark fields, then again in `update_fwd`. This implementation does > | both in one > | pass over the fields. `update_fwd` does not visit fields. > | > | This reduced Wasm instructions executed by 14% in my benchmark. > | > | - Marking phase threads backwards pointers (ignores forwards > | pointers). Then we > | do one pass instead of two: for a marked object, unthread it (update > | forwards pointers to the object's new location), move it to its new > | location, > | then thread its forwards pointers. This completely eliminates one of > | the 3 > | passes, but fields need to be visited twice as before (unlike the > | algorithm > | above). > | > | I think this one is originally described in "An Efficient Garbage > | Compaction > | Algorithm", but I found that paper to be difficult to follow. A > | short > | description of the same algorithm exists in "High-Performance > | Garbage > | Collection for Memory-Constrained Environments" in section 5.1.2. > | > | This reduced Wasm instructions executed by 19.8% in my benchmark. > | > | In this algorithm, fields that won't be moved can be threaded any > | time before > | the second pass (pointed objects need to be marked and pushed to the > | mark > | stack with headers before threading a field). For example, in GHC, > | mut list > | entries can be threaded before or after marking (but before the > | second pass) > | as IIRC mut lists are not moved. Same for fields of large objects. > | > | As far as I can see, mark-compact GC is still the default when max > | heap size is specified and the oldest generation size is (by default) > | more than 30% of the max heap size. I'm not sure if max heap size is > | specified often (it's off by default), so not sure what would be the > | impact of these improvements be, but if anyone would be interested in > | funding me to implement these ideas (second algorithm above, and the > | bitmap iteration in the previous email) I could try to allocate one or > | two days a week to finish in a few months. > | > | Normally these are simple changes, but it's difficult to test and > | debug GHC's RTS as we don't have a test suite readily available and > | the code is not easily testable. In my previous implementations of > | these algorithms I had unit tests for the GC where I could easily > | generate arbitrary graphs (with cycles, backwards ptrs, forwards ptrs, > | ptrs from/to roots etc.) and test GC in isolation. Implementation of > | (2) took less than a day, and I didn't have to debug it more once the > | tests passed. It's really unfortunate that GHC's RTS makes this kind > | of thing difficult.. > | > | Ömer > | > | Ömer Sinan Ağacan , 7 Oca 2021 Per, 20:42 > | tarihinde şunu yazdı: > | > > | > Hello, > | > > | > I recently implemented the algorithm used by GHC's compacting GC in > | > another project. The algorithm (after marking) makes two passes over > | > the heap /generation. In GHC, these passes are implemented in [1] > | and > | > in the next function. > | > > | > In my implementation I tried 3 ways of implementing these passes, > | one > | > of which is the same as GHC's code, and benchmarked each version. I > | > found that the fastest implementation is not what's used in GHC, but > | it could easily be used. > | > > | > I should mention that my code targets Wasm, and I benchmarked Wasm > | > instructions executed. Not CPU cycles, CPU instructions, or anything > | > like that. It's very likely that the results will be different when > | > benchmarking code running on actual hardware. > | > > | > Secondly, in my case the heap is mostly dead (residency is low). In > | > GHC, compaction for the oldest generation is enabled when residency > | > passes a threshold, so the assumption is the heap is mostly live. > | I'm > | > guessing this should also make some difference. > | > > | > Anyway, the first implementation I tried was similar to GHC's scan, > | > but I did > | > > | > scan += object_size(scan); > | > > | > instead of bumping scan by one, as GHC does in [2]. This was the > | > slowest version. > | > > | > Second implementation did the same as GHC (bumped scan by one). This > | > was faster, but still slower than the next version. > | > > | > What I found to be the best is scanning the bitmap, not the heap. > | The > | > bitmap iterator reads one word at a time. In each iteration it > | checks > | > if the bitmap word is 0. In GHC, in the best case this can skip 16 > | > words on heap on 32-bit systems, and 32 words on 64-bit. Reminder: > | we > | > need two bits per object in the bitmap, see [3]. (this is not the > | case > | > in my implementation so the payoff is > | > better) > | > > | > When the bitmap word is not 0 I use "count trailing zeros" (or > | "count > | > leading zeros" depending on the bitmap implementation) to get the > | > number of words to skip. This is a single instruction on Wasm and > | x86 > | > (TZCNT or LZCNT, available via __builtin_ctzl and __builtin_clzl in > | gcc). > | > > | > So instead of skipping one word at a time, this can potentially skip > | > 16 words (or 32 on 64-bit architectures). When that's not possible, > | it > | > can still skip multiple words by using ctz/clz. > | > > | > Ömer > | > > | > [1]: > | > > | https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgith > | > > | ub.com%2Fghc%2Fghc%2Fblob%2Fbd877edd9499a351db947cd51ed583872b2facdf%2 > | > Frts%2Fsm%2FCompact.c%23L824- > | L879&data=04%7C01%7Csimonpj%40microso > | > > | ft.com%7C58ade0545503419b747d08d9469092de%7C72f988bf86f141af91ab2d7cd0 > | > > | 11db47%7C1%7C0%7C637618409054020073%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC > | > > | 4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000&sd > | > ata=H3RvKMPjE%2BvQExIgu5HRudVAZ20YWcPonrLFKnMbTYI%3D&reserved=0 > | > [2]: > | > > | https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgith > | > > | ub.com%2Fghc%2Fghc%2Fblob%2Fbd877edd9499a351db947cd51ed583872b2facdf%2 > | > > | Frts%2Fsm%2FCompact.c%23L838&data=04%7C01%7Csimonpj%40microsoft.co > | > > | m%7C58ade0545503419b747d08d9469092de%7C72f988bf86f141af91ab2d7cd011db4 > | > > | 7%7C1%7C0%7C637618409054020073%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjA > | > > | wMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000&sdata=t > | > VqznK82Q9rs%2F2jpONLFbzhfVmUQ2sr4mIsCH2cxKAc%3D&reserved=0 > | > [3]: > | > > | https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgith > | > > | ub.com%2Fghc%2Fghc%2Fblob%2Fbd877edd9499a351db947cd51ed583872b2facdf%2 > | > Frts%2Fsm%2FCompact.h%23L18- > | L55&data=04%7C01%7Csimonpj%40microsoft > | > > | .com%7C58ade0545503419b747d08d9469092de%7C72f988bf86f141af91ab2d7cd011 > | > > | db47%7C1%7C0%7C637618409054020073%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4w > | > > | LjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000&sdat > | > a=uHwS5OpCRIF7UZd92i05SKnl0y1ZK2UojgATLxm7WHc%3D&reserved=0 > | _______________________________________________ > | ghc-devs mailing list > | ghc-devs at haskell.org > | https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail. > | haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc- > | devs&data=04%7C01%7Csimonpj%40microsoft.com%7C58ade0545503419b747d > | 08d9469092de%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637618409054 > | 020073%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJ > | BTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000&sdata=xCUxl2w2wsIsKDenizmmNh6pE > | LHCQhbdhJIn%2B5tTDps%3D&reserved=0 > _______________________________________________ > 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 simonpj at microsoft.com Fri Jul 16 23:12:42 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Fri, 16 Jul 2021 23:12:42 +0000 Subject: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating) In-Reply-To: References: Message-ID: But then, does that mean that the `ol_witness` field of the `OverLit` is not used by the renamer at all? * In (HsOverLit GhcPs), which is the output of the parser, and the input of the renamer, the ol_witness field is garbage. See GHC.Hs.Utils.mkHsIntegral, which fills that field with `noExpr`. * In (HsOverLit GhcRn), which is the output of the renamer, and the input of the typechecker, the ol_witness fiels is (HsVar ), of type (HsExpr GhcRn), where is the Name of the fromX function. * In (HsOverLit GhcTc), which is the output of the typechecker and the input of the desugarer, the ol_witness field is the expression (fromX lit), of type (HsExpr GhcTc), the literal value itself. Some, but not all, of this is stated in Note [Overloaded literal witnesses] in Language.Haskell.Syntax.Lit.hs maybe the intention of `ol_witness` is to be for "entertainment purposes only", Not exactly. In the parser we have to make a field of type (HsExpr GhcPs), and that's what noExpr is. But no one looks it, ever. in which case instead of just fixing the docs, we should move `ol_witness` from `HsOverLit` to `XOverLit GhcRn` and `XOverLit GhcTc`. Yes, it would be much better to use the extension field. That would stop the (GHC-independent) Language.Haskell.Syntax needing to talk about "witnesses". If you tackle this (which would be great) you might want to look at the other uses of noExpr too. OK? Maybe start by making a ticket for this change. Simon From: Erdi, Gergo Sent: 12 July 2021 09:59 To: Simon Peyton Jones Cc: 'GHC' Subject: RE: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating) PUBLIC Thanks, this is useful and it is starting to convince myself that there *is* a documentation bug here. It seems the big thing I was missing was the existence of `hsOverLitName`. That's what returns `Data.String.fromString` for overloaded string literals. But then, does that mean that the `ol_witness` field of the `OverLit` is not used by the renamer at all? This contradicts the Note, or maybe I am reading it too wishfully - maybe the intention of `ol_witness` is to be for "entertainment purposes only", i.e. something provided by the parser for third-party tools but not consumed by the renamer. Or maybe `ol_witness` is only to be used in getting information *from* the renamer to the typechecker (note that the code you pasted below doesn't use the input's `ol_witness` field for anything at all), in which case instead of just fixing the docs, we should move `ol_witness` from `HsOverLit` to `XOverLit GhcRn` and `XOverLit GhcTc`. I'm happy to prepare a patch for this (code + Note) if you agree this is the correct reading of the current code. Thanks, Gergo From: Simon Peyton Jones > Sent: Monday, July 12, 2021 4:37 PM To: Erdi, Gergo > Cc: 'GHC' > Subject: [External] RE: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating) I don't really understand how my question fits into the 'bug report' bucket. The quoted passage is not from the user manual, but rather, from a GHC Note Only that GHC is doing something that you think is wrong - or at least not as documented. If so, that's a bug. If not, the conversation is illuminating, and more easily rediscovered later in the bug tracker. I am not interested in end-to-end behaviour, but what actually happens GHC phase by GHC phase. When is the reference to `fromString` introduced, when is it resolved (by default to `Data.String.fromString`), does `RebindableSyntax` allo me to replace not just `fromString`, but also `unpackCString#`? I'm happy to help - but can I ask that when you think you understand, can you submit a patch that clarifies the relevant Note(s), or adds one, so that the Gergos of the future will find the answer laid out right where you tried to find it? In GHC.Rename.Pat rnOverLit origLit = do { opt_NumDecimals <- xoptM LangExt.NumDecimals ; let { lit@(OverLit {ol_val=val}) | opt_NumDecimals = origLit {ol_val = generalizeOverLitVal (ol_val origLit)} | otherwise = origLit } ; let std_name = hsOverLitName val ; (from_thing_name, fvs1) <- lookupSyntaxName std_name * hsOverLitName returns Data.String.fromString for string literals. That is where fromString first appears. * Then lookupSyntaxName just returns Data.String.fromString when RebindableSyntax is off; or looks up "fromString" when RebindableSyntax is on. When I say "Data.String.fromString" here, I mean the original name i.e. the fromString defined in Data.String - not some possibly different entity that happens to be in scope with the qualified name "Data.String.fromString". Does that help? From: Erdi, Gergo > Sent: 12 July 2021 09:21 To: Simon Peyton Jones > Cc: 'GHC' > Subject: RE: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating) PUBLIC I don't really understand how my question fits into the 'bug report' bucket. The quoted passage is not from the user manual, but rather, from a GHC Note. My reading of that note was that if I write a string literal in a Haskell program, and compile it with OverloadedStrings, it would parse into `HsLit _ (HsString _ fs)` with `HsOverLit _ (OverLit _ (HsIsString _ fs) "Data.String.fromString"`, and then the renamer and the type checker would work from that. If this understanding were correct, then I could generate parsed (and not yet renamed/typechecked) code that is, instead, `HsOverLit _ (OverLit _ (HsIsString _ fs) "myStringLitUnpackerFunction"`, and there would be no `fromString` dependency. Yet, that's not what seems to happen. Can you (or anyone else) go into more detail about how rebindable syntax resolution and OverloadedStrings interacts in this particular case? I am not interested in end-to-end behaviour, but what actually happens GHC phase by GHC phase. When is the reference to `fromString` introduced, when is it resolved (by default to `Data.String.fromString`), does `RebindableSyntax` allo me to replace not just `fromString`, but also `unpackCString#`? From: Simon Peyton Jones > Sent: Monday, July 12, 2021 3:32 PM To: Erdi, Gergo > Cc: 'GHC' > Subject: [External] RE: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating) Gergo, If you think you have uncovered a bug, could you submit a bug report on the issue tracker, with a way to reproduce it? It's a bit hard to decode exactly what is happening from what you say. The user manual documentation doesn't say this in so many words (that's a bug), but with OverloadedStrings, the literal "foo" is replaced by Data.String.fromString "foo" Guessing a bit, that is probably why GHC complains that it can't load Data.String.fromString. If in addition you want to use your own fromString, not the built-in one, then you need to add RebindableSyntax. Simon From: Erdi, Gergo > Sent: 12 July 2021 08:13 To: Simon Peyton Jones > Cc: 'GHC' > Subject: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating) PUBLIC OK so I tried out OverloadedStrings and it basically went as bad as I expected. The documentation on `HsOverLit` is very promising: it points to the Note [Overloaded literal witnesses], which states: Note [Overloaded literal witnesses] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ *Before* type checking, the HsExpr in an HsOverLit is the name of the coercion function, 'fromInteger' or 'fromRational'. So that sounds great, right? It sounds like just before renaming, I should be able to replace `HsLit _ (HsString _ fs)` with `HsOverLit _ (OverLit _ (HsIsString _ fs) unpack` with my own `unpack` function coming from my own package, and everything would work out. Unfortunately, this is not what happens: if I try getting this through the renamer, I get this error: Failed to load interface for 'Data.String' no unit id matching 'base' was found Can't find interface-file declaration for variable fromString Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error So even though I am specifying my own coercion function, it is still looking for `Data.String.fromString` which is not going to work, since I don't have `base`. So either I am misunderstanding that Note, or it is simply out of date, but in either case, this isn't going to be a viable route to going base-less. Gergo From: Erdi, Gergo Sent: Tuesday, July 6, 2021 5:39 PM To: Simon Peyton Jones > Cc: GHC > Subject: RE: Marking ParsedModule fragments as non-user-originating PUBLIC Thanks Simon! Of course, you're right, it's the renamer, not the typechecker - I didn't really check, just saw that "it happens during `typecheckModule`. I'll look at the rebindable syntax stuff in detail, but at least for OverloadedStrings, I already know that the problem will be that ultimately they do go through the `String` type from `base`, and I need to use GHC baselessly. This is a problem for two reasons: * I can't implement `IsString` for `MyString`, because `IsString` is in `base` * Even if I made my own fake `base` with a fake `IsString` class, there is nothing to put in the codomain of `fromString`: I *only* have `MyString`, not `String`. And renaming `MyString to `String` in my fake `base` is not going to cut it, since `String` is wired into GHC to be a type synonym for `[Char]` (which `MyString` is not). I foresee similar problems for OverloadedLists :/ Thanks, Gergo From: Simon Peyton Jones > Sent: Tuesday, July 6, 2021 5:08 PM To: Erdi, Gergo > Cc: GHC > Subject: [External] RE: Marking ParsedModule fragments as non-user-originating The typechecker now complains that the `ViewPatterns` language extension is not turned on I think it's the renamer: rnPatAndThen mk p@(ViewPat _ expr pat) = do { liftCps $ do { vp_flag <- xoptM LangExt.ViewPatterns ; checkErr vp_flag (badViewPat p) } More generally, don't you just want OverloadedStrings or OverloadedLists? You might want to read Note [Handling overloaded and rebindable constructs] in GHC.Rename.Expr, and Note [Rebindable syntax and HsExpansion] in GCH.Hs.Expr. These Notes describe how GHC already does something similar to what you want. Maybe you can use the same mechanism in your plugin. Simon From: ghc-devs > On Behalf Of Erdi, Gergo via ghc-devs Sent: 06 July 2021 09:08 To: ghc-devs at haskell.org Subject: Marking ParsedModule fragments as non-user-originating PUBLIC Hi, I'd like to hijack some syntax (like string literals or list patterns) for my own use, and I thought a low-tech way of doing that is to transform the ParsedModule before typechecking. For example, if I have a function `uncons :: Array a -> Maybe (a, Array a)`, I can rewrite the pattern `[x1, x2, x3]` into the view pattern `(uncons -> Just (x1, (uncons -> Just (x2, (uncons -> Just (x3, (uncons -> Nothing)))))))` and let the normal GHC type checker take over from here. This is working for me so far, except for one problem: the typechecker now complains that the `ViewPatterns` language extension is not turned on. I would like to make the view patterns coming from my ParsedModule rewriter to be exempt from this check (but of course still require the `ViewPatterns` extension for user-originating code). Is there a way to do that? Or would I be better off checking for user-originating view patterns myself before the rewrite and then changing the `DynFlags` to always enable view patterns for typechecking? Thanks, Gergo 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. 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 Mon Jul 19 16:35:13 2021 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Mon, 19 Jul 2021 17:35:13 +0100 Subject: FYI: Darwin CI currently broken for forks Message-ID: Hi all, There is a configuration issue with the darwin builders which has meant that for the last 6 days CI has been broken if you have pushed from a fork because the majority of darwin builders are only configured to work with branches pushed to the main project. These failures manifest as timeout errors (https://gitlab.haskell.org/blamario/ghc/-/jobs/733244). Hopefully this can be resolved in the coming days. Cheers, Matt From csaba.hruska at gmail.com Wed Jul 21 11:12:30 2021 From: csaba.hruska at gmail.com (Csaba Hruska) Date: Wed, 21 Jul 2021 13:12:30 +0200 Subject: Haskell program introspection tooling development. Message-ID: Hello, I'm using the external STG interpreter to introspect the runtime behaviour of Haskell programs. Lately I've added an initial call-graph construction feature that I plan to refine further. https://twitter.com/csaba_hruska/status/1417486380536582151 Is there anyone who has dynamic analysis related research ambitions and wants to study Haskell program runtime behaviour in detail? If so then it would be great to talk. Cheers, Csaba -------------- next part -------------- An HTML attachment was scrubbed... URL: From sam.derbyshire at gmail.com Thu Jul 22 18:51:14 2021 From: sam.derbyshire at gmail.com (Sam Derbyshire) Date: Thu, 22 Jul 2021 20:51:14 +0200 Subject: Rewriting plugins: request for feedback In-Reply-To: References: Message-ID: Hi everyone, I've uploaded the new type-checking plugin API to Hackage: https://hackage.haskell.org/package/ghc-tcplugin-api. Let me know how you get on. It should be much easier to iterate on the design and add new functionality, now that the API isn't tied to GHC. Thanks, Sam -------------- next part -------------- An HTML attachment was scrubbed... URL: From gergo at erdi.hu Fri Jul 23 09:14:32 2021 From: gergo at erdi.hu (=?ISO-8859-2?Q?=C9RDI_Gerg=F5?=) Date: Fri, 23 Jul 2021 17:14:32 +0800 (+08) Subject: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating) In-Reply-To: References: Message-ID: On Fri, 16 Jul 2021, Simon Peyton Jones via ghc-devs wrote: > Yes, it would be much better to use the extension field.  That would stop the > (GHC-independent) Language.Haskell.Syntax needing to talk about “witnesses”. Here it is: https://gitlab.haskell.org/ghc/ghc/-/issues/20151 From adam at sandbergericsson.se Fri Jul 23 20:43:08 2021 From: adam at sandbergericsson.se (Adam Sandberg Eriksson) Date: Fri, 23 Jul 2021 22:43:08 +0200 Subject: Is simplified subsumption really necessary? In-Reply-To: References: <40fcef62-e173-780d-5a5d-dd2d198647b3@obsidian.systems> <7293a3b9-eb08-a52f-996e-118d61c67f87@obsidian.systems> Message-ID: Somewhat related: while migrating quite a bit of code to GHC > 9 I found that after seeing some errors it was quite easy to identify (from error messages) when I needed to manually eta-expand something. I'm wondering if the error messages could be better (explicitly mentioning simplified subsumption and eta-expanding as a solution) or perhaps if the migration could even have been automated? The ship might have sailed on this too, but perhaps something to keep in mind for future changes. Adam Sandberg Eriksson On Sun, 20 Jun 2021, at 23:22, Simon Peyton Jones via ghc-devs wrote: > Yes, maybe the seq thing would be possible. But it feels like a hack, and I’m far from convinced that the optimiser would really eliminate the overhead. If I was convinced that deep subsumption was really better, it might be worth investigating the hack more deeply. But in fact I’ve become convinced of the opposite, that deep subsumption just isn’t worth the extra complexity – the simpler system allows Quick Look for example. > > Simon > > *From:* John Ericson > *Sent:* 20 June 2021 18:07 > *To:* ghc-devs ; Simon Peyton Jones > *Subject:* Re: Is simplified subsumption really necessary? > > I'm sorry, I misunderstood the paper and thought the depth of the instantiation and subsumption could be varied more independently. > > That said, what about the seq example below? Does forcing any function that is eta expanded like that sketchy to you? There is still a runtime cost to the eta expansion, but think with more elbow grease that could also be addressed (post-type-erasure optimization or new coercions). > > John > > On 6/18/21 3:56 PM, Simon Peyton Jones wrote: >> Richard’s paper argues for lazy rather than eager instantiation. >> >> It does *not* argue for deep rather than shallow subsumption and instantiation; on the contrary, it argues for shallow. (That is, for “simple subsumption”.) And it is simple subsumption that is the focus of this conversation. >> >> Simon >> >> *From:* John Ericson >> *Sent:* 18 June 2021 16:56 >> *To:* ghc-devs >> *Cc:* Simon Peyton Jones >> *Subject:* Re: Is simplified subsumption really necessary? >> >> On 6/16/21 12:00 PM, Simon Peyton Jones via ghc-devs wrote: >> >>> I’m sorry to hear that Chris. It’s exactly backwards from what I would expect – the typing rules with simple subsumption are, well, simpler than those for complicated subsumption, and so one might hope that your intuition had fewer complexities to grapple with. >> In https://richarde.dev/papers/2021/stability/stability.pdf it is written >> >>> The analysis around stability in this paper strongly suggests that GHC should use the lazy, shallow approach to instantiation. Yet the struggles with lazy instantiation above remain. In order to simplify the implementation, GHC has recently (for GHC 9.0) switched to use exclusively eager instantiation.This choice sacrifices stability for convenience in implementation. >>> >> I think the principles outlined in the paper are very good, and explain the queasiness some users may feel in 9.0 >> >>> >>> But wouldn't it be possible to choose a desugaring with seq that doesn't do so? >>> >>> I just don’t know how to do that. Maybe someone else does. >> Is it not >> >> f `seq` \x -> f x >> >> and similar? I haven't thought about the issue in a while or in very much depth, but when I first discussed the proposal years back with some other people at work, they spit-balled the same counter-proposal. >> >> ---- >> >> Having little "skin in the game" as I haven't yet ported any serious programs over to 9.0, I suppose I am glad the experimentation with QuickLook is happening, and OK that our accepting on-par fewer programs now opens design space for later (i.e. we got the breakage out of the way.) But I certainly think there are improvements in the spirit outlined in Richard's paper to be done down the road. >> >> John >> > _______________________________________________ > 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.Erdi at sc.com Tue Jul 27 07:11:30 2021 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Tue, 27 Jul 2021 07:11:30 +0000 Subject: Where else do I need to register fixity declarations? Message-ID: PUBLIC Hi, In the attached program, I am typechecking two Haskell modules with GHC 9.0.1: `Imported.hs` defines some infix operators, and `Importer.hs` uses them. After typechecking the first one, I put it in the moduleNameProvidersMap and the HPT. However, when I am typechecking the second one, the fixity declarations of the infix operators aren't picked up correctly. I know they aren't because I have defined operators that only typecheck if they are parsed right-associatively. In contrast, if I put both the definitions and the usage into the same file (`Standalone.hs`), typechecking succeeds (as I would expect it to). What am I doing wrong? Is filling the `mi_fixities` field of the `ModIface` not enough to let importers see the correct fixities? Thanks, Gergo 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: -------------- next part -------------- A non-text attachment was scrubbed... Name: Standalone.hs Type: application/octet-stream Size: 271 bytes Desc: Standalone.hs URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: Imported.hs Type: application/octet-stream Size: 162 bytes Desc: Imported.hs URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: Importer.hs Type: application/octet-stream Size: 181 bytes Desc: Importer.hs URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: Main.hs Type: application/octet-stream Size: 4912 bytes Desc: Main.hs URL: From gergo at erdi.hu Tue Jul 27 07:50:58 2021 From: gergo at erdi.hu (=?UTF-8?B?R2VyZ8WRIMOJcmRp?=) Date: Tue, 27 Jul 2021 15:50:58 +0800 Subject: Where else do I need to register fixity declarations? In-Reply-To: References: Message-ID: I should add that I've also tried adding the just-loaded module to the EPS but that also doesn't fix the issue. On Tue, Jul 27, 2021, 15:14 Erdi, Gergo via ghc-devs wrote: > > > Hi, > > > > In the attached program, I am typechecking two Haskell modules with GHC > 9.0.1: `Imported.hs` defines some infix operators, and `Importer.hs` uses > them. After typechecking the first one, I put it in the > moduleNameProvidersMap and the HPT. However, when I am typechecking the > second one, the fixity declarations of the infix operators aren’t picked up > correctly. I know they aren’t because I have defined operators that only > typecheck if they are parsed right-associatively. In contrast, if I put > both the definitions and the usage into the same file (`Standalone.hs`), > typechecking succeeds (as I would expect it to). > > > > What am I doing wrong? Is filling the `mi_fixities` field of the > `ModIface` not enough to let importers see the correct fixities? > > > > Thanks, > > Gergo > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From sylvain at haskus.fr Tue Jul 27 08:11:50 2021 From: sylvain at haskus.fr (Sylvain Henry) Date: Tue, 27 Jul 2021 10:11:50 +0200 Subject: Where else do I need to register fixity declarations? In-Reply-To: References: Message-ID: > What am I doing wrong? Is filling the `mi_fixities` field of the `ModIface` not enough to let importers see the correct fixities? It seems like the renamer is looking for the fixities via `mi_fix_fn (mi_final_exts iface)`, not `mi_fixities`. You should try to replace:   , mi_final_exts = mi_final_exts empty with:   , mi_final_exts = (mi_final_exts empty){ mi_fix_fn = mkIfaceFixCache (mi_fixities partial) -------------- next part -------------- An HTML attachment was scrubbed... URL: From gergo at erdi.hu Tue Jul 27 08:52:26 2021 From: gergo at erdi.hu (=?UTF-8?B?R2VyZ8WRIMOJcmRp?=) Date: Tue, 27 Jul 2021 16:52:26 +0800 Subject: Where else do I need to register fixity declarations? In-Reply-To: References: Message-ID: Thanks, this works! I guess this is the kind of problems I run into by using `mkIface_` directly instead of via `mkIfaceTc`. Unfortunately, if I try that, I end up with a panic in `GHC.Iface.Recomp.mkHashFun` in my real program (see separate email earlier). On Tue, Jul 27, 2021, 16:14 Sylvain Henry wrote: > > What am I doing wrong? Is filling the `mi_fixities` field of the > `ModIface` not enough to let importers see the correct fixities? > > It seems like the renamer is looking for the fixities via `mi_fix_fn > (mi_final_exts iface)`, not `mi_fixities`. > > You should try to replace: > > , mi_final_exts = mi_final_exts empty > > with: > > , mi_final_exts = (mi_final_exts empty){ mi_fix_fn = mkIfaceFixCache > (mi_fixities partial) > > > _______________________________________________ > 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 Tue Jul 27 10:09:49 2021 From: gergo at erdi.hu (=?ISO-8859-2?Q?=C9RDI_Gerg=F5?=) Date: Tue, 27 Jul 2021 18:09:49 +0800 (+08) Subject: CI build failures Message-ID: Hi, I'm seeing three build failures in CI: 1. On perf-nofib, it fails with: == make boot -j --jobserver-fds=3,4 --no-print-directory; in /builds/cactus/ghc/nofib/real/smallpt ------------------------------------------------------------------------ /builds/cactus/ghc/ghc/bin/ghc -M -dep-suffix "" -dep-makefile .depend -osuf o -O2 -Wno-tabs -Rghc-timing -H32m -hisuf hi -packageunboxed-ref -rtsopts smallpt.hs : cannot satisfy -package unboxed-ref (use -v for more information) (e.g. https://gitlab.haskell.org/cactus/ghc/-/jobs/743141#L1465) 2. On validate-x86_64-darwin, pretty much every test fails because of the following extra stderr output: + +: + warning: Couldn't figure out C compiler information! + Make sure you're using GNU gcc, or clang (e.g. https://gitlab.haskell.org/cactus/ghc/-/jobs/743129#L3655) 3. On validate-x86_64-linux-deb9-integer-simple, T11545 fails on memory consumption: Unexpected stat failures: perf/compiler/T11545.run T11545 [stat decreased from x86_64-linux-deb9-integer-simple-validate baseline @ 5f3991c7cab8ccc9ab8daeebbfce57afbd9acc33] (normal) This one is interesting because there is already a commit that is supposed to fix this: commit efaad7add092c88eab46e00a9f349d4675bbee06 Author: Matthew Pickering Date: Wed Jul 21 10:03:42 2021 +0100 Stop ug_boring_info retaining a chain of old CoreExpr [...] ------------------------- Metric Decrease: T11545 ------------------------- But still, it's failing. Can someone kick these build setups please? -- .--= ULLA! =-----------------. \ http://gergo.erdi.hu \ `---= gergo at erdi.hu =-------' From moritz.angermann at gmail.com Tue Jul 27 10:47:14 2021 From: moritz.angermann at gmail.com (Moritz Angermann) Date: Tue, 27 Jul 2021 18:47:14 +0800 Subject: CI build failures In-Reply-To: References: Message-ID: You can safely ignore the x86_64-darwin failure. I can get you the juicy details over a beverage some time. It boils down to some odd behavior using rosetta2 on AArch64 Mac mini’s to build x86_64 GHCs. There is a fix somewhere from Ben, so it’s just a question of time until it’s properly fixed. The other two I’m afraid I have no idea. I’ll see to restart them. (You can’t ?) On Tue 27. Jul 2021 at 18:10, ÉRDI Gergő wrote: > Hi, > > I'm seeing three build failures in CI: > > 1. On perf-nofib, it fails with: > > == make boot -j --jobserver-fds=3,4 --no-print-directory; > in /builds/cactus/ghc/nofib/real/smallpt > ------------------------------------------------------------------------ > /builds/cactus/ghc/ghc/bin/ghc -M -dep-suffix "" -dep-makefile .depend > -osuf o -O2 -Wno-tabs -Rghc-timing -H32m -hisuf hi -packageunboxed-ref > -rtsopts smallpt.hs > : cannot satisfy -package unboxed-ref > (use -v for more information) > > (e.g. https://gitlab.haskell.org/cactus/ghc/-/jobs/743141#L1465) > > 2. On validate-x86_64-darwin, pretty much every test fails because of the > following extra stderr output: > > + > +: > + warning: Couldn't figure out C compiler information! > + Make sure you're using GNU gcc, or clang > > (e.g. https://gitlab.haskell.org/cactus/ghc/-/jobs/743129#L3655) > > 3. On validate-x86_64-linux-deb9-integer-simple, T11545 fails on memory > consumption: > > Unexpected stat failures: > perf/compiler/T11545.run T11545 [stat decreased from > x86_64-linux-deb9-integer-simple-validate baseline @ > 5f3991c7cab8ccc9ab8daeebbfce57afbd9acc33] (normal) > > This one is interesting because there is already a commit that is supposed > to fix this: > > commit efaad7add092c88eab46e00a9f349d4675bbee06 > Author: Matthew Pickering > Date: Wed Jul 21 10:03:42 2021 +0100 > > Stop ug_boring_info retaining a chain of old CoreExpr > > [...] > > ------------------------- > Metric Decrease: > T11545 > ------------------------- > > But still, it's failing. > > Can someone kick these build setups please? > > -- > > .--= ULLA! =-----------------. > \ http://gergo.erdi.hu \ > `---= gergo at erdi.hu =-------' > _______________________________________________ > 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 Tue Jul 27 10:50:45 2021 From: gergo at erdi.hu (=?UTF-8?B?R2VyZ8WRIMOJcmRp?=) Date: Tue, 27 Jul 2021 18:50:45 +0800 Subject: CI build failures In-Reply-To: References: Message-ID: The other two are resilient to restarts. On Tue, Jul 27, 2021, 18:49 Moritz Angermann wrote: > You can safely ignore the x86_64-darwin failure. I can get you the juicy > details over a beverage some time. It boils down to some odd behavior using > rosetta2 on AArch64 Mac mini’s to build x86_64 GHCs. There is a fix > somewhere from Ben, so it’s just a question of time until it’s properly > fixed. > > The other two I’m afraid I have no idea. I’ll see to restart them. (You > can’t ?) > > On Tue 27. Jul 2021 at 18:10, ÉRDI Gergő wrote: > >> Hi, >> >> I'm seeing three build failures in CI: >> >> 1. On perf-nofib, it fails with: >> >> == make boot -j --jobserver-fds=3,4 --no-print-directory; >> in /builds/cactus/ghc/nofib/real/smallpt >> ------------------------------------------------------------------------ >> /builds/cactus/ghc/ghc/bin/ghc -M -dep-suffix "" -dep-makefile .depend >> -osuf o -O2 -Wno-tabs -Rghc-timing -H32m -hisuf hi >> -packageunboxed-ref >> -rtsopts smallpt.hs >> : cannot satisfy -package unboxed-ref >> (use -v for more information) >> >> (e.g. https://gitlab.haskell.org/cactus/ghc/-/jobs/743141#L1465) >> >> 2. On validate-x86_64-darwin, pretty much every test fails because of the >> following extra stderr output: >> >> + >> +: >> + warning: Couldn't figure out C compiler information! >> + Make sure you're using GNU gcc, or clang >> >> (e.g. https://gitlab.haskell.org/cactus/ghc/-/jobs/743129#L3655) >> >> 3. On validate-x86_64-linux-deb9-integer-simple, T11545 fails on memory >> consumption: >> >> Unexpected stat failures: >> perf/compiler/T11545.run T11545 [stat decreased from >> x86_64-linux-deb9-integer-simple-validate baseline @ >> 5f3991c7cab8ccc9ab8daeebbfce57afbd9acc33] (normal) >> >> This one is interesting because there is already a commit that is >> supposed >> to fix this: >> >> commit efaad7add092c88eab46e00a9f349d4675bbee06 >> Author: Matthew Pickering >> Date: Wed Jul 21 10:03:42 2021 +0100 >> >> Stop ug_boring_info retaining a chain of old CoreExpr >> >> [...] >> >> ------------------------- >> Metric Decrease: >> T11545 >> ------------------------- >> >> But still, it's failing. >> >> Can someone kick these build setups please? >> >> -- >> >> .--= ULLA! =-----------------. >> \ http://gergo.erdi.hu \ >> `---= gergo at erdi.hu =-------' >> _______________________________________________ >> 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 ben at smart-cactus.org Tue Jul 27 13:55:00 2021 From: ben at smart-cactus.org (Ben Gamari) Date: Tue, 27 Jul 2021 09:55:00 -0400 Subject: CI build failures In-Reply-To: References: Message-ID: <877dhbvp42.fsf@smart-cactus.org> ÉRDI Gergő writes: > Hi, > > I'm seeing three build failures in CI: > Hi, > 1. On perf-nofib, it fails with: > Don't worry about this one for the moment. This job is marked as accepting of failure for a reason (hence the job state being an orange exclamation mark rather than a red X). > == make boot -j --jobserver-fds=3,4 --no-print-directory; > in /builds/cactus/ghc/nofib/real/smallpt > ------------------------------------------------------------------------ > /builds/cactus/ghc/ghc/bin/ghc -M -dep-suffix "" -dep-makefile .depend > -osuf o -O2 -Wno-tabs -Rghc-timing -H32m -hisuf hi -packageunboxed-ref > -rtsopts smallpt.hs > : cannot satisfy -package unboxed-ref > (use -v for more information) > > (e.g. https://gitlab.haskell.org/cactus/ghc/-/jobs/743141#L1465) > > 2. On validate-x86_64-darwin, pretty much every test fails because of the > following extra stderr output: > > + > +: > + warning: Couldn't figure out C compiler information! > + Make sure you're using GNU gcc, or clang > > (e.g. https://gitlab.haskell.org/cactus/ghc/-/jobs/743129#L3655) > Yes, this will be fixed by !6162 once I get it passing CI. > 3. On validate-x86_64-linux-deb9-integer-simple, T11545 fails on memory > consumption: > > Unexpected stat failures: > perf/compiler/T11545.run T11545 [stat decreased from x86_64-linux-deb9-integer-simple-validate baseline @ > 5f3991c7cab8ccc9ab8daeebbfce57afbd9acc33] (normal) > This test appears to be quite sensitive to environment. I suspect we should further increase its acceptance window to avoid this sort of spurious failure. Cheers, 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 gergo at erdi.hu Tue Jul 27 13:57:23 2021 From: gergo at erdi.hu (=?UTF-8?B?R2VyZ8WRIMOJcmRp?=) Date: Tue, 27 Jul 2021 21:57:23 +0800 Subject: CI build failures In-Reply-To: <877dhbvp42.fsf@smart-cactus.org> References: <877dhbvp42.fsf@smart-cactus.org> Message-ID: Thanks, this is all great news On Tue, Jul 27, 2021, 21:56 Ben Gamari wrote: > ÉRDI Gergő writes: > > > Hi, > > > > I'm seeing three build failures in CI: > > > Hi, > > > 1. On perf-nofib, it fails with: > > > Don't worry about this one for the moment. This job is marked as > accepting of failure for a reason (hence the job state being an orange > exclamation mark rather than a red X). > > > == make boot -j --jobserver-fds=3,4 --no-print-directory; > > in /builds/cactus/ghc/nofib/real/smallpt > > ------------------------------------------------------------------------ > > /builds/cactus/ghc/ghc/bin/ghc -M -dep-suffix "" -dep-makefile .depend > > -osuf o -O2 -Wno-tabs -Rghc-timing -H32m -hisuf hi > -packageunboxed-ref > > -rtsopts smallpt.hs > > : cannot satisfy -package unboxed-ref > > (use -v for more information) > > > > (e.g. https://gitlab.haskell.org/cactus/ghc/-/jobs/743141#L1465) > > > > 2. On validate-x86_64-darwin, pretty much every test fails because of > the > > following extra stderr output: > > > > + > > +: > > + warning: Couldn't figure out C compiler information! > > + Make sure you're using GNU gcc, or clang > > > > (e.g. https://gitlab.haskell.org/cactus/ghc/-/jobs/743129#L3655) > > > Yes, this will be fixed by !6162 once I get it passing CI. > > > 3. On validate-x86_64-linux-deb9-integer-simple, T11545 fails on memory > > consumption: > > > > Unexpected stat failures: > > perf/compiler/T11545.run T11545 [stat decreased from > x86_64-linux-deb9-integer-simple-validate baseline @ > > 5f3991c7cab8ccc9ab8daeebbfce57afbd9acc33] (normal) > > > This test appears to be quite sensitive to environment. I suspect we > should further increase its acceptance window to avoid this sort of > spurious failure. > > Cheers, > > Cheers, > > - Ben > -------------- next part -------------- An HTML attachment was scrubbed... URL: From guandayuan0715 at gmail.com Fri Jul 30 18:02:56 2021 From: guandayuan0715 at gmail.com (Guanda Yuan) Date: Fri, 30 Jul 2021 13:02:56 -0500 Subject: How to Collect Type Errors? Message-ID: Hello all, I want to write a plugin for Haskell Language Server, to collect type errors in the code. I'm new to GHC API, so I need some help. My current thought is, I can collect diagnostics or the error messages and extract the type error infos. I have tried to referred to the Haddock documentation for GHC API, but I'm still not sure which function should I use. Thanks, Guanda -------------- next part -------------- An HTML attachment was scrubbed... URL: From lonetiger at gmail.com Sat Jul 31 15:08:26 2021 From: lonetiger at gmail.com (Phyx) Date: Sat, 31 Jul 2021 16:08:26 +0100 Subject: Install WIP app in haskell org Message-ID: Hi Ben, Is it possible to install the WIP app into the github Haskell org? https://github.com/apps/wip It's quite handy to mark things as in progress. Regards, Tamar -------------- next part -------------- An HTML attachment was scrubbed... URL: