| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
|
| |
Use an (Raw)PkgQual datatype instead of `Maybe FastString` to represent
package imports. Factorize the code that renames RawPkgQual into PkgQual
in function `rnPkgQual`. Renaming consists in checking if the FastString
is the magic "this" keyword, the home-unit unit-id or something else.
Bump haddock submodule
|
|
|
|
|
|
|
|
| |
In order to do this I thought it was prudent to change the list type to
a bag type to avoid doing a lot of premature work in plusGRE because of
++.
Fixes #19201
|
|
|
|
|
|
|
|
|
|
|
| |
This commit tries to untangle the zoo of diagnostic-related functions
in `Tc.Utils.Monad` so that we can have the interfaces mentions only
`TcRnMessage`s while we push the creation of these messages upstream.
It also ports TcRnMessage diagnostics to use the new API, in particular
this commit switch to use TcRnMessage in the external interfaces
of the diagnostic functions, and port the old SDoc to be wrapped
into TcRnUnknownMessage.
|
|
|
|
|
|
|
|
|
|
|
|
| |
- 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.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* Don't show suggestions for similar variables when a data constructor
in a pattern is not in scope.
* Only suggest record fields when a record field for record creation or
updating is not in scope.
* Suggest similar record fields when a record field is not in scope with
-XOverloadedRecordDot.
* Show suggestions for data constructors if a type constructor or type
is not in scope, but only if -XDataKinds is enabled.
Fixes #19843.
|
| |
|
|
|
|
|
|
|
|
|
|
| |
Replace uses of WARN macro with calls to:
warnPprTrace :: Bool -> SDoc -> a -> a
Remove the now unused HsVersions.h
Bump haddock submodule
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
There is no reason to use CPP. __LINE__ and __FILE__ macros are now
better replaced with GHC's CallStack. As a bonus, assert error messages
now contain more information (function name, column).
Here is the mapping table (HasCallStack omitted):
* ASSERT: assert :: Bool -> a -> a
* MASSERT: massert :: Bool -> m ()
* ASSERTM: assertM :: m Bool -> m ()
* ASSERT2: assertPpr :: Bool -> SDoc -> a -> a
* MASSERT2: massertPpr :: Bool -> SDoc -> m ()
* ASSERTM2: assertPprM :: m Bool -> SDoc -> m ()
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
1. `text` is as efficient as `ptext . sLit` thanks to the rewrite rules
2. `text` is visually nicer than `ptext . sLit`
3. `ptext . sLit` encourages using one `ptext` for several `sLit` as in:
ptext $ case xy of
... -> sLit ...
... -> sLit ...
which may allocate SDoc's TextBeside constructors at runtime instead
of sharing them into CAFs.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This commit introduces a new `Severity` type constructor called
`SevIgnore`, which can be used to classify diagnostic messages which are
not meant to be displayed to the user, for example suppressed warnings.
This extra constructor allows us to get rid of a bunch of redundant
checks when emitting diagnostics, typically in the form of the pattern:
```
when (optM Opt_XXX) $
addDiagnosticTc (WarningWithFlag Opt_XXX) ...
```
Fair warning! Not all checks should be omitted/skipped, as evaluating some data
structures used to produce a diagnostic might still be expensive (e.g.
zonking, etc). Therefore, a case-by-case analysis must be conducted when
deciding if a check can be removed or not.
Last but not least, we remove the unnecessary `CmdLine.WarnReason` type, which is now
redundant with `DiagnosticReason`.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Other than that:
* Fix T16167,json,json2,T7478,T10637 tests to reflect the introduction of
the `MessageClass` type
* Remove `makeIntoWarning`
* Remove `warningsToMessages`
* Refactor GHC.Tc.Errors
1. Refactors GHC.Tc.Errors so that we use `DiagnosticReason` for "choices"
(defer types errors, holes, etc);
2. We get rid of `reportWarning` and `reportError` in favour of a general
`reportDiagnostic`.
* Introduce `DiagnosticReason`, `Severity` is an enum: This big commit makes
`Severity` a simple enumeration, and introduces the concept of `DiagnosticReason`,
which classifies the /reason/ why we are emitting a particular diagnostic.
It also adds a monomorphic `DiagnosticMessage` type which is used for
generic messages.
* The `Severity` is computed (for now) from the reason, statically.
Later improvement will add a `diagReasonSeverity` function to compute
the `Severity` taking `DynFlags` into account.
* Rename `logWarnings` into `logDiagnostics`
* Add note and expand description of the `mkHoleError` function
|
|
|
|
|
| |
This commit adds the `lint:compiler` Hadrian target to the CI runner.
It does also fixes hints in the compiler/ and libraries/base/ codebases.
|
|
|
|
|
|
|
|
| |
Metric Increase:
T10370
parsing001
Updates haddock submodule
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
It's surprisingly tricky to deal with 'main' (#19397). This
patch does quite bit of refactoring do to it right. Well,
more-right anyway!
The moving parts are documented in GHC.Tc.Module
Note [Dealing with main]
Some other oddments:
* Rename tcRnExports to rnExports; no typechecking here!
* rnExports now uses checkNoErrs rather than failIfErrsM;
the former fails only if rnExports itself finds errors
* Small improvements to tcTyThingCategory, which ultimately
weren't important to the patch, but I've retained as
a minor improvement.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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
|
|
|
|
|
| |
Fixes #17853. We mustn't discard the result of pickGREs, because doing
so might lead to incorrect redundant import warnings.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Fixes #5972. This adds an extension NoFieldSelectors to disable the generation
of selector functions corresponding to record fields. When this extension is
enabled, record field selectors are not accessible as functions, but users are
still able to use them for record construction, pattern matching and updates.
See Note [NoFieldSelectors] in GHC.Rename.Env for details.
Defining the same field multiple times requires the DuplicateRecordFields
extension to be enabled, even when NoFieldSelectors is in use.
Along the way, this fixes the use of non-imported DuplicateRecordFields in GHCi
with -fimplicit-import-qualified (fixes #18729).
Moreover, it extends DisambiguateRecordFields to ignore non-fields when looking
up fields in record updates (fixes #18999), as described by
Note [DisambiguateRecordFields for updates].
Co-authored-by: Simon Hafner <hafnersimon@gmail.com>
Co-authored-by: Fumiaki Kinoshita <fumiexcel@gmail.com>
|
| |
|
|
|
|
| |
Updates Haddock submodule
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This commit boldly removes the ErrDoc and the MsgDoc from the codebase.
The former was introduced with the only purpose of classifying errors
according to their importance, but a similar result can be obtained just
by having a simple [SDoc], and placing bullets after each of them.
On top of that I have taken the perhaps controversial decision to also
banish MsgDoc, as it was merely a type alias over an SDoc and as such it wasn't
offering any extra type safety. Granted, it was perhaps making type
signatures slightly more "focused", but at the expense of cognitive
burden: if it's really just an SDoc, let's call it with its proper name.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch significantly refactors key renamer datastructures (primarily Avail
and GlobalRdrElt) in order to treat DuplicateRecordFields in a more robust way.
In particular it allows the extension to be used with pattern synonyms (fixes
where mangled record selector names could be printed instead of field labels
(e.g. with -Wpartial-fields or hole fits, see new tests).
The key idea is the introduction of a new type GreName for names that may
represent either normal entities or field labels. This is then used in
GlobalRdrElt and AvailInfo, in place of the old way of representing fields
using FldParent (yuck) and an extra list in AvailTC.
Updates the haddock submodule.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
I was working on making DynFlags stateless (#17957), especially by
storing loaded plugins into HscEnv instead of DynFlags. It turned out to
be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin
isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I
didn't feel like introducing yet another hs-boot file to break the loop.
Additionally I remember that while we introduced the module hierarchy
(#13009) we talked about splitting GHC.Driver.Types because it contained
various unrelated types and functions, but we never executed. I didn't
feel like making GHC.Driver.Types bigger with more unrelated Plugins
related types, so finally I bit the bullet and split GHC.Driver.Types.
As a consequence this patch moves a lot of things. I've tried to put
them into appropriate modules but nothing is set in stone.
Several other things moved to avoid loops.
* Removed Binary instances from GHC.Utils.Binary for random compiler
things
* Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they
import a lot of things that users of GHC.Utils.Binary don't want to
depend on.
* put everything related to Units/Modules under GHC.Unit:
GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.}
* Created several modules under GHC.Types: GHC.Types.Fixity, SourceText,
etc.
* Split GHC.Utils.Error (into GHC.Types.Error)
* Finally removed GHC.Driver.Types
Note that this patch doesn't put loaded plugins into HscEnv. It's left
for another patch.
Bump haddock submodule
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Before this patch, referring to a data constructor in a term-level
context led to a scoping error:
ghci> id Int
<interactive>:1:4: error: Data constructor not in scope: Int
After this patch, the renamer falls back to the type namespace
and successfully finds the Int. It is then rejected in the type
checker with a more useful error message:
<interactive>:1:4: error:
• Illegal term-level use of the type constructor ‘Int’
imported from ‘Prelude’ (and originally defined in ‘GHC.Types’)
• In the first argument of ‘id’, namely ‘Int’
In the expression: id Int
We also do this for type variables.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Haskell and Cmm parsers/lexers now report errors and warnings using ADTs
defined in GHC.Parser.Errors. They can be printed using functions in
GHC.Parser.Errors.Ppr.
Some of the errors provide hints with a separate ADT (e.g. to suggest to
turn on some extension). For now, however, hints are not consistent
across all messages. For example some errors contain the hints in the
main message. I didn't want to change any message with this patch. I
expect these changes to be discussed and implemented later.
Surprisingly, this patch enhances performance. On CI
(x86_64/deb9/hadrian, ghc/alloc):
parsing001 -11.5%
T13719 -2.7%
MultiLayerModules -3.5%
Naperian -3.1%
Bump haddock submodule
Metric Decrease:
MultiLayerModules
Naperian
T13719
parsing001
|
|
|
|
|
|
|
|
|
| |
- put panic related functions into GHC.Utils.Panic
- put trace related functions using DynFlags in GHC.Driver.Ppr
One step closer making Outputable fully independent of DynFlags.
Bump haddock submodule
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Executing on the plan described in #17582, this patch changes the way if expressions
are handled in the compiler in the presence of rebindable syntax. We get rid of the
SyntaxExpr field of HsIf and instead, when rebindable syntax is on, we rewrite the HsIf
node to the appropriate sequence of applications of the local `ifThenElse` function.
In order to be able to report good error messages, with expressions as they were
written by the user (and not as desugared by the renamer), we make use of TTG
extensions to extend GhcRn expression ASTs with an `HsExpansion` construct, which
keeps track of a source (GhcPs) expression and the desugared (GhcRn) expression that
it gives rise to. This way, we can typecheck the latter while reporting the former in
error messages.
In order to discard the error context lines that arise from typechecking the desugared
expressions (because they talk about expressions that the user has not written), we
carefully give a special treatment to the nodes fabricated by this new renaming-time
transformation when typechecking them. See Note [Rebindable syntax and HsExpansion]
for more details. The note also includes a recipe to apply the same treatment to
other rebindable constructs.
Tests 'rebindable11' and 'rebindable12' have been added to make sure we report
identical error messages as before this patch under various circumstances.
We also now disable rebindable syntax when processing untyped TH quotes, as per
the discussion in #18102 and document the interaction of rebindable syntax and
Template Haskell, both in Note [Template Haskell quotes and Rebindable Syntax]
and in the user guide, adding a test to make sure that we do not regress in
that regard.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This started as a simple fix for #18321 that organically grew into a
much more sweeping refactor of how auxiliary bindings for derived
instances are handled. I have rewritten `Note [Auxiliary binders]`
in `GHC.Tc.Deriv.Generate` to explain all of the moving parts, but
the highlights are:
* Previously, the OccName of each auxiliary binding would be given
a suffix containing a hash of its package name, module name, and
parent data type to avoid name clashes. This was needlessly
complicated, so we take the more direct approach of generating
`Exact` `RdrName`s for each auxiliary binding with the same
`OccName`, but using an underlying `System` `Name` with a fresh
`Unique` for each binding. Unlike hashes, allocating new `Unique`s
does not require any cleverness and avoid name clashes all the
same...
* ...speaking of which, in order to convince the renamer that multiple
auxiliary bindings with the same `OccName` (but different
`Unique`s) are kosher, we now use `rnLocalValBindsLHS` instead of
`rnTopBindsLHS` to rename auxiliary bindings. Again, see
`Note [Auxiliary binders]` for the full story.
* I have removed the `DerivHsBind` constructor for
`DerivStuff`—which was only used for `Data.Data`-related
auxiliary bindings—and refactored `gen_Data_binds` to use
`DerivAuxBind` instead. This brings the treatment of
`Data.Data`-related auxiliary bindings in line with every other
form of auxiliary binding.
Fixes #18321.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Co-authored-by: Facundo Domínguez <facundo.dominguez@tweag.io>
QualifiedDo is implemented using the same placeholders for operation names in
the AST that were devised for RebindableSyntax. Whenever the renamer checks
which names to use for do syntax, it first checks if the do block is qualified
(e.g. M.do { stmts }), in which case it searches for qualified names in
the module M.
This allows users to write
{-# LANGUAGE QualifiedDo #-}
import qualified SomeModule as M
f x = M.do -- desugars to:
y <- M.return x -- M.return x M.>>= \y ->
M.return y -- M.return y M.>>
M.return y -- M.return y
See Note [QualifiedDo] and the users' guide for more details.
Issue #18214
Proposal:
https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0216-qualified-do.rst
Since we change the constructors `ITdo` and `ITmdo` to carry the new module
name, we need to bump the haddock submodule to account or the new shape of
these constructors.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
In some cases it was possible for lookupGlobalOccRn_maybe to return an
error, when it should be returning a Nothing. If it called
lookupExactOcc_either when there were no matching GlobalRdrElts in the
otherwise case, it would return an error message. This could be caused
when lookupThName_maybe in Template Haskell was looking in different
namespaces (thRdrNameGuesses), guessing different namespaces that the
name wasn't guaranteed to be found in.
However, by addressing this some more accurate errors were being lost in
the conversion to Maybes. So some of the lookup* functions have been
shuffled about so that errors should always be ignored in
lookup*_maybes, and propagated otherwise.
This fixes #18263
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This updates comments only.
This patch replaces leaf module names according to new module
hierarchy [1][2] as followings:
* Expand leaf names to easily find the module path:
for instance, `Id.hs` to `GHC.Types.Id`.
* Modify leaf names according to new module hierarchy:
for instance, `Convert.hs` to `GHC.ThToHs`.
* Fix typo:
for instance, `GHC.Core.TyCo.Rep.hs` to `GHC.Core.TyCo.Rep`
See also !3375
[1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular
[2]: https://gitlab.haskell.org/ghc/ghc/issues/13009
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
We often have (ModuleName, Bool) or (Module, Bool) pairs for "extended"
module names (without or with a unit id) disambiguating boot and normal
modules. We think this is important enough across the compiler that it
deserves a new nominal product type. We do this with synnoyms and a
functor named with a `Gen` prefix, matching other newly created
definitions.
It was also requested that we keep custom `IsBoot` / `NotBoot` sum type.
So we have it too. This means changing many the many bools to use that
instead.
Updates `haddock` submodule.
|
|
|
|
|
|
|
| |
Introduce GHC.Unit.* hierarchy for everything concerning units, packages
and modules.
Update Haddock submodule
|
|
|
|
|
|
|
| |
Update Haddock submodule
Metric Increase:
haddock.compiler
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* SysTools
* Parser
* GHC.Builtin
* GHC.Iface.Recomp
* Settings
Update Haddock submodule
Metric Decrease:
Naperian
parsing001
|
|
|
|
| |
Update Haddock submodule
|
|
|
|
|
|
|
| |
Update Haddock submodule
Metric Increase:
haddock.compiler
|
|
|
|
| |
Update submodule: haddock
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Before this patch, GHC relied on Ord SrcSpan to identify source elements, by
using SrcSpan as Map keys:
blackList :: Map SrcSpan () -- compiler/GHC/HsToCore/Coverage.hs
instanceMap :: Map SrcSpan Name -- compiler/GHC/HsToCore/Docs.hs
Firstly, this design is not valid in presence of UnhelpfulSpan, as it
distinguishes between UnhelpfulSpan "X" and UnhelpfulSpan "Y", but those
strings are messages for the user, unfit to serve as identifiers for source
elements.
Secondly, this design made it hard to extend SrcSpan with additional data.
Recall that the definition of SrcSpan is:
data SrcSpan =
RealSrcSpan !RealSrcSpan
| UnhelpfulSpan !FastString
Say we want to extend the RealSrcSpan constructor with additional information:
data SrcSpan =
RealSrcSpan !RealSrcSpan !AdditionalInformation
| UnhelpfulSpan !FastString
getAdditionalInformation :: SrcSpan -> AdditionalInformation
getAdditionalInformation (RealSrcSpan _ a) = a
Now, in order for Map SrcSpan to keep working correctly, we must *ignore* additional
information when comparing SrcSpan values:
instance Ord SrcSpan where
compare (RealSrcSpan r1 _) (RealSrcSpan r2 _) = compare r1 r2
...
However, this would violate an important law:
a == b therefore f a == f b
Ignoring AdditionalInformation in comparisons would mean that with
f=getAdditionalInformation, the law above does not hold.
A more robust design is to avoid Ord SrcSpan altogether, which is what this patch implements.
The mappings are changed to use RealSrcSpan instead:
blackList :: Set RealSrcSpan -- compiler/GHC/HsToCore/Coverage.hs
instanceMap :: Map RealSrcSpan Name -- compiler/GHC/HsToCore/Docs.hs
All SrcSpan comparisons are now done with explicit comparison strategies:
SrcLoc.leftmost_smallest
SrcLoc.leftmost_largest
SrcLoc.rightmost_smallest
These strategies are not subject to the law mentioned above and can easily
discard both the string stored in UnhelpfulSpan and AdditionalInformation.
Updates haddock submodule.
|
|
|
|
| |
submodule updates: nofib, haddock
|
|
|
|
|
|
|
| |
Switching from `lookupGlobalOccRn_maybe` to `lookupInfoOccRn`
to check whether a `main` function is in scope. Unfortunately
`lookupGlobalOccRn_maybe` complains if there are multiple `main`
functions in scope.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
There are two main payloads of this patch:
1. This introduces IsPass, which allows e.g. printing
code to ask what pass it is running in (Renamed vs
Typechecked) and thus print extension fields. See
Note [IsPass] in Hs.Extension
2. This moves the HsWrap constructor into an extension
field, where it rightly belongs. This is done for
HsExpr and HsCmd, but not for HsPat, which is left
as an exercise for the reader.
There is also some refactoring around SyntaxExprs, but this
is really just incidental.
This patch subsumes !1721 (sorry @chreekat).
Along the way, there is a bit of refactoring in GHC.Hs.Extension,
including the removal of NameOrRdrName in favor of NoGhcTc.
This meant that we had no real need for GHC.Hs.PlaceHolder, so
I got rid of it.
Updates haddock submodule.
-------------------------
Metric Decrease:
haddock.compiler
-------------------------
|
| |
|
|
|