[Git][ghc/ghc][wip/tc-lcl-env-refactor] 21 commits: JS: Implement h$clock_gettime in the JavaScript RTS (#23360)

Matthew Pickering (@mpickering) gitlab at gitlab.haskell.org
Thu May 18 15:12:19 UTC 2023



Matthew Pickering pushed to branch wip/tc-lcl-env-refactor at Glasgow Haskell Compiler / GHC


Commits:
5e3f9bb5 by Josh Meredith at 2023-05-16T13:59:22-04:00
JS: Implement h$clock_gettime in the JavaScript RTS (#23360)

- - - - -
90e69d5d by Zubin Duggal at 2023-05-16T14:00:00-04:00
compiler: Use compact representation for SourceText

SourceText is serialized along with INLINE pragmas into interface files. Many of
these SourceTexts are identical, for example "{-# INLINE#". When deserialized,
each such SourceText was previously expanded out into a [Char], which is highly
wasteful of memory, and each such instance of the text would allocate an
independent list with its contents as deserializing breaks any sharing that might
have existed.

Instead, we use a `FastString` to represent these, so that each instance unique
text will be interned and stored in a memory efficient manner.

- - - - -
b70bc690 by Zubin Duggal at 2023-05-16T14:00:00-04:00
compiler: Use compact representation/FastStrings for `SourceNote`s

`SourceNote`s should not be stored as [Char] as this is highly wasteful
and in certain scenarios can be highly duplicated.

Metric Decrease:
  hard_hole_fits

- - - - -
6231a126 by Zubin Duggal at 2023-05-16T14:00:00-04:00
compiler: Use compact representation for UsageFile (#22744)

Use FastString to store filepaths in interface files, as this data is
highly redundant so we want to share all instances of filepaths in the
compiler session.

- - - - -
47a58150 by Zubin Duggal at 2023-05-16T14:00:00-04:00
testsuite: add test for T22744

This test checks for #22744 by compiling 100 modules which each have
a dependency on 1000 distinct external files.

Previously, when loading these interfaces from disk, each individual instance
of a filepath in the interface will would be allocated as an individual object
on the heap, meaning we have heap objects for 100*1000 files, when there are
only 1000 distinct files we care about.

This test checks this by first compiling the module normally, then measuring
the peak memory usage in a no-op recompile, as the recompilation checking will
force the allocation of all these filepaths.

- - - - -
0451bdc9 by Ben Gamari at 2023-05-16T21:31:40-04:00
users guide: Add glossary

Currently this merely explains the meaning of "technology preview" in
the context of released features.

- - - - -
0ba52e4e by Ben Gamari at 2023-05-16T21:31:40-04:00
Update glossary.rst
- - - - -
3d23060c by Ben Gamari at 2023-05-16T21:31:40-04:00
Use glossary directive
- - - - -
2972fd66 by Sylvain Henry at 2023-05-16T21:32:20-04:00
JS: fix getpid (fix #23399)

- - - - -
5fe1d3e6 by Matthew Pickering at 2023-05-17T21:42:00-04:00
Use setSrcSpan rather than setLclEnv in solveForAll

In subsequent MRs (#23409) we want to remove the TcLclEnv argument from
a CtLoc. This MR prepares us for that by removing the one place where
the entire TcLclEnv is used, by using it more precisely to just set the
contexts source location.

Fixes #23390

- - - - -
385edb65 by Torsten Schmits at 2023-05-17T21:42:40-04:00
Update the users guide paragraph on -O in GHCi

In relation to #23056

- - - - -
16777d40 by sheaf at 2023-05-18T16:11:11+01:00
Zonking monad transformers

  - Introduce two zonking monad transformers, ZonkT and ZonkBndrT.
    ZonkT is a reader monad transformer over ZonkEnv.
    ZonkBndrT m is the codensity monad over ZonkT m.

    ZonkBndrT is used for computations that accumulate binders
    in the ZonkEnv.

  - Split up the zonking functions relating purely to types into
    GHC.Tc.Zonk.Type.

    This should allow us to introduce a slimmed-down zonking monad,
    which doesn't wrap the full TcM but a much smaller monad.
    This opens up the possibility of refactoring ErrCtxt to use this
    smaller zonking monad.

  - Refactor the remaining zonking functions to work over the monads
    ZonkTcM = ZonkT TcM and ZonkBndrTcM = ZonkBndrT TcM.

- - - - -
b6320856 by sheaf at 2023-05-18T16:11:12+01:00
Data.Bag: add INLINEABLE to polymorphic functions

This commit allows polymorphic methods in GHC.Data.Bag to be
specialised, avoiding having to pass explicit dictionaries when they
are instantiated with e.g. a known monad.

- - - - -
50dcd778 by Matthew Pickering at 2023-05-18T16:11:49+01:00
Big TcLclEnv and CtLoc refactoring

The overall goal of this refactoring is to reduce the dependency
footprint of the parser and syntax tree. Good reasons include:

- Better module graph parallelisability
- Make it easier to migrate error messages without introducing module loops
- Philosophically, there's not reason for the AST to depend on half the
  compiler.

One of the key edges which added this dependency was

> GHC.Hs.Expr -> GHC.Tc.Types (TcLclEnv)

As this in turn depending on TcM which depends on HscEnv and so on.

Therefore the goal of this patch is to move `TcLclEnv` out of
`GHC.Tc.Types` so that `GHC.Hs.Expr` can import TcLclEnv without
incurring a huge dependency chain.

The changes in this patch are:

* Move TcLclEnv from GHC.Tc.Types to GHC.Tc.Types.LclEnv
* Create new smaller modules for the types used in TcLclEnv
  New Modules:
  - GHC.Tc.Types.TcRef
  - GHC.Tc.Types.ErrCtxt
  - GHC.Tc.Types.TcIdSigInfo
  - GHC.Tc.Types.TcBinder
  - GHC.Tc.Types.TcTyThing
  - GHC.Tc.Types.TH
  - GHC.Tc.Types.LclEnv
  - GHC.Tc.Types.CtLocEnv
  - GHC.Tc.Errors.Types.PromotionErr

  Removed Boot File:
  - {-# SOURCE #-} GHC.Tc.Types

* Introduce TcLclCtxt, the part of the TcLclEnv which doesn't
  participate in restoreLclEnv.

* Replace TcLclEnv in CtLoc with specific CtLocEnv which is defined in
  GHC.Tc.Types.CtLocEnv. Use CtLocEnv in Implic and CtLoc to record the
  location of the implication and constraint.

By splitting up TcLclEnv from GHC.Tc.Types we allow GHC.Hs.Expr to no
longer depend on the TcM monad and all that entails.

Fixes #23389 #23409

- - - - -
d0d94bcd by Matthew Pickering at 2023-05-18T16:11:50+01:00
Remove dependency of GHC.Tc.Utils.TcType on GHC.Driver.Session

This removes the usage of DynFlags from Tc.Utils.TcType  so that it no
longer depends on GHC.Driver.Session. In general we don't want anything
which is a dependency of Language.Haskell.Syntax to depend on
GHC.Driver.Session and removing this edge gets us closer to that goal.

- - - - -
064d68e1 by Matthew Pickering at 2023-05-18T16:11:50+01:00
Move isIrrefutableHsPat to GHC.Rename.Utils and rename to isIrrefutableHsPatRn

This removes edge from GHC.Hs.Pat to GHC.Driver.Session, which makes
Language.Haskell.Syntax end up depending on GHC.Driver.Session.

- - - - -
5f81551d by Matthew Pickering at 2023-05-18T16:11:50+01:00
Remove dependency of GHC.Tc.Types.Constraint on GHC.Driver.Session

- - - - -
ae48ad4c by Matthew Pickering at 2023-05-18T16:11:50+01:00
hole fit plugins: Split definition into own module

The hole fit plugins are defined in terms of TcM, a type we want to
avoid depending on from `GHC.Tc.Errors.Types`. By moving it into its own
module we can remove this dependency. It also simplifies the necessary
boot file.

- - - - -
c9c61506 by Matthew Pickering at 2023-05-18T16:11:50+01:00
Move GHC.Core.Opt.CallerCC Types into separate module

This allows `GHC.Driver.DynFlags` to depend on these types without
depending on CoreM and hence the entire simplifier pipeline.

We can also remove a hs-boot file with this change.

- - - - -
0e09a616 by Matthew Pickering at 2023-05-18T16:11:50+01:00
Remove unecessary SOURCE import

- - - - -
410d6822 by Matthew Pickering at 2023-05-18T16:11:50+01:00
testsuite: Accept new output for CountDepsAst and CountDepsParser tests

These are in a separate commit as the improvement to these tests is the
cumulative effect of the previous set of patches rather than just the
responsibility of the last one in the patchset.

- - - - -


30 changed files:

- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/Dwarf.hs
- compiler/GHC/CmmToAsm/PPC/CodeGen.hs
- compiler/GHC/CmmToAsm/X86/CodeGen.hs
- compiler/GHC/Core/Opt/CallerCC.hs
- − compiler/GHC/Core/Opt/CallerCC.hs-boot
- + compiler/GHC/Core/Opt/CallerCC/Types.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/WorkWrap.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Data/Bag.hs
- compiler/GHC/Data/IOEnv.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Plugins.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/HsToCore/Usage.hs
- compiler/GHC/Iface/Errors/Types.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Iface/Recomp.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/21e645c433f940eacb5cd3a52ab7390d9ebef059...410d682208e32f506ebec66811d8f19286f6d641

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/21e645c433f940eacb5cd3a52ab7390d9ebef059...410d682208e32f506ebec66811d8f19286f6d641
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230518/924b44ac/attachment-0001.html>


More information about the ghc-commits mailing list