summaryrefslogtreecommitdiff
path: root/compiler/Language
Commit message (Collapse)AuthorAgeFilesLines
* Minor fix to pretty-printing of linear typesKrzysztof Gogolewski2021-08-051-4/+0
| | | | | | The function ppr_arrow_chain was not printing multiplicities. Also remove the Outputable instance: no longer used, and could cover bugs like those.
* Use HsExpansion for overloaded list patternssheaf2021-06-291-6/+1
| | | | Fixes #14380, #19997
* HsUniToken and HsToken for HsArrow (#19623)Vladislav Zavialov2021-06-163-11/+24
| | | | | | Another step towards a simpler design for exact printing. Updates the haddock submodule.
* Change representation of HsGetField and HsProjectionShayne Fletcher2021-05-272-32/+35
| | | | | Another change in a series improving record syntax in the AST. The key change in this commit is the renaming of `HsFieldLabel` to `DotFieldOcc`.
* HsToken for HsPar, ParPat, HsCmdPar (#19523)Vladislav Zavialov2021-05-233-0/+20
| | | | This patch is a first step towards a simpler design for exact printing.
* Change representation of field selector occurencesShayne Fletcher2021-05-235-34/+86
| | | | | | | | | | | | - Change the names of the fields in in `data FieldOcc` - Renames `HsRecFld` to `HsRecSel` - Replace `AmbiguousFieldOcc p` in `HsRecSel` with `FieldOcc p` - Contains a haddock submodule update The primary motivation of this change is to remove `AmbiguousFieldOcc`. This is one of a suite of changes improving how record syntax (most notably record update syntax) is represented in the AST.
* Remove Maybe from Context in HsQualTyAlan Zimmerman2021-05-211-1/+1
| | | | | | Updates haddock submodule Closes #19845
* Changes to HsRecField'Shayne Fletcher2021-05-194-45/+53
|
* Remove useless {-# LANGUAGE CPP #-} pragmasSylvain Henry2021-05-125-5/+5
|
* Fully remove HsVersions.hSylvain Henry2021-05-123-7/+0
| | | | | | | | | | Replace uses of WARN macro with calls to: warnPprTrace :: Bool -> SDoc -> a -> a Remove the now unused HsVersions.h Bump haddock submodule
* Allow visible type application for levity-poly data consSimon Peyton Jones2021-05-072-5/+0
| | | | | | | | | | | | | | | | | | | | | | | | | | | This patch was driven by #18481, to allow visible type application for levity-polymorphic newtypes. As so often, it started simple but grew: * Significant refactor: I removed HsConLikeOut from the client-independent Language.Haskell.Syntax.Expr, and put it where it belongs, as a new constructor `ConLikeTc` in the GHC-specific extension data type for expressions, `GHC.Hs.Expr.XXExprGhcTc`. That changed touched a lot of files in a very superficial way. * Note [Typechecking data constructors] explains the main payload. The eta-expansion part is no longer done by the typechecker, but instead deferred to the desugarer, via `ConLikeTc` * A little side benefit is that I was able to restore VTA for data types with a "stupid theta": #19775. Not very important, but the code in GHC.Tc.Gen.Head.tcInferDataCon is is much, much more elegant now. * I had to refactor the levity-polymorphism checking code in GHC.HsToCore.Expr, see Note [Checking for levity-polymorphic functions] Note [Checking levity-polymorphic data constructors]
* 19486 Nearly all uses of `uniqCompareFS` are dubious and lack a ↵Sasha Bogicevic2021-05-061-1/+1
| | | | non-determinism justification
* Pretty-print HsArgPar applications correctly (#19737)Ryan Scott2021-04-271-4/+51
| | | | | | | | | | | Previously, the `Outputable` instance for `HsArg` was being used to pretty-print each `HsArgPar` in a list of `HsArg`s individually, which simply doesn't work. In lieu of the `Outputable` instance, we now use a dedicated `pprHsArgsApp` function to print a list of `HsArg`s as a single unit. I have also added documentation to the `Outputable` instance for `HsArg` to more clearly signpost that it is only suitable for debug pretty-printing. Fixes #19737.
* Rename references to Note [Trees That Grow] consistently [skip ci]wip/amg/rename-ttg-notesAdam Gundry2021-04-236-12/+18
| | | | | | I tend to find Notes by (case-sensitive) grep, and I spent a surprisingly long time looking for this Note, because it was referenced inconsistently with different cases, and without the module name.
* EPA : rename 'api annotations' to 'exact print annotations'Alan Zimmerman2021-03-316-132/+136
| | | | | | In comments, and notes. Follow-up from !2418, see #19579
* EPA : Rename AddApiAnn to AddEpAnnAlan Zimmerman2021-03-311-2/+2
| | | | | | | As port of the process of migrating naming from API Annotations to exact print annotations (EPA) Follow-up from !2418, see #19579
* Add compiler linting to CIHécate2021-03-256-50/+36
| | | | | This commit adds the `lint:compiler` Hadrian target to the CI runner. It does also fixes hints in the compiler/ and libraries/base/ codebases.
* Transfer tickish things to GHC.Types.TickishLuite Stegeman2021-03-202-2/+2
| | | | | Metric Increase: MultiLayerModules
* rename Tickish to CoreTickishLuite Stegeman2021-03-202-3/+3
|
* GHC Exactprint main commitAlan Zimmerman2021-03-205-95/+166
| | | | | | | | Metric Increase: T10370 parsing001 Updates haddock submodule
* Implement record dot syntaxwip/joachim/bump-haddockShayne Fletcher2021-03-062-1/+136
|
* Wrap LHsContext in Maybe in the GHC ASTAlan Zimmerman2021-03-012-3/+3
| | | | | | | If the context is missing it is captured as Nothing, rather than putting a noLoc in the ParsedSource. Updates haddock submodule
* Improve handling of overloaded labels, literals, lists etcwip/T19154Simon Peyton Jones2021-02-191-151/+4
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | When implementing Quick Look I'd failed to remember that overloaded labels, like #foo, should be treated as a "head", so that they can be instantiated with Visible Type Application. This caused #19154. A very similar ticket covers overloaded literals: #19167. This patch fixes both problems, but (annoyingly, albeit temporarily) in two different ways. Overloaded labels I dealt with overloaded labels by buying fully into the Rebindable Syntax approach described in GHC.Hs.Expr Note [Rebindable syntax and HsExpansion]. There is a good overview in GHC.Rename.Expr Note [Handling overloaded and rebindable constructs]. That module contains much of the payload for this patch. Specifically: * Overloaded labels are expanded in the renamer, fixing #19154. See Note [Overloaded labels] in GHC.Rename.Expr. * Left and right sections used to have special code paths in the typechecker and desugarer. Now we just expand them in the renamer. This is harder than it sounds. See GHC.Rename.Expr Note [Left and right sections]. * Infix operator applications are expanded in the typechecker, specifically in GHC.Tc.Gen.App.splitHsApps. See Note [Desugar OpApp in the typechecker] in that module * ExplicitLists are expanded in the renamer, when (and only when) OverloadedLists is on. * HsIf is expanded in the renamer when (and only when) RebindableSyntax is on. Reason: the coverage checker treats HsIf specially. Maybe we could instead expand it unconditionally, and fix up the coverage checker, but I did not attempt that. Overloaded literals Overloaded literals, like numbers (3, 4.2) and strings with OverloadedStrings, were not working correctly with explicit type applications (see #19167). Ideally I'd also expand them in the renamer, like the stuff above, but I drew back on that because they can occur in HsPat as well, and I did not want to to do the HsExpanded thing for patterns. But they *can* now be the "head" of an application in the typechecker, and hence something like ("foo" @T) works now. See GHC.Tc.Gen.Head.tcInferOverLit. It's also done a bit more elegantly, rather than by constructing a new HsExpr and re-invoking the typechecker. There is some refactoring around tcShortCutLit. Ultimately there is more to do here, following the Rebindable Syntax story. There are a lot of knock-on effects: * HsOverLabel and ExplicitList no longer need funny (Maybe SyntaxExpr) fields to support rebindable syntax -- good! * HsOverLabel, OpApp, SectionL, SectionR all become impossible in the output of the typecheker, GhcTc; so we set their extension fields to Void. See GHC.Hs.Expr Note [Constructor cannot occur] * Template Haskell quotes for HsExpanded is a bit tricky. See Note [Quotation and rebindable syntax] in GHC.HsToCore.Quote. * In GHC.HsToCore.Match.viewLExprEq, which groups equal HsExprs for the purpose of pattern-match overlap checking, I found that dictionary evidence for the same type could have two different names. Easily fixed by comparing types not names. * I did quite a bit of annoying fiddling around in GHC.Tc.Gen.Head and GHC.Tc.Gen.App to get error message locations and contexts right, esp in splitHsApps, and the HsExprArg type. Tiresome and not very illuminating. But at least the tricky, higher order, Rebuilder function is gone. * Some refactoring in GHC.Tc.Utils.Monad around contexts and locations for rebindable syntax. * Incidentally fixes #19346, because we now print renamed, rather than typechecked, syntax in error mesages about applications. The commit removes the vestigial module GHC.Builtin.RebindableNames, and thus triggers a 2.4% metric decrease for test MultiLayerModules (#19293). Metric Decrease: MultiLayerModules T12545
* Fix typosBrian Wignall2021-02-062-2/+2
|
* The Char kind (#11342)Daniel Rogozin2021-02-061-0/+2
| | | | | | | | | | | | | | | | | | | | | | Co-authored-by: Rinat Stryungis <rinat.stryungis@serokell.io> Implement GHC Proposal #387 * Parse char literals 'x' at the type level * New built-in type families CmpChar, ConsSymbol, UnconsSymbol * New KnownChar class (cf. KnownSymbol and KnownNat) * New SomeChar type (cf. SomeSymbol and SomeNat) * CharTyLit support in template-haskell Updated submodules: binary, haddock. Metric Decrease: T5205 haddock.base Metric Increase: Naperian T13035
* Make PatSyn immutableSimon Peyton Jones2021-01-291-4/+3
| | | | | | | | | | Provoked by #19074, this patch makes GHC.Core.PatSyn.PatSyn immutable, by recording only the *Name* of the matcher and builder rather than (as currently) the *Id*. See Note [Keep Ids out of PatSyn] in GHC.Core.PatSyn. Updates haddock submodule.
* Track the dependencies of `GHC.Hs.Expr.Types`John Ericson2021-01-231-5/+9
| | | | | | Thery is still, in my view, far too numerous, but I believe this won't be too hard to improve upon. At the very lease, we can always add more extension points!
* Separate AST from GhcPass (#18936)John Ericson2021-01-2310-0/+7164
---------------- What: There are two splits. The first spit is: - `Language.Haskell.Syntax.Extension` - `GHC.Hs.Extension` where the former now just contains helpers like `NoExtCon` and all the families, and the latter is everything having to do with `GhcPass`. The second split is: - `Language.Haskell.Syntax.<mod>` - `GHC.Hs.<mod>` Where the former contains all the data definitions, and the few helpers that don't use `GhcPass`, and the latter contains everything else. The second modules also reexport the former. ---------------- Why: See the issue for more details, but in short answer is we're trying to grasp at the modularity TTG is supposed to offer, after a long time of mainly just getting the safety benefits of more complete pattern matching on the AST. Now, we have an AST datatype which, without `GhcPass` is decently stripped of GHC-specific concerns. Whereas before, not was it GHC-specific, it was aware of all the GHC phases despite the parameterization, with the instances and parametric data structure side-by-side. For what it's worth there are also some smaller, imminent benefits: - The latter change also splits a strongly connected component in two, since none of the `Language.Haskell.Syntax.*` modules import the older ones. - A few TTG violations (Using GhcPass directly in the AST) in `Expr` are now more explicitly accounted for with new type families to provide the necessary indirection. ----------------- Future work: - I don't see why all the type families should live in `Language.Haskell.Syntax.Extension`. That seems anti-modular for little benefit. All the ones used just once can be moved next to the AST type they serve as an extension point for. - Decide what to do with the `Outputable` instances. Some of these are no orphans because they referred to `GhcPass`, and had to be moved. I think the types could be generalized so they don't refer to `GhcPass` and therefore can be moved back, but having gotten flak for increasing the size and complexity types when generalizing before, I did *not* want to do this. - We should triage the remaining contents of `GHC.Hs.<mod>`. The renaming helpers are somewhat odd for needing `GhcPass`. We might consider if they are a) in fact only needed by one phase b) can be generalized to be non-GhcPass-specific (e.g. take a callback rather than GADT-match with `IsPass`) and then they can live in `Language.Haskell.Syntax.<mod>`. For more details, see https://gitlab.haskell.org/ghc/ghc/-/wikis/implementing-trees-that-grow Bumps Haddock submodule