| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
GHC is very wishy-washy about rejecting instance declarations with
nested `forall`s or contexts that are surrounded by outermost
parentheses. This can even lead to some strange interactions with
`ScopedTypeVariables`, as demonstrated in #18240. This patch makes
GHC more consistently reject instance types with nested
`forall`s/contexts so as to prevent these strange interactions.
On the implementation side, this patch tweaks `splitLHsInstDeclTy`
and `getLHsInstDeclHead` to not look through parentheses, which can
be semantically significant. I've added a
`Note [No nested foralls or contexts in instance types]` in
`GHC.Hs.Type` to explain why. This also introduces a
`no_nested_foralls_contexts_err` function in `GHC.Rename.HsType` to
catch nested `forall`s/contexts in instance types. This function is
now used in `rnClsInstDecl` (for ordinary instance declarations) and
`rnSrcDerivDecl` (for standalone `deriving` declarations), the latter
of which fixes #18271.
On the documentation side, this adds a new
"Formal syntax for instance declaration types" section to the GHC
User's Guide that presents a BNF-style grammar for what is and isn't
allowed in instance types.
Fixes #18240. Fixes #18271.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch fixes the bug and implements the feature request of #3000.
1. If `Module` is a real module name and `identifier` a name of a
top-level function in `Module` then `:break Module.identifer` works
also for an `identifier` that is out of scope.
2. Extend the syntax for `:break identifier` to:
:break [ModQual.]topLevelIdent[.nestedIdent]...[.nestedIdent]
`ModQual` is optional and is either the effective name of a module or
the local alias of a qualified import statement.
`topLevelIdent` is the name of a top level function in the module
referenced by `ModQual`.
`nestedIdent` is optional and the name of a function nested in a let or
where clause inside the previously mentioned function `nestedIdent` or
`topLevelIdent`.
If `ModQual` is a module name, then `topLevelIdent` can be any top level
identifier in this module. If `ModQual` is missing or a local alias of a
qualified import, then `topLevelIdent` must be in scope.
Breakpoints can be set on arbitrarily deeply nested functions, but the
whole chain of nested function names must be specified.
3. To support the new functionality rewrite the code to tab complete `:break`.
|
|
|
|
|
|
|
|
|
|
|
| |
Starting with Win 8.1/Server 2012 windows no longer preallocates
page tables for reserverd memory eagerly, which prevented us from
using this approach in the past.
We also try to allocate the heap high in the memory space.
Hopefully this makes it easier to allocate things in the low
4GB of memory that need to be there. Like jump islands for the
linker.
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Zonk residual constraints in checkForExistence to reveal user type
errors.
Previously when `:instances` was used with instances that have TypeError
constraints the result would look something like:
instance [safe] s0 => Err 'A -- Defined at ../Bug2.hs:8:10
whereas after zonking, `:instances` now sees the `TypeError` and
properly eliminates the constraint from the results.
|
|
|
|
| |
[skip ci]
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
ghc-bignum is a newer package that aims to replace the legacy
integer-simple and integer-gmp packages.
* it supports several backends. In particular GMP is still supported and
most of the code from integer-gmp has been merged in the "gmp"
backend.
* the pure Haskell "native" backend is new and is much faster than the
previous pure Haskell implementation provided by integer-simple
* new backends are easier to write because they only have to provide a
few well defined functions. All the other code is common to all
backends. In particular they all share the efficient small/big number
distinction previously used only in integer-gmp.
* backends can all be tested against the "native" backend with a simple
Cabal flag. Backends are only allowed to differ in performance, their
results should be the same.
* Add `integer-gmp` compat package: provide some pattern synonyms and
function aliases for those in `ghc-bignum`. It is intended to avoid
breaking packages that depend on `integer-gmp` internals.
Update submodules: text, bytestring
Metric Decrease:
Conversions
ManyAlternatives
ManyConstructors
Naperian
T10359
T10547
T10678
T12150
T12227
T12234
T12425
T13035
T13719
T14936
T1969
T4801
T4830
T5237
T5549
T5837
T8766
T9020
parsing001
space_leak_001
T16190
haddock.base
On ARM and i386, T17499 regresses (+6% > 5%).
On x86_64 unregistered, T13701 sometimes regresses (+2.2% > 2%).
Metric Increase:
T17499
T13701
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This is the first step towards implementation of the linear types proposal
(https://github.com/ghc-proposals/ghc-proposals/pull/111).
It features
* A language extension -XLinearTypes
* Syntax for linear functions in the surface language
* Linearity checking in Core Lint, enabled with -dlinear-core-lint
* Core-to-core passes are mostly compatible with linearity
* Fields in a data type can be linear or unrestricted; linear fields
have multiplicity-polymorphic constructors.
If -XLinearTypes is disabled, the GADT syntax defaults to linear fields
The following items are not yet supported:
* a # m -> b syntax (only prefix FUN is supported for now)
* Full multiplicity inference (multiplicities are really only checked)
* Decent linearity error messages
* Linear let, where, and case expressions in the surface language
(each of these currently introduce the unrestricted variant)
* Multiplicity-parametric fields
* Syntax for annotating lambda-bound or let-bound with a multiplicity
* Syntax for non-linear/multiple-field-multiplicity records
* Linear projections for records with a single linear field
* Linear pattern synonyms
* Multiplicity coercions (test LinearPolyType)
A high-level description can be found at
https://ghc.haskell.org/trac/ghc/wiki/LinearTypes/Implementation
Following the link above you will find a description of the changes made to Core.
This commit has been authored by
* Richard Eisenberg
* Krzysztof Gogolewski
* Matthew Pickering
* Arnaud Spiwack
With contributions from:
* Mark Barbone
* Alexander Vershilov
Updates haddock submodule.
|
| |
|
| |
|
| |
|
| |
|
|
|
|
|
| |
This bit of documentation got outdated after commit
1fcede43d2b30f33b7505e25eb6b1f321be0407f
|
| |
|
|
|
|
|
|
|
| |
The initial version was rewritten by Tamar Christina.
It was rewritten in large parts by Andreas Klebinger.
Co-authored-by: Andreas Klebinger <klebinger.andreas@gmx.at>
|
| |
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Issue #18191 revealed that the types of GADT constructors don't quite
adhere to the `forall`-or-nothing rule. This patch serves to clean up
this sad state of affairs somewhat. The main change is not in the
code itself, but in the documentation, as this patch introduces two
sections to the GHC User's Guide:
* A "Formal syntax for GADTs" section that presents a BNF-style
grammar for what is and isn't allowed in GADT constructor types.
This mostly exists to codify GHC's existing behavior, but it also
imposes a new restriction that addresses #18191: the outermost
`forall` and/or context in a GADT constructor is not allowed to be
surrounded by parentheses. Doing so would make these
`forall`s/contexts nested, and GADTs do not support nested
`forall`s/contexts at present.
* A "`forall`-or-nothing rule" section that describes exactly what
the `forall`-or-nothing rule is all about. Surprisingly, there was
no mention of this anywhere in the User's Guide up until now!
To adhere the new specification in the "Formal syntax for GADTs"
section of the User's Guide, the following code changes were made:
* A new function, `GHC.Hs.Type.splitLHsGADTPrefixTy`, was introduced.
This is very much like `splitLHsSigmaTy`, except that it avoids
splitting apart any parentheses, which can be syntactically
significant for GADT types. See
`Note [No nested foralls or contexts in GADT constructors]` in
`GHC.Hs.Type`.
* `ConDeclGADTPrefixPs`, an extension constructor for `XConDecl`, was
introduced so that `GHC.Parser.PostProcess.mkGadtDecl` can return
it when given a prefix GADT constructor. Unlike `ConDeclGADT`,
`ConDeclGADTPrefixPs` does not split the GADT type into its argument
and result types, as this cannot be done until after the type is
renamed (see `Note [GADT abstract syntax]` in `GHC.Hs.Decls` for why
this is the case).
* `GHC.Renamer.Module.rnConDecl` now has an additional case for
`ConDeclGADTPrefixPs` that (1) splits apart the full `LHsType` into
its `forall`s, context, argument types, and result type, and
(2) checks for nested `forall`s/contexts. Step (2) used to be
performed the typechecker (in `GHC.Tc.TyCl.badDataConTyCon`) rather
than the renamer, but now the relevant code from the typechecker
can simply be deleted.
One nice side effect of this change is that we are able to give a
more accurate error message for GADT constructors that use visible
dependent quantification (e.g., `MkFoo :: forall a -> a -> Foo a`),
which improves the stderr in the `T16326_Fail6` test case.
Fixes #18191. Bumps the Haddock submodule.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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)
|
|
|
|
|
| |
Details from https://gitlab.haskell.org/ghc/ghc/issues/8684
and https://github.com/takano-akio/filelock/pull/7#discussion_r280332430
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
With this patch, we always parse f @t as a type application,
thereby producing better error messages.
This steals two syntactic forms:
* Prefix form of the @-operator in expressions. Since the @-operator is
a divergence from the Haskell Report anyway, this is not a major loss.
* Prefix form of @-patterns. Since we are stealing loose infix form
anyway, might as well sacrifice the prefix form for the sake of much
better error messages.
|
|
|
|
|
| |
The duplicate "orphan instance" phrase here doesn't make sense, and was
probably an accident.
|
|
|
|
|
| |
We can now assume that the thread and processor group interfaces are
available.
|
| |
|
| |
|
|
|
|
|
|
|
|
|
|
|
| |
Previously no attempt was made to avoid multiple threads writing their
capability-local eventlog buffers to the eventlog writer simultaneously.
This could result in multiple eventlog streams being interleaved. Fix
this by documenting that the EventLogWriter's write() and flush()
functions may be called reentrantly and fix the default writer to
protect its FILE* by a mutex.
Fixes #18210.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch updates file paths according to new module hierarchy [1]:
* GHC/Core.hs <= coreSyn/CoreSyn.hs
* GHC/Core/Coercion.hs <= types/Coercion.hs
* GHC/Core/Coercion/Axiom.hs <= types/CoAxiom.hs
* GHC/Core/Coercion/Opt.hs <= types/OptCoercion.hs
* GHC/Core/DataCon.hs <= basicTypes/DataCon.hs
* GHC/Core/FamInstEnv.hs <= types/FamInstEnv.hs
* GHC/Core/Lint.hs <= coreSyn/CoreLint.hs
* GHC/Core/Subst.hs <= coreSyn/CoreSubst.hs
* GHC/Core/TyCo/Rep.hs <= types/TyCoRep.hs
* GHC/Core/TyCon.hs <= types/TyCon.hs
* GHC/Core/Type.hs <= types/Type.hs
* GHC/Core/Unify.hs <= types/Unify.hs
* GHC/Types/Literal.hs <= basicTypes/Literal.hs
* GHC/Types/Var.hs <= basicTypes/Var.hs
[1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular
[skip ci]
|
|
|
|
|
|
|
|
|
|
| |
We should allow a wrapper with up to 82 parameters when the original
function had 82 parameters to begin with.
I verified that this made no difference on NoFib, but then again
it doesn't use huge records...
Fixes #18122.
|
|
|
|
| |
Fixes #18206.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This function and its accompanying rule resolve issue #5218.
A future PR to the bytestring library will make the internal
Data.ByteString.Internal.unsafePackAddress compute string length
with cstringLength#. This will improve the status quo because it is
eligible for constant folding.
Additionally, introduce a new data constructor to ForeignPtrContents
named FinalPtr. This additional data constructor, when used in the
IsString instance for ByteString, leads to more Core-to-Core
optimization opportunities, fewer runtime allocations, and smaller
binaries.
Also, this commit re-exports all the functions from GHC.CString
(including cstringLength#) in GHC.Exts. It also adds a new test
driver. This test driver is used to perform substring matches on Core
that is dumped after all the simplifier passes. In this commit, it is
used to check that constant folding of cstringLength# works.
|
|
|
|
| |
[skip ci]
|
| |
|
| |
|
|
|
|
|
|
|
|
|
| |
This patch adds the fixes that allow for file names containing spaces to
be passed to GHCi's ':script' command to the release notes for 8.12 and
expands the user-guide documentation for ':script' by mentioning how
such file names can be passed.
Related to #18027.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
When assigning registers we now first try registers we
assigned to in the past, instead of picking the "first"
one.
This is in extremely helpful when dealing with loops for
which variables are dead for part of the loop.
This is important for patterns like this:
foo = arg1
loop:
use(foo)
...
foo = getVal()
goto loop;
There we:
* assign foo to the register of arg1.
* use foo, it's dead after this use as it's overwritten after.
* do other things.
* look for a register to put foo in.
If we pick an arbitrary one it might differ from the register the
start of the loop expect's foo to be in.
To fix this we simply look for past register assignments for
the given variable. If we find one and the register is free we
use that register.
This reduces the need for fixup blocks which match the register
assignment between blocks. In the example above between the end
and the head of the loop.
This patch also moves branch weight estimation ahead of register
allocation and adds a flag to control it (cmm-static-pred).
* It means the linear allocator is more likely to assign the hotter
code paths first.
* If it assign these first we are:
+ Less likely to spill on the hot path.
+ Less likely to introduce fixup blocks on the hot path.
These two measure combined are surprisingly effective. Based on nofib
we get in the mean:
* -0.9% instructions executed
* -0.1% reads/writes
* -0.2% code size.
* -0.1% compiler allocations.
* -0.9% compile time.
* -0.8% runtime.
Most of the benefits are simply a result of removing redundant moves
and spills.
Reduced compiler allocations likely are the result of less code being
generated. (The added lookup is mostly non-allocating).
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Implementation for Ticket #16393.
Explicit specificity allows users to manually create inferred type variables,
by marking them with braces.
This way, the user determines which variables can be instantiated through
visible type application.
The additional syntax is included in the parser, allowing users to write
braces in type variable binders (type signatures, data constructors etc).
This information is passed along through the renamer and verified in the
type checker.
The AST for type variable binders, data constructors, pattern synonyms,
partial signatures and Template Haskell has been updated to include the
specificity of type variables.
Minor notes:
- Bumps haddock submodule
- Disables pattern match checking in GHC.Iface.Type with GHC 8.8
|
|
|
|
|
|
|
|
|
|
| |
This commit updates the ghc command's man page as followings:
* Enable `man_show_urls` to show URL addresses in the `DESCRIPTION`
section of ghc.rst, because sphinx currently removes hyperlinks
for man pages.
* Add a `SEE ALSO` section to point to the GHC homepage
|
| |
|
|
|
|
|
|
|
|
|
| |
Removes mentioning of Hugs
(it is not helpful for new users anymore).
Changes the wording for the rest of the paragraph.
Fixes #18132.
|
|
|
|
| |
Fixes #18074.
|
| |
|
|
|
|
|
|
|
|
| |
* remove references to `-package-key` which has been removed in 2016
(240ddd7c39536776e955e881d709bbb039b48513)
* remove support for `-this-package-key` which has been deprecated at the
same time
|
|
|
|
| |
accordingly)
|
| |
|
| |
|
|
|
|
|
| |
Previously this was not easily available to the user. Fix this.
Non-moving collection lifecycle events are now reported with -lg.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Issue #18076 drew my attention to the undocumented `-fast-llvm` flag for
the LLVM code generator introduced in
22733532171330136d87533d523f565f2a4f102f. Speaking to Moritz about this,
the motivation for this flag was to avoid potential incompatibilities
between LLVM and the assembler/linker toolchain by making LLVM
responsible for machine-code generation.
Unfortunately, this cannot possibly work: the LLVM backend's mangler
performs a number of transforms on the assembler generated by LLVM that
are necessary for correctness. These are currently:
* mangling Haskell functions' symbol types to be `object` instead of
`function` on ELF platforms (necessary for tables-next-to-code)
* mangling AVX instructions to ensure that we don't assume alignment
(which LLVM otherwise does)
* mangling Darwin's subsections-via-symbols directives
Given that these are all necessary I don't believe that we can support
`-fast-llvm`. Let's rather remove it.
|
| |
|