[Git][ghc/ghc][wip/aforemny/parameterize-source-text-lits-over-pass] 9 commits: ttg: Use List instead of Bag in AST for LHsBindsLR

Alexander Foremny (@aforemny) gitlab at gitlab.haskell.org
Mon Jun 10 10:11:38 UTC 2024



Alexander Foremny pushed to branch wip/aforemny/parameterize-source-text-lits-over-pass at Glasgow Haskell Compiler / GHC


Commits:
1ccd023a by Jacco Krijnen at 2024-06-10T11:37:15+02:00
ttg: Use List instead of Bag in AST for LHsBindsLR

Considering that the parser used to create a Bag of binds using a
cons-based approach, it can be also done using lists. The operations in
the compiler don't really require Bag.

By using lists, there is no dependency on GHC.Data.Bag anymore from the
AST.

Progress towards #21592

- - - - -
62b585cc by Fabian Kirchner at 2024-06-10T11:37:15+02:00
ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var

Progress towards #21592

Specificity, ForAllTyFlag and its' helper functions are extracted from
GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity.

Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on
GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls.
At this point, this would cause cyclic dependencies.

- - - - -
051e17c2 by Fabian Kirchner at 2024-06-10T11:37:16+02:00
ttg: Move some AST types into Language.Haskell.Syntax.Basic

In particular, we move:
* TopLevelFlag
* TypeOrData
* TyConFlavour

Progress towards #21592

- - - - -
cd4ab6d8 by Adowrath at 2024-06-10T11:37:16+02:00
ttg: Split HsSrcBang, remove ref to DataCon from Syntax.Type

Progress towards #21592

This splits HsSrcBang up, creating the new HsBang within
`Language.Haskell.Syntax.Basic`. `HsBang` holds the unpackedness
and strictness information, while `HsSrcBang` only adds the SourceText
for usage within the compiler directly.

Inside the AST, to preserve the SourceText, it is hidden behind the
pre-existing extension point `XBindTy`. All other occurrences of
`HsSrcBang` were adapted to deconstruct the inner `HsBang`, and when
interacting with the `BindTy` constructor, the hidden `SourceText` is
extracted/inserted into the `XBindTy` extension point.

`GHC.Core.DataCon` exports both `HsSrcBang` and `HsBang` for
convenience. A constructor function `mkHsSrcBang` that takes all
individual components has been added.

Two exceptions has been made though:
- The `Outputable HsSrcBang` instance is replaced by
  `Outputable HsBang`. While being only GHC-internal, the only place
  it's used is in outputting `HsBangTy` constructors -- which already
  have `HsBang`. It wouldn't make sense to reconstruct a `HsSrcBang` just
  to ignore the `SourceText` anyway.
- The error `TcRnUnexpectedAnnotation` did not use the `SourceText`,
  so it too now only holds a `HsBang`.

- - - - -
10d3ad93 by Mauricio at 2024-06-10T11:37:16+02:00
AST: Moved definitions that use GHC.Utils.Panic to GHC namespace

Progress towards #21592

- - - - -
3be9f119 by Alexander Foremny at 2024-06-10T12:08:37+02:00
ttg: StringLiteral -> StringLit (type)

`GHC.Types.SourceText.StringLiteral` does not abbreviate "Literal",
while `GHC.Types.SourceText.{IntegralLit,FractionalLit}` do. To increase
consistency, `StringLiteral` was renamed to `StringLit`.

- - - - -
3fbeaa57 by Alexander Foremny at 2024-06-10T12:08:41+02:00
ttg: StringLiteral -> SL (data constructor)

`GHC.Types.SourceText.StringLit` has data constructor `StringLiteral`,
while `GHC.Types.SourceText.{IntegralLit,FractionalLit}` have data
constructors `{IL,FL}`. To increase consistency, the data constructor
`StringLiteral` was renamed to `SL`.

- - - - -
f184b084 by Alexander Foremny at 2024-06-10T12:08:43+02:00
ttg: use `StringLit` for `HsIsString`

While `OverLitVal`'s data constructors `HsIntegral`, `HsFractional`
carried `IntegralLit`, `FractionalLit` types, `HsIsString` carries only
`SourceText` and `FastString`. We will want to parameterize over
`SourceText`, which `StringLit`s will support. So we change `HsIsString`
to carry a `StringLit`.

- - - - -
f3c2baf1 by Alexander Foremny at 2024-06-10T12:11:04+02:00
ttg: parameterize `GHC.Types.SourceText`'s literals over `pass`

In order to move `GHC.Types.SourceText.SourceText` out of
`Language.Haskell`, we parameterize `GHC.Types.SourceText`'s literals by
`pass`, and replace, say, `IntegralLit`'s `SourceText` field by
`XIntegralLit pass`.

- - - - -


30 changed files:

- compiler/GHC.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/InstEnv.hs
- compiler/GHC/Core/TyCo/Rep.hs-boot
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Lit.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Stats.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Match/Literal.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Pmc/Solver/Types.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/HaddockLex.x


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/61f98f622842296db099099dd29172309af23068...f3c2baf141dd99c5daa0981c76b76916d564958e

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/61f98f622842296db099099dd29172309af23068...f3c2baf141dd99c5daa0981c76b76916d564958e
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/20240610/63665495/attachment-0001.html>


More information about the ghc-commits mailing list