| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch simplifies GHC to use simple subsumption.
Ticket #17775
Implements GHC proposal #287
https://github.com/ghc-proposals/ghc-proposals/blob/master/
proposals/0287-simplify-subsumption.rst
All the motivation is described there; I will not repeat it here.
The implementation payload:
* tcSubType and friends become noticably simpler, because it no
longer uses eta-expansion when checking subsumption.
* No deeplyInstantiate or deeplySkolemise
That in turn means that some tests fail, by design; they can all
be fixed by eta expansion. There is a list of such changes below.
Implementing the patch led me into a variety of sticky corners, so
the patch includes several othe changes, some quite significant:
* I made String wired-in, so that
"foo" :: String rather than
"foo" :: [Char]
This improves error messages, and fixes #15679
* The pattern match checker relies on knowing about in-scope equality
constraints, andd adds them to the desugarer's environment using
addTyCsDs. But the co_fn in a FunBind was missed, and for some reason
simple-subsumption ends up with dictionaries there. So I added a
call to addTyCsDs. This is really part of #18049.
* I moved the ic_telescope field out of Implication and into
ForAllSkol instead. This is a nice win; just expresses the code
much better.
* There was a bug in GHC.Tc.TyCl.Instance.tcDataFamInstHeader.
We called checkDataKindSig inside tc_kind_sig, /before/
solveEqualities and zonking. Obviously wrong, easily fixed.
* solveLocalEqualitiesX: there was a whole mess in here, around
failing fast enough. I discovered a bad latent bug where we
could successfully kind-check a type signature, and use it,
but have unsolved constraints that could fill in coercion
holes in that signature -- aargh.
It's all explained in Note [Failure in local type signatures]
in GHC.Tc.Solver. Much better now.
* I fixed a serious bug in anonymous type holes. IN
f :: Int -> (forall a. a -> _) -> Int
that "_" should be a unification variable at the /outer/
level; it cannot be instantiated to 'a'. This was plain
wrong. New fields mode_lvl and mode_holes in TcTyMode,
and auxiliary data type GHC.Tc.Gen.HsType.HoleMode.
This fixes #16292, but makes no progress towards the more
ambitious #16082
* I got sucked into an enormous refactoring of the reporting of
equality errors in GHC.Tc.Errors, especially in
mkEqErr1
mkTyVarEqErr
misMatchMsg
misMatchMsgOrCND
In particular, the very tricky mkExpectedActualMsg function
is gone.
It took me a full day. But the result is far easier to understand.
(Still not easy!) This led to various minor improvements in error
output, and an enormous number of test-case error wibbles.
One particular point: for occurs-check errors I now just say
Can't match 'a' against '[a]'
rather than using the intimidating language of "occurs check".
* Pretty-printing AbsBinds
Tests review
* Eta expansions
T11305: one eta expansion
T12082: one eta expansion (undefined)
T13585a: one eta expansion
T3102: one eta expansion
T3692: two eta expansions (tricky)
T2239: two eta expansions
T16473: one eta
determ004: two eta expansions (undefined)
annfail06: two eta (undefined)
T17923: four eta expansions (a strange program indeed!)
tcrun035: one eta expansion
* Ambiguity check at higher rank. Now that we have simple
subsumption, a type like
f :: (forall a. Eq a => Int) -> Int
is no longer ambiguous, because we could write
g :: (forall a. Eq a => Int) -> Int
g = f
and it'd typecheck just fine. But f's type is a bit
suspicious, and we might want to consider making the
ambiguity check do a check on each sub-term. Meanwhile,
these tests are accepted, whereas they were previously
rejected as ambiguous:
T7220a
T15438
T10503
T9222
* Some more interesting error message wibbles
T13381: Fine: one error (Int ~ Exp Int)
rather than two (Int ~ Exp Int, Exp Int ~ Int)
T9834: Small change in error (improvement)
T10619: Improved
T2414: Small change, due to order of unification, fine
T2534: A very simple case in which a change of unification order
means we get tow unsolved constraints instead of one
tc211: bizarre impredicative tests; just accept this for now
Updates Cabal and haddock submodules.
Metric Increase:
T12150
T12234
T5837
haddock.base
Metric Decrease:
haddock.compiler
haddock.Cabal
haddock.base
Merge note: This appears to break the
`UnliftedNewtypesDifficultUnification` test. It has been marked as
broken in the interest of merging.
(cherry picked from commit 66b7b195cb3dce93ed5078b80bf568efae904cc5)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
| |
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch updates the user interface of GHCi so that file names passed
to the ':script' command can be wrapped in double quotes.
For example:
:script "foo bar.script"
The implementation uses a modified version of 'words' that treats
character sequences enclosed in double quotes as single words.
Fixes #18027.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch updates the user interface of GHCi so that file names passed
to the ':script' command may contain spaces escaped with a backslash.
For example:
:script foo\ bar.script
The implementation uses a modified version of 'words' that does not
break on escaped spaces.
Fixes #18027.
|
|
|
|
|
|
|
| |
This commit adds a link to the user's guide in ghci's
`:help` message.
Newcomers could easily reach to details of ghci.
|
| |
|
|
|
|
| |
accordingly)
|
|
|
|
| |
Use `withPprStyle` instead to apply a specific style to a SDoc.
|
|
|
|
|
|
|
| |
Introduce GHC.Unit.* hierarchy for everything concerning units, packages
and modules.
Update Haddock submodule
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Over the years the unit management code has been modified a lot to keep
up with changes in Cabal (e.g. support for several library components in
the same package), to integrate BackPack, etc. I found it very hard to
understand as the terminology wasn't consistent, was referring to past
concepts, etc.
The terminology is now explained as clearly as I could in the Note
"About Units" and the code is refactored to reflect it.
-------------------
Many names were misleading: UnitId is not an Id but could be a virtual
unit (an indefinite one instantiated on the fly), IndefUnitId
constructor may contain a definite instantiated unit, etc.
* Rename IndefUnitId into InstantiatedUnit
* Rename IndefModule into InstantiatedModule
* Rename UnitId type into Unit
* Rename IndefiniteUnitId constructor into VirtUnit
* Rename DefiniteUnitId constructor into RealUnit
* Rename packageConfigId into mkUnit
* Rename getPackageDetails into unsafeGetUnitInfo
* Rename InstalledUnitId into UnitId
Remove references to misleading ComponentId: a ComponentId is just an
indefinite unit-id to be instantiated.
* Rename ComponentId into IndefUnitId
* Rename ComponentDetails into UnitPprInfo
* Fix display of UnitPprInfo with empty version: this is now used for
units dynamically generated by BackPack
Generalize several types (Module, Unit, etc.) so that they can be used
with different unit identifier types: UnitKey, UnitId, Unit, etc.
* GenModule: Module, InstantiatedModule and InstalledModule are now
instances of this type
* Generalize DefUnitId, IndefUnitId, Unit, InstantiatedUnit,
PackageDatabase
Replace BackPack fake "hole" UnitId by a proper HoleUnit constructor.
Add basic support for UnitKey. They should be used more in the future to
avoid mixing them up with UnitId as we do now.
Add many comments.
Update Haddock submodule
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* Rename InstalledPackageInfo into GenericUnitInfo
The name InstalledPackageInfo is only kept for alleged backward
compatibility reason in Cabal. ghc-boot has its own stripped down copy
of this datatype but it doesn't need to keep the name. Internally we
already use type aliases (UnitInfo in GHC, PackageCacheFormat in
ghc-pkg).
* Rename UnitInfo fields: add "unit" prefix and fix misleading names
* Add comments on every UnitInfo field
* Rename SourcePackageId into PackageId
"Package" already indicates that it's a "source package". Installed
package components are called units.
Update Haddock submodule
|
|
|
|
|
|
|
| |
Update Haddock submodule
Metric Increase:
haddock.compiler
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
In tab-completion for the `:break` command, only those
identifiers should be shown, that are accepted in the
`:break` command. Hence these identifiers must be
- defined in an interpreted module
- top-level
- currently in scope
- listed in a `ModBreaks` value as a possible breakpoint.
The identifiers my be qualified or unqualified.
To get all possible top-level breakpoints for tab-completeion
with the correct qualification do:
1. Build the list called `pifsBreaks` of all pairs of
(Identifier, module-filename) from the `ModBreaks` values.
Here all identifiers are unqualified.
2. Build the list called `pifInscope` of all pairs of
(Identifiers, module-filename) with identifiers from
the `GlobalRdrEnv`. Take only those identifiers that are
in scope and have the correct prefix.
Here the identifiers may be qualified.
3. From the `pifInscope` list seclect all pairs that can be
found in the `pifsBreaks` list, by comparing only the
unqualified part of the identifier.
The remaining identifiers can be used for tab-completion.
This ensures, that we show only identifiers, that can be used
in a `:break` command.
|
|
|
|
|
|
| |
Instead of passing `DynFlags` to functions such as `isStmt` and
`hasImport` in `GHC.Runtime.Eval` we pass `ParserFlags`. It's a much
simpler structure that can be created purely with `mkParserFlags'`.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* SysTools
* Parser
* GHC.Builtin
* GHC.Iface.Recomp
* Settings
Update Haddock submodule
Metric Decrease:
Naperian
parsing001
|
|
|
|
| |
Update Haddock submodule
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
As far as GHC is concerned, installed package components ("units") are
identified by an opaque ComponentId string provided by Cabal. But we
don't want to display it to users (as it contains a hash) so GHC queries
the database to retrieve some infos about the original source package
(name, version, component name).
This patch caches these infos in the ComponentId itself so that we don't
need to provide DynFlags (which contains installed package informations)
to print a ComponentId.
In the future we want GHC to support several independent package states
(e.g. for plugins and for target code), hence we need to avoid
implicitly querying a single global package state.
|
|
|
|
|
|
|
| |
Update Haddock submodule
Metric Increase:
haddock.compiler
|
|
|
|
| |
Update submodule: haddock
|
|
|
|
|
|
|
|
| |
Should make `member` queries faster and avoid messing up with missing
`nubSort`.
Metric Increase:
hie002
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* extract flags and ways into their own modules (with some renaming)
* remove one SOURCE import of GHC.Driver.Session from GHC.Driver.Phases
* when GHC uses dynamic linking (WayDyn), `interpWays` was only
reporting WayDyn even if the host was profiled (WayProf). Now it
returns both as expected (might fix #16803).
* `mkBuildTag :: [Way] -> String` wasn't reporting a canonical tag for
differently ordered lists. Now we sort and nub the list to fix this.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
In #14335 we want to be able to use both the internal interpreter (for
the plugins) and the external interpreter (for TH and GHCi) at the same
time.
This patch performs some preliminary refactoring: the `hsc_interp` field
of HscEnv replaces `hsc_iserv` and is now used to indicate which
interpreter (internal, external) to use to execute TH and GHCi.
Opt_ExternalInterpreter flag and iserv options in DynFlags are now
queried only when we set the session DynFlags. It should help making GHC
multi-target in the future by selecting an interpreter according to the
selected target.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
When GHC is parsing a file generated by a tool, e.g. by the C preprocessor, the
tool may insert #line pragmas to adjust the locations reported to the user.
As the result, the locations recorded in RealSrcLoc are not monotonic. Elements
that appear later in the StringBuffer are not guaranteed to have a higher
line/column number.
In fact, there are no guarantees whatsoever, as #line pragmas can arbitrarily
modify locations. This lack of guarantees makes ideas such as #17544
infeasible.
This patch adds an additional bit of information to every SrcLoc:
newtype BufPos = BufPos { bufPos :: Int }
A BufPos represents the location in the StringBuffer, unaffected by any
pragmas.
Updates haddock submodule.
Metric Increase:
haddock.Cabal
haddock.base
haddock.compiler
MultiLayerModules
Naperian
parsing001
T12150
|
|
|
|
| |
Update haddock submodule
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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
|
| |
|
|
|
|
| |
Update haddock submodule
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This adopts a patch from NetBSD's packaging fixing the `GhcThreaded`
option of the make build system. In addition we introduce a `ghcThreaded`
option in hadrian's `Flavour` type.
Also fix Hadrian's treatment of the `Use Threaded` entry in `settings`.
Previously it would incorrectly claim `Use Threaded = True` if we were
building the `threaded` runtime way. However, this is inconsistent with
the `make` build system, which defines it to be whether the `ghc`
executable is linked against the threaded runtime.
Fixes #17692.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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
-------------------------
|
| |
|
| |
|
|
|
|
|
| |
Metric Decrease:
haddock.compiler
|
| |
|
|
|
|
| |
Haskeline now depends upon exceptions. See #16752.
|
|
|
|
|
| |
These were probably added with some GLOBAL_VARs, but those GLOBAL_VARs
are now gone.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
`:steplocal` enables only breakpoints in the current top-level binding.
When a normal breakpoint is hit, then the module name and the break id from the `BRK_FUN` byte code
allow us to access the corresponding entry in a ModBreak table. From this entry we then get the SrcSpan
(see compiler/main/InteractiveEval.hs:bindLocalsAtBreakpoint).
With this source-span we can then determine the current top-level binding, needed for the steplocal command.
However, if we break at an exception or at an error, we don't have an BRK_FUN byte-code, so we don't have any source information.
The function `bindLocalsAtBreakpoint` creates an `UnhelpfulSpan`, which doesn't allow us to determine the current top-level binding.
To avoid a `panic`, we have to check for `UnhelpfulSpan` in the function `ghc/GHCi/UI.hs:stepLocalCmd`.
Hence a :steplocal command after a break-on-exception or a break-on-error is not possible.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This commit allows command name resolution for GHCi commands
with option `!` as follows:
ghci> :k! Int
Int :: *
= Int
This commit changes implementation as follows:
Before:
* Prefix match with full string including the option `!` (e.g. `k!`)
After (this patch):
* Prefix match without option suffix `!` (e.g. `k`)
* in addition, suffix match with option `!`
See also #8305 and #8113
|
| |
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
| |
As described in the new Note [LLVM Configuration] in SysTools, we now
load llvm-targets and llvm-passes lazily to avoid the overhead of doing
so when -fllvm isn't used (also known as "the common case").
Noticed in #17003.
Metric Decrease:
T12234
T12150
|
|
|
|
|
|
| |
You can always just not use or even build `iserv`. I don't think the
maintenance cost of the CPP is worth...I can't even tell what the
benefit is.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The generated headers are now generated per stage, which means we can
skip hacks like `ghc_boot_platform.h` and just have that be the stage 0
header as proper. In general, stages are to be embraced: freely generate
everything in each stage but then just build what you depend on, and
everything is symmetrical and efficient. Trying to avoid stages because
bootstrapping is a mind bender just creates tons of bespoke
mini-mind-benders that add up to something far crazier.
Hadrian was pretty close to this "stage-major" approach already, and so
was fairly easy to fix. Make needed more work, however: it did know
about stages so at least there was a scaffold, but few packages except
for the compiler cared, and the compiler used its own counting system.
That said, make and Hadrian now work more similarly, which is good for
the transition to Hadrian. The merits of embracing stage aside, the
change may be worthy for easing that transition alone.
|
|
|
|
| |
This commit updates GHCi's help message for GHC 8.10.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This commit refactors interface file generation to allow information
from the later passed (NCG, STG) to be stored in interface files.
We achieve this by splitting interface file generation into two parts:
* Partial interfaces, built based on the result of the core pipeline
* A fully instantiated interface, which also contains the final
fingerprints and can optionally contain information produced by the backend.
This change is required by !1304 and !1530.
-dynamic-too handling is refactored too: previously when generating code
we'd branch on -dynamic-too *before* code generation, but now we do it
after.
(Original code written by @AndreasK in !1530)
Performance
~~~~~~~~~~~
Before this patch interface files where created and immediately flushed
to disk which made space leaks impossible.
With this change we instead use NFData to force all iface related data
structures to avoid space leaks.
In the process of refactoring it was discovered that the code in the
ToIface Module allocated a lot of thunks which were immediately forced
when writing/forcing the interface file. So we made this module more
strict to avoid creating many of those thunks.
Bottom line is that allocations go down by about ~0.1% compared to
master.
Residency is not meaningfully different after this patch.
Runtime was not benchmarked.
Co-Authored-By: Andreas Klebinger <klebinger.andreas@gmx.at>
Co-Authored-By: Ömer Sinan Ağacan <omer@well-typed.com>
|
|
|
|
|
|
|
| |
Add GHC.Hs module hierarchy replacing hsSyn.
Metric Increase:
haddock.compiler
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Having an IORef in FastString to memoize the z-encoded version is
unecessary because there is this amazing thing Haskell can do natively,
it's called "lazyness" :)
We simply remove the UNPACK and strictness annotations from the constructor
field corresponding to the z-encoding, making it lazy, and store the
(pure) z-encoded string there.
The only complication here is 'hasZEncoding' which allows cheking if a
z-encoding was computed for a given string. Since this is only used for
compiler performance statistics though it's not actually necessary to have
the current per-string granularity.
Instead I add a global IORef counter to the FastStringTable and use
unsafePerformIO to increment the counter whenever a lazy z-encoding is
forced.
|