summaryrefslogtreecommitdiff
path: root/testsuite
Commit message (Collapse)AuthorAgeFilesLines
* testsuite: add test for T22744Zubin Duggal2023-05-163-0/+44
| | | | | | | | | | | | | | This test checks for #22744 by compiling 100 modules which each have a dependency on 1000 distinct external files. Previously, when loading these interfaces from disk, each individual instance of a filepath in the interface will would be allocated as an individual object on the heap, meaning we have heap objects for 100*1000 files, when there are only 1000 distinct files we care about. This test checks this by first compiling the module normally, then measuring the peak memory usage in a no-op recompile, as the recompilation checking will force the allocation of all these filepaths.
* compiler: Use compact representation for SourceTextZubin Duggal2023-05-161-12/+13
| | | | | | | | | | | | SourceText is serialized along with INLINE pragmas into interface files. Many of these SourceTexts are identical, for example "{-# INLINE#". When deserialized, each such SourceText was previously expanded out into a [Char], which is highly wasteful of memory, and each such instance of the text would allocate an independent list with its contents as deserializing breaks any sharing that might have existed. Instead, we use a `FastString` to represent these, so that each instance unique text will be interned and stored in a memory efficient manner.
* Add -Wmissing-role-annotationsOleg Grenrus2023-05-165-0/+58
| | | | Implements #22702
* Migrate errors to diagnostics in GHC.Tc.Modulesheaf2023-05-1581-473/+809
| | | | | | | | | | | | | | | | | | | | This commit migrates the errors in GHC.Tc.Module to use the new diagnostic infrastructure. It required a significant overhaul of the compatibility checks between an hs-boot or signature module and its implementation; we now use a Writer monad to accumulate errors; see the BootMismatch datatype in GHC.Tc.Errors.Types, with its panoply of subtypes. For the sake of readability, several local functions inside the 'checkBootTyCon' function were split off into top-level functions. We split off GHC.Types.HscSource into a "boot or sig" vs "normal hs file" datatype, as this mirrors the logic in several other places where we want to treat hs-boot and hsig files in a similar fashion. This commit also refactors the Backpack checks for type synonyms implementing abstract data, to correctly reject implementations that contain qualified or quantified types (this fixes #23342 and #23344).
* Split up tyThingToIfaceDecl from GHC.Iface.Makesheaf2023-05-152-0/+2
| | | | | | | This commit moves tyThingToIfaceDecl and coAxiomToIfaceDecl from GHC.Iface.Make into GHC.Iface.Decl. This avoids GHC.Types.TyThing.Ppr, which needs tyThingToIfaceDecl, transitively depending on e.g. GHC.Iface.Load and GHC.Tc.Utils.Monad.
* Split DynFlags structure into own moduleOleg Grenrus2023-05-153-13/+15
| | | | | This will allow to make command line parsing to depend on diagnostic system (which depends on dynflags)
* Fix GHCJS OS platform (fix #23346)Sylvain Henry2023-05-153-0/+21
|
* Improve "ambiguous occurrence" error messagessheaf2023-05-1532-147/+178
| | | | | | | | | This error was sometimes a bit confusing, especially when data families were involved. This commit improves the general presentation of the "ambiguous occurrence" error, and adds a bit of extra context in the case of data families. Fixes #23301
* Unbreak some tests with latest GNU grep, which now warns about stray '\'.M Farkas-Dyck2023-05-154-5/+5
| | | | | | | | Confusingly, the testsuite mangled the error to say "stray /". We also migrate some tests from grep to grep -E, as it seems the author actually wanted an "POSIX extended" (a.k.a. sane) regex. Background: POSIX specifies 2 "regex" syntaxen: "basic" and "extended". Of these, only "extended" syntax is actually a regular expression. Furthermore, "basic" syntax is inconsistent in its use of the '\' character — sometimes it escapes a regex metacharacter, but sometimes it unescapes it, i.e. it makes an otherwise normal character become a metacharacter. This baffles me and it seems also the authors of these tests. Also, the regex(7) man page (at least on Linux) says "basic" syntax is obsolete. Nearly all modern tools and libraries are consistent in this use of the '\' character (of which many use "extended" syntax by default).
* Make GHC.Types.Id.Make.shouldUnpackTy a bit more cleverSimon Peyton Jones2023-05-138-0/+176
| | | | | | | As #23307, GHC.Types.Id.Make.shouldUnpackTy was leaving money on the table, failing to unpack arguments that are perfectly unpackable. The fix is pretty easy; see Note [Recursive unboxing]
* Use a uniform return convention in bytecode for unary resultsAlexis King2023-05-135-0/+47
| | | | fixes #22958
* Use the eager unifier in the constraint solverSimon Peyton Jones2023-05-1236-145/+273
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch continues the refactoring of the constraint solver described in #23070. The Big Deal in this patch is to call the regular, eager unifier from the constraint solver, when we want to create new equalities. This replaces the existing, unifyWanted which amounted to yet-another-unifier, so it reduces duplication of a rather subtle piece of technology. See * Note [The eager unifier] in GHC.Tc.Utils.Unify * GHC.Tc.Solver.Monad.wrapUnifierTcS I did lots of other refactoring along the way * I simplified the treatment of right hand sides that contain CoercionHoles. Now, a constraint that contains a hetero-kind CoercionHole is non-canonical, and cannot be used for rewriting or unification alike. This required me to add the ch_hertero_kind flag to CoercionHole, with consequent knock-on effects. See wrinkle (2) of `Note [Equalities with incompatible kinds]` in GHC.Tc.Solver.Equality. * I refactored the StopOrContinue type to add StartAgain, so that after a fundep improvement (for example) we can simply start the pipeline again. * I got rid of the unpleasant (and inefficient) rewriterSetFromType/Co functions. With Richard I concluded that they are never needed. * I discovered Wrinkle (W1) in Note [Wanteds rewrite Wanteds] in GHC.Tc.Types.Constraint, and therefore now prioritise non-rewritten equalities. Quite a few error messages change, I think always for the better. Compiler runtime stays about the same, with one outlier: a 17% improvement in T17836 Metric Decrease: T17836 T18223
* Fix coercion optimisation for SelCo (#23362)Krzysztof Gogolewski2023-05-122-0/+22
| | | | | | setNominalRole_maybe is supposed to output a nominal coercion. In the SelCo case, it was not updating the stored role to Nominal, causing #23362.
* Allow Core optimizations when interpreting bytecodeKrzysztof Gogolewski2023-05-128-1/+42
| | | | | | | | | | Tracking ticket: #23056 MR: !10399 This adds the flag `-funoptimized-core-for-interpreter`, permitting use of the `-O` flag to enable optimizations when compiling with the interpreter backend, like in ghci.
* Don't panic in mkNewTyConRhssheaf2023-05-123-0/+90
| | | | | | | | | | | | | This function could come across invalid newtype constructors, as we only perform validity checking of newtypes once we are outside the knot-tied typechecking loop. This patch changes this function to fake up a stub type in the case of an invalid newtype, instead of panicking. This patch also changes "checkNewDataCon" so that it reports as many errors as possible at once. Fixes #23308
* rts: Refine memory retention behaviour to account for pinned/compacted objectsMatthew Pickering2023-05-112-0/+72
| | | | | | | | | | | | | | | | | | | | | | | When using the copying collector there is still a lot of data which isn't copied (such as pinned, compacted, large objects etc). The logic to decide how much memory to retain didn't take into account that these wouldn't be copied. Therefore we pessimistically retained 2* the amount of memory for these blocks even though they wouldn't be copied by the collector. The solution is to split up the heap into two parts, the parts which will be copied and the parts which won't be copied. Then the appropiate factor is applied to each part individually (2 * for copying and 1.2 * for not copying). The T23221 test demonstrates this improvement with a program which first allocates many unpinned ByteArray# followed by many pinned ByteArray# and observes the difference in the ultimate memory baseline between the two. There are some charts on #23221. Fixes #23221
* Add a test for #21278Krzysztof Gogolewski2023-05-113-0/+21
|
* Add fused multiply-add instructionssheaf2023-05-114-0/+516
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch adds eight new primops that fuse a multiplication and an addition or subtraction: - `{fmadd,fmsub,fnmadd,fnmsub}{Float,Double}#` fmadd x y z is x * y + z, computed with a single rounding step. This patch implements code generation for these primops in the following backends: - X86, AArch64 and PowerPC NCG, - LLVM - C WASM uses the C implementation. The primops are unsupported in the JavaScript backend. The following constant folding rules are also provided: - compute a * b + c when a, b, c are all literals, - x * y + 0 ==> x * y, - ±1 * y + z ==> z ± y and x * ±1 + z ==> z ± x. NB: the constant folding rules incorrectly handle signed zero. This is a known limitation with GHC's floating-point constant folding rules (#21227), which we hope to resolve in the future.
* Add a test for #17284Krzysztof Gogolewski2023-05-113-0/+14
| | | | Since !10123 we now reject this program.
* Look both ways when looking for quantified equalitiesSimon Peyton Jones2023-05-112-1/+9
| | | | | When looking up (t1 ~# t2) in the quantified constraints, check both orientations. Forgetting this led to #23333.
* Add a regression test for #21050Krzysztof Gogolewski2023-05-093-0/+38
|
* JS: add GHC.JS.Optimizer, remove RTS.Printer, add Linker.Optdoyougnu2023-05-094-8/+116
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This MR changes some simple optimizations and is a first step in re-architecting the JS backend pipeline to add the optimizer. In particular it: - removes simple peep hole optimizations from `GHC.StgToJS.Printer` and removes that module - adds module `GHC.JS.Optimizer` - defines the same peep hole opts that were removed only now they are `Syntax -> Syntax` transformations rather than `Syntax -> JS code` optimizations - hooks the optimizer into code gen - adds FuncStat and ForStat constructors to the backend. Working Ticket: - #22736 Related MRs: - MR !10142 - MR !10000 ------------------------- Metric Decrease: CoOpt_Read ManyAlternatives PmSeriesS PmSeriesT PmSeriesV T10421 T12707 T13253 T13253-spj T15164 T17516 T18140 T18282 T18698a T18698b T18923 T1969 T19695 T20049 T3064 T5321FD T5321Fun T783 T9198 T9233 T9630 -------------------------
* Add structured error messages for GHC.Rename.ModuleTorsten Schmits2023-05-0515-64/+94
| | | | | | | | | | | Tracking ticket: #20115 MR: !10361 This converts uses of `mkTcRnUnknownMessage` to newly added constructors of `TcRnMessage`. Only addresses the single warning missing from the previous MR.
* Rework plugin initialisation pointsAaron Allen2023-05-0511-5/+95
| | | | | | | | | | | | | | | | | | In general this patch pushes plugin initialisation points to earlier in the pipeline. As plugins can modify the `HscEnv`, it's imperative that the plugins are initialised as soon as possible and used thereafter. For example, there are some new tests which modify hsc_logger and other hooks which failed to fire before (and now do) One consequence of this change is that the error for specifying the usage of a HPT plugin from the command line has changed, because it's now attempted to be loaded at initialisation rather than causing a cyclic module import. Closes #21279 Co-authored-by: Matthew Pickering <matthewtpickering@gmail.com>
* Add structured error messages for GHC.Rename.UtilsTorsten Schmits2023-05-05115-200/+201
| | | | | | | | | Tracking ticket: #20115 MR: !10350 This converts uses of `mkTcRnUnknownMessage` to newly added constructors of `TcRnMessage`.
* Fix type variable substitution in gen_Newtype_fam_instsRyan Scott2023-05-043-0/+27
| | | | | | | | | | | | | Previously, `gen_Newtype_fam_insts` was substituting the type variable binders of a type family instance using `substTyVars`, which failed to take type variable dependencies into account. There is similar code in `GHC.Tc.TyCl.Class.tcATDefault` that _does_ perform this substitution properly, so this patch: 1. Factors out this code into a top-level `substATBndrs` function, and 2. Uses `substATBndrs` in `gen_Newtype_fam_insts`. Fixes #23329.
* Fix remaining issues with bound checking (#23123)Sylvain Henry2023-05-041-1/+1
| | | | | | | | | | | | | | | | | | | | While fixing these I've also changed the way we store addresses into ByteArray#. Addr# are composed of two parts: a JavaScript array and an offset (32-bit number). Suppose we want to store an Addr# in a ByteArray# foo at offset i. Before this patch, we were storing both fields as a tuple in the "arr" array field: foo.arr[i] = [addr_arr, addr_offset]; Now we only store the array part in the "arr" field and the offset directly in the array: foo.dv.setInt32(i, addr_offset): foo.arr[i] = addr_arr; It avoids wasting space for the tuple.
* JS: fix bounds checking (Issue 23123)Josh Meredith2023-05-042-2/+1
| | | | | | | | | | | | | | | | | | | | * For ByteArray-based bounds-checking, the JavaScript backend must use the `len` field, instead of the inbuild JavaScript `length` field. * Range-based operations must also check both the start and end of the range for bounds * All indicies are valid for ranges of size zero, since they are essentially no-ops * For cases of ByteArray accesses (e.g. read as Int), the end index is (i * sizeof(type) + sizeof(type) - 1), while the previous implementation uses (i + sizeof(type) - 1). In the Int32 example, this is (i * 4 + 3) * IndexByteArrayOp_Word8As* primitives use byte array indicies (unlike the previous point), but now check both start and end indicies * Byte array copies now check if the arrays are the same by identity and then if the ranges overlap.
* Add hashes to unit-ids created by hadrianromes2023-05-047-8/+10
| | | | | | | | | | | This commit adds support for computing an inputs hash for packages compiled by hadrian. The result is that ABI incompatible packages should be given different hashes and therefore be distinct in a cabal store. Hashing is enabled by the `--flag`, and is off by default as the hash contains a hash of the source files. We enable it when we produce release builds so that the artifacts we distribute have the right unit ids.
* Hardwire a better unit-id for ghcromes2023-05-041-1/+5
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Previously, the unit-id of ghc-the-library was fixed as `ghc`. This was done primarily because the compiler must know the unit-id of some packages (including ghc) a-priori to define wired-in names. However, as seen in #20742, a reinstallable `ghc` whose unit-id is fixed to `ghc` might result in subtle bugs when different ghc's interact. A good example of this is having GHC_A load a plugin compiled by GHC_B, where GHC_A and GHC_B are linked to ghc-libraries that are ABI incompatible. Without a distinction between the unit-id of the ghc library GHC_A is linked against and the ghc library the plugin it is loading was compiled against, we can't check compatibility. This patch gives a slightly better unit-id to ghc (ghc-version) by (1) Not setting -this-unit-id to ghc, but rather to the new unit-id (modulo stage0) (2) Adding a definition to `GHC.Settings.Config` whose value is the new unit-id. (2.1) `GHC.Settings.Config` is generated by Hadrian (2.2) and also by cabal through `compiler/Setup.hs` This unit-id definition is imported by `GHC.Unit.Types` and used to set the wired-in unit-id of "ghc", which was previously fixed to "ghc" The commits following this one will improve the unit-id with a cabal-style package hash and check compatibility when loading plugins. Note that we also ensure that ghc's unit key matches unit id both when hadrian or cabal builds ghc, and in this way we no longer need to add `ghc` to the WiringMap.
* Don't forget to check the parent in an export listsheaf2023-05-033-0/+6
| | | | | | | | Commit 3f374399 introduced a bug which caused us to forget to include the parent of an export item of the form T(..) (that is, IEThingAll) when checking for duplicate exports. Fixes #23318
* Add sized primitive literal syntaxBen Orchard2023-05-0310-260/+347
| | | | | | | | | | | | | | Adds a new LANGUAGE pragma ExtendedLiterals, which enables defining unboxed numeric literals such as `0xFF#Word8 :: Word8#`. Implements GHC proposal 0451: https://github.com/ghc-proposals/ghc-proposals/blob/b384a538b34f79d18a0201455b7b3c473bc8c936/proposals/0451-sized-literals.rst Fixes #21422. Bumps haddock submodule. Co-authored-by: Krzysztof Gogolewski <krzysztof.gogolewski@tweag.io>
* Add structured error messages for GHC.Rename.NamesTorsten Schmits2023-04-3068-74/+104
| | | | | | | | | Tracking ticket: #20115 MR: !10336 This converts uses of `mkTcRnUnknownMessage` to newly added constructors of `TcRnMessage`.
* Add the Unsatisfiable classsheaf2023-04-2927-0/+470
| | | | | | | | | This commit implements GHC proposal #433, adding the Unsatisfiable class to the GHC.TypeError module. This provides an alternative to TypeError for which error reporting is more predictable: we report it when we are reporting unsolved Wanted constraints. Fixes #14983 #16249 #16906 #18310 #20835
* testsuite: wasm32-specific fixesCheng Shao2023-04-2711-15/+49
| | | | This patch includes all wasm32-specific testsuite fixes.
* testsuite: add missing annotations for some testsCheng Shao2023-04-275-8/+17
| | | | | | | This patch adds missing annotations (req_th, req_dynamic_lib_support, req_rts_linker) to some tests. They were discovered when testing wasm32, though it's better to be explicit about what features they require, rather than simply adding when(arch('wasm32'), skip).
* testsuite: add the req_host_target_ghc predicateCheng Shao2023-04-272-0/+20
| | | | | | | This patch adds the req_host_target_ghc predicate to the testsuite to assert the ghc compiler being tested can compile both host/target code. When testing cross GHCs this is not supported yet, but it may change in the future.
* testsuite: add the req_process predicateCheng Shao2023-04-275-2/+16
| | | | | | This patch adds the req_process predicate to the testsuite to assert the platform has a process model, also marking tests that involve spawning processes as req_process. Also bumps hpc & process submodule.
* testsuite: add the req_ghc_with_threaded_rts predicateCheng Shao2023-04-278-11/+18
| | | | | | | This patch adds the req_ghc_with_threaded_rts predicate to the testsuite to assert the platform has threaded RTS, and mark some tests as req_ghc_with_threaded_rts. Also makes ghc_with_threaded_rts a config field instead of a global variable.
* testsuite: fix permission bits in copy_filesCheng Shao2023-04-272-1/+3
| | | | | | | | When the testsuite driver copy files instead of symlinking them, it should also copy the permission bits, otherwise there'll be permission denied errors. Also, enforce file copying when testing wasm32, since wasmtime doesn't handle host symlinks quite well (https://github.com/bytecodealliance/wasmtime/issues/6227).
* testsuite: exclude ghci ways if no rts linker is presentCheng Shao2023-04-272-1/+11
| | | | | | This patch implements logic to automatically exclude ghci ways when there is no rts linker. It's way better than having to annotate individual test cases.
* testsuite: include target exe extension in heap profile filenamesCheng Shao2023-04-271-5/+6
| | | | | | This patch fixes hp2ps related framework failures when testing the wasm backend by including target exe extension in heap profile filenames.
* testsuite: fix cross prefix strippingCheng Shao2023-04-271-8/+6
| | | | | | | | This patch fixes cross prefix stripping in the testsuite driver. The normalization logic used to only handle prefixes of the triple form <arch>-<vendor>-<os>, now it's relaxed to allow any number of tokens in the prefix tuple, so the cross prefix stripping logic would work when ghc is configured with something like --target=wasm32-wasi.
* EPA: Use ExplicitBraces only in HsModuleAlan Zimmerman2023-04-2617-117/+27
| | | | | | | | | !9018 brought in exact print annotations in LayoutInfo for open and close braces at the top level. But it retained them in the HsModule annotations too. Remove the originals, so exact printing uses LayoutInfo
* Refactor GenStgRhs to include the Type in both constructors (#23280, #22576, ↵Josh Meredith2023-04-264-4/+4
| | | | | | | | | #22364) Carry the actual type of an expression through the PreStgRhs and into GenStgRhs for use in later stages. Currently this is used in the JavaScript backend to fix some tests from the above mentioned issues: EtaExpandLevPoly, RepPolyWrappedVar2, T13822, T14749.
* DmdAnal: Unleash demand signatures of free RULE and unfolding binders (#23208)Sebastian Graf2023-04-2610-101/+162
| | | | | | | | | | | | | | | | | | | | | | | | | | | In #23208 we observed that the demand signature of a binder occuring in a RULE wasn't unleashed, leading to a transitively used binder being discarded as absent. The solution was to use the same code path that we already use for handling exported bindings. See the changes to `Note [Absence analysis for stable unfoldings and RULES]` for more details. I took the chance to factor out the old notion of a `PlusDmdArg` (a pair of a `VarEnv Demand` and a `Divergence`) into `DmdEnv`, which fits nicely into our existing framework. As a result, I had to touch quite a few places in the code. This refactoring exposed a few small bugs around correct handling of bottoming demand environments. As a result, some strictness signatures now mention uniques that weren't there before which caused test output changes to T13143, T19969 and T22112. But these tests compared whole -ddump-simpl listings which is a very fragile thing to begin with. I changed what exactly they test for based on the symptoms in the corresponding issues. There is a single regression in T18894 because we are more conservative around stable unfoldings now. Unfortunately it is not easily fixed; let's wait until there is a concrete motivation before invest more time. Fixes #23208.
* Give more guarntees about ImplicitParams (#23289)Andrei Borzenkov2023-04-253-0/+16
| | | | | | | | | | | | | | | | - Added new section in the GHC user's guide that legends behavior of nested implicit parameter bindings in these two cases: let ?f = 1 in let ?f = 2 in ?f and data T where MkT :: (?f :: Int) => T f :: T -> T -> Int f MkT MkT = ?f - Added new test case to examine this behavior.
* JS: Fix h$base_access implementation (issue 22576)Josh Meredith2023-04-253-3/+3
|
* JS/base: provide implementation for mkdir (issue 22374)Josh Meredith2023-04-251-1/+1
|
* More informative errors for bad imports (#21826)Soham Chowdhury2023-04-2548-123/+211
|