- Jan 23, 2025
-
-
Karim Taha authored
Draft: try to eliminate all usages of `addFatalError' and substitue with `addError' followed by `return badValue' for a suitable `badValue'
-
Karim Taha authored
The motivation is that some parsing errors still halt the whole pipeline due to wrong interaction between the catch mechansim and the layout rule requiring emission of `error' tokens, So we try to keep as much info in the source up until the occurrence of error.
-
Karim Taha authored
Use the new `%error {} {}` resumption facilities with `ValD`, `HsUnboundVar', `WildPat' and `HsWildCardTy' constructors representing parse errors.
-
Karim Taha authored
-
Resolves #18631 Co-authored-by:
Richard Eisenberg <rae@cs.brynmawr.edu>
-
- Jan 22, 2025
-
-
Vladislav Zavialov authored
This patch rewrites part of the logic for dealing with built-in and punned names, making it more principled and fixing a few bugs. * Kill off filterCTuple. Its purpose was to improve pretty-printing of constraint tuples, and the appropriate place for this is namePun_maybe. * Remove unitTyCon, unboxedUnitTyCon, and soloTyCon from wiredInTyCons. Their inclusion in the list was a workaround for shoddy logic in lookupOrigNameCache. Now we treat tuples of all arities uniformly. * In isBuiltInOcc_maybe, only match on actual built-in syntax, e.g. "FUN" shouldn't be there (#25174). Also take ListTuplePuns into account (#25179). * When matching OccNames, use the ShortByteString directly to avoid potentially costly conversions to ByteString and String. * Introduce isInfiniteFamilyOrigName_maybe, a purpose-built helper for looking up tuples/sums in the OrigNameCache. This clears up the previously convoluted relation between the orig name cache and built-in syntax. * Reuse isKnownOrigName_maybe to eliminate the need for isPunOcc_maybe. * Classify MkSolo and MkSolo# as UserSyntax, thus fixing whole-module reexports (#25182). * Teach valid-hole-fits about tuples, unboxed tuples, and unboxed sums, up to a certain arity (#25180). * Drop the unnecessary special case for unary constraint tuples in the type checker (finish_tuple). It was a workaround for the lack of CSolo. * Update Notes and other comments, add tests.
-
- Jan 21, 2025
-
-
Fix build with gcc-15 which defaults to C23 standard (-std=gnu23) Fixes #25662 ``` utils/hp2ps/Utilities.c:6:14: error: warning: conflicting types for built-in function ‘malloc’; expected ‘void *(long unsigned int)’ [-Wbuiltin-declaration-mismatch] 6 | extern void* malloc(); | ^~~~~~ | 6 | extern void* malloc(); | ^ utils/hp2ps/Utilities.c:5:1: error: note: ‘malloc’ is declared in header ‘<stdlib.h>’ 4 | #include "Error.h" +++ |+#include <stdlib.h> 5 | | 5 | | ^ utils/hp2ps/Utilities.c: In function ‘xmalloc’: utils/hp2ps/Utilities.c:80:17: error: error: too many arguments to function ‘malloc’; expected 0, have 1 80 | r = (void*) malloc(n); | ^~~~~~ ~ | 80 | r = (void*) malloc(n); | ^ utils/hp2ps/Utilities.c:6:14: error: note: declared here 6 | extern void* malloc(); | ^~~~~~ | 6 | extern void* malloc(); | ^ utils/hp2ps/Utilities.c: In function ‘xrealloc’: utils/hp2ps/Utilities.c:92:18: error: warning: conflicting types for built-in function ‘realloc’; expected ‘void *(void *, long unsigned int)’ [-Wbuiltin-declaration-mismatch] 92 | extern void *realloc(); | ^~~~~~~ | 92 | extern void *realloc(); | ^ utils/hp2ps/Utilities.c:92:18: error: note: ‘realloc’ is declared in header ‘<stdlib.h>’ | 92 | extern void *realloc(); | ^ utils/hp2ps/Utilities.c:94:9: error: error: too many arguments to function ‘realloc’; expected 0, have 2 94 | r = realloc(p, n); | ^~~~~~~ ~ | 94 | r = realloc(p, n); | ^ utils/hp2ps/Utilities.c:92:18: error: note: declared here 92 | extern void *realloc(); | ^~~~~~~ | 92 | extern void *realloc(); | ^ ```
-
This commit refactors the HomePackageTable and HomeUnitGraph: (1) It fixes a quadratic-in-the-number-of-modules space leak in upsweep (#25511) (2) And it reworks these structures into their own modules to simplify the driver. The refactor is driven by the introduction of IO in the HPT interface, but is a bit more aggressive in simplifying the interfaces to enforce correct usage (ie to avoid performance pitfalls). Specifically: - The `HomeUnitGraph` (HUG) is now in `GHC.Unit.Home.Graph` - The `HomePackageTable` (HPT) is now in `GHC.Unit.Home.PackageTable` - The HPT now stores an `IORef` with the table of loaded home package modules. - The interface to the HPT now requires IO - The interface now enforces that the HPT is a datastructure that only grows - This is not enforced in the interface, but, clients of the HPT should never care about there being more or less entries in the HPT when these additional entries are not relevant to their result. - The exception to the invariant that the HPT is monotonically increasing is `restrictHpt`, a function which is called at a "barrier point" (during which there are no other threads inspecting or inserting in the HPT). The invariant can be temporarily broken at this point (currently, after upsweep). This is safe because a single thread holds control over the structure (thus the invariant being broken is never observed). The hug_var and associated structures in the driver, which aimed to improve memory usage in the driver by updating in place a HUG during upsweep, are no longer required as the HPT entries in the HUG are now themselves mutable by construction. This was previously explained in Note [ModuleNameSet, efficiency and space leaks], which is no longer relevant and was deleted. Fixes #25511 Co-authored-by:
Matthew Pickering <matthewtpickering@gmail.com> ------------------------- Metric Decrease: MultiComponentModulesRecomp MultiLayerModulesRecomp -------------------------
-
This patch: * Ensures that we do not pretty-print a field like `foo :: {-# UNPACK #-} !Int` as `foo :: ! {-# UNPACK -#} Int` (as we were doing before) when running the `:info` command. * Prevents coercions that arise from `UNPACK`ed fields (e.g., such as when one unpacks a newtype) from being printed in `:info` output unless `-dppr-debug` is enabled. Fixes #25651.
-
- Jan 20, 2025
-
-
!13778 accidentally changed hie.yaml to use hie-bios.bat as the default hie-bios script, which completely breaks hie support on non-Windows platforms. This patch reverts that change.
-
Matthew Pickering authored
We now store an ExternalModuleGraph in the EPS. When an new interface is loaded, the module graph is extended with a node for the loaded interface. The result is a partial module graph. If you want to run a transitive closure query on the graph you must first force the transitive closure to be loaded by using `loadExternalGraphBelow`. The primary advantage (for now) is that the transitive dependency calculation does not have to be repeated in getLinkDeps. If your module had many dependencies and many splices, performing this calculation at every splice site took a significant amount of time. We might also want to use this module graph in future for considering questions such as reachability of rules or accessibilty of instance imported by levelled imported. This patch removes another place in the compiler where transitive dependency is calculated in an ad-hoc manner. In general, the transitive dependency calculation should be cached and computed using a ModuleGraph abstraction. The transitive dependency query required by getLinkDeps operates on a graph without hs-boot nodes. If a linkable from a module in a loop is needed, then all modules in the loop are necessary to be available to execute that module. Therefore there is a query in `ModuleGraph` and `ExternalModuleGraph` which allows a transitive closure query to be performed on a graph without loops. Fixes #25634 ------------------------- Metric Decrease: MultiLayerModulesTH_Make MultiLayerModulesTH_OneShot Metric Increase: mhu-perf ------------------------- Co-authored-by:
Rodrigo Mesquita <rodrigo.m.mesquita@gmail.com>
-
- Jan 18, 2025
-
-
-
-
This is a useful test from !8392 which is worth keeping around.
-
This appears to be responsible for the regression described in #25653. This reverts commit daff1e30.
-
sheaf authored
This commit generalises the infrastructure used for diagnostic codes, allowing it to be used for other namespaces than the GHC namespace. In particular, this enables GHCi to re-use the same infrastructure to emit error messages.
-
The problem was that an equation in `split` had two guards (one about visiblity and one about `n_req`). So it fell thorugh if /either/ was False. But the next equation then assumed an invisible binder. Simple bug, easily fixed. Fixes #25661.
-
- Jan 17, 2025
-
-
Mateusz Goślinowski authored
-
MOVD takes the input format. Fixes #25658
-
- Jan 16, 2025
-
-
sheaf authored
This commit refactors makeTypeConcrete to call checkTyEqRhs with the appropriate parameters. This avoids duplicating subtle logic in two places in the compiler. Changes: 1. Refactor of 'TyEqFlags'. Now 'TyEqFlags' stores a 'TEFTask', which is a description of which of the following checks we want to perform in 'checkTyEqRhs': - occurs check - level check - concreteness check In the process, the 'AreUnifying' datatype has been removed, as it is no longer needed. 2. Refactor of 'checkTyVar': a. Make use of the new 'TEFTask' data type to decide which checks to perform. In particular, this ensures that we perform **both** a concreteness check and a level check when both are required; previously we only did a concreteness check (that was a bug!). b. Recursively call 'checkTyVar' on the kind of unfilled metavariables. This deals with a bug in which we failed to uphold the invariant that the kind of a concrete type must itself be concrete. See test cases T23051, T23176. 3. Re-write of 'makeTypeConcrete', which now simply calls 'checkTyEqRhs' with appropriate 'TyEqFlags'/'TEFTask'. This gets rid of code duplication and risk for the two code paths going out-of-sync. Fixes #25616. See also #23883.
-
- Jan 15, 2025
-
-
This fixes the following esbuild error: ✘ [ERROR] Could not resolve "node:timers" www/ghc_wasm_jsffi.js:66:25: 66 │ return (await import("node:timers")).setImmediate; ╵ ~~~~~~~~~~~~~ The package "node:timers" wasn't found on the file system but is built into node. Are you trying to bundle for node? You can use "--platform=node" to do that, which will remove this error. Previously (i.e. after !13503), one had to work around this by passing `--external:node:timers`.
-
- Jan 13, 2025
-
-
Patrick authored
This commit improves kind inference for data family instances by kind-checking the constructors, for H98 and newtype declarations (ONLY), as well as kind-checking the result kind signature (when using GADT syntax). This fixes #25611. Typechecker changes: In `tcDataFamInstHeader`, we now kind-check the constructors using `kcConDecls`, for H98-style decls and newtype decls ONLY. See Note [Kind inference for data family instances]. Testsuite changes: - The T25611{a,b,c,d} tests test the new kind inference implementation. - a,b: infer result kind from constructors (H98 case) - c: renamed version of test UnliftedNewtypesUnassociatedFamilyFail, which now passes - d: GADT case, checking that we don't infer overly rigid kinds when kind-checking the constructors in data family instances. - DataInstanceKindsDefaults tests defaulting data instance kinds without UnliftedNewtypes or UnliftedDatatypes, as outlined in Note [Defaulting result kind of newtype/data family instance]. Also a few notes are updated to reflect the changes. Co-authored-by:
default avatarSimon Peyton Jones <simon.peytonjones@gmail.com>
-
Speculative evaluation can cause performance regressions, therefore we turn it off by default. It can be enabled again with the -fspec-eval-dictfun flag See #25284
-
See: * https://github.com/haskell/core-libraries-committee/issues/300 Seeks to: * move existing instances for NonEmpty (except of Eq and Ord) out of GHC.Internal.Base into new GHC.Internal.Data.NonEmpty (to avoid otherwise unavoidable cycles in the module graph); * move map out of Data.List.NonEmpty (base package) into GHC.Internal.Data.NonEmpty; * define fmap as map for NonEmpty instance of Functor, avoiding code duplication; * re-export map from existing GHC.Internal.Data.List.NonEmpty; and * re-export map from Data.List.NonEmpty (base package); without breaking anything in the GHC repository. Various tests *.stdout and *.stderr files are amended also.
-
sheaf authored
This commit: - turns the SDoc used in ErrCtxt into a proper error datatype, ErrCtxtMsg, which contains all the different error contexts that can be added, - replaces ErrInfo with [ErrCtxt]. ErrInfo used to contain two SDocs; the first is replaced with [ErrCtxt], and the second is removed, with the relevant information being put in the appropriate error message constructors. Fixes #23436
-
- Jan 10, 2025
-
-
While the testsuite driver already normalizes these away, they are nevertheless a severe nuisance when diffing outside of the testsuite. Intriguingly, this doesn't completely eliminate the unit IDs; some wired-in names are still printed. However, this is a cheap and helpful improvement over the status quo so I am simply going to accept this. Fixes #25334.
-
Fixes #25574
-
- Jan 09, 2025
-
-
This makes it considerably easier to grok the structure of the heap when IPE information is available.
-
- Jan 07, 2025
-
-
Luite Stegeman authored
We found that speculative evaluation can increase the amount of allocations in some circumstances. This patch adds new flags for selectively disabling speculative evaluation, allowing us to test the effect of the optimization. The new flags are: -fspec-eval globally enable speculative evaluation -fspec-eval-dictfun enable speculative evaluation for dictionary functions (no effect if speculative evaluation is globally disabled) The new flags are on by default for all optimisation levels. See #25284
-
-
Addresses #25630 In particular, * Introduce ConArgKind and use it. * Make kcConDecls and tcConDecls work the same way concerning the kind of argument types
-
There were two ad-hoc mechanisms used to determine which modules were in the interactive scope. 1. Look at everything in the GRE, to see what is imported qualified. 2. Look at the last loaded module in the HPT. (1) Is very inefficient, GlobalRdrEnvs can be very big. (2) is incorrect, there is no reason to assume the "last" thing added to the HPT has any relevance to module loading order. Happily, the same checks can be implemented directly by looking at the interactive imports from the interactive context. This mirrors what happens for normal imports. Arguably, the error reporting code shouldn't be doing this kind of processing and it should be an option is set when rendering the error message. However, this just improves the situation and doesn't block progress on that front in future. See #14225 and #15611 Fixes #25600
-
- Dec 30, 2024
-
-
-
The issue has been fixed by commit f5d3e03c. Only T23883a is the actual regression test, the remaining ones are tricky cases found during development of an independent fix !11313.
-
- Dec 29, 2024
-
-
Ticket #25468 showed an assertion failure in CSE because a top-level Id was being used before it was defined. Reason: Note [Glomming] in GHC.Core.Opt.OccurAnal. Solution (used in many places): just put all the top-level bindings in scope at the beginning of CSE. Compile-time allocation wobbles up and down a tiny bit; geo mean is zero. But MultiLayerModulesTH_OneShot and hard_hole_fits increase (on some architectures only) by a bit oever 2% . I think these are just a random fluctuations. Metric Increase: MultiLayerModulesTH_OneShot hard_hole_fits
-