Simon Peyton Jones pushed to branch wip/T23162-part2 at Glasgow Haskell Compiler / GHC
Commits:
b8821d43 by Simon Peyton Jones at 2025-11-15T23:18:00+00:00
Better
Fix Yikes 3
Ensure we do F a ~ F b for families with no eqns
- - - - -
2 changed files:
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Tc/Solver/FunDeps.hs
Changes:
=====================================
compiler/GHC/Core/TyCon.hs
=====================================
@@ -2448,8 +2448,9 @@ isOpenTypeFamilyTyCon (TyCon { tyConDetails = details })
| FamilyTyCon {famTcFlav = OpenSynFamilyTyCon } <- details = True
| otherwise = False
--- | Is this a non-empty closed type family? Returns 'Nothing' for
--- abstract or empty closed families.
+-- | Is this a /non-empty/ closed type family?
+-- Returns 'Nothing' for closed type family with no equations, as well
+-- as for open families, data famlilies, abstract families
isClosedFamilyTyCon_maybe :: TyCon -> Maybe (CoAxiom Branched)
isClosedFamilyTyCon_maybe (TyCon { tyConDetails = details })
| FamilyTyCon {famTcFlav = ClosedSynFamilyTyCon mb} <- details = mb
=====================================
compiler/GHC/Tc/Solver/FunDeps.hs
=====================================
@@ -25,6 +25,7 @@ import GHC.Core.FamInstEnv
import GHC.Core.Coercion
import GHC.Core.Predicate( EqRel(..) )
import GHC.Core.TyCon
+import GHC.Core.Type( tyConAppTyCon_maybe )
import GHC.Core.Unify( tcUnifyTysForInjectivity, typeListsAreApart )
import GHC.Core.Coercion.Axiom
import GHC.Core.TyCo.Subst( elemSubst )
@@ -467,7 +468,8 @@ tryEqFunDeps work_item@(EqCt { eq_lhs = work_lhs
, eq_eq_rel = eq_rel })
| NomEq <- eq_rel
, TyFamLHS fam_tc work_args <- work_lhs -- We have F args ~N# rhs
- = do { eqs_for_me <- simpleStage$ getInertFamEqsFor fam_tc work_args work_rhs
+ = do { simpleStage $ traceTcS "tryEqFunDeps" (ppr work_item)
+ ; eqs_for_me <- simpleStage $ getInertFamEqsFor fam_tc work_args work_rhs
; tryFamEqFunDeps eqs_for_me fam_tc work_args work_item }
| otherwise
= nopStage ()
@@ -482,7 +484,7 @@ tryFamEqFunDeps eqs_for_me fam_tc work_args
else do { -- Note [Do local fundeps before top-level instances]
tryFDEqns fam_tc work_args work_item $
mkLocalBuiltinFamEqFDs eqs_for_me fam_tc ops work_args work_rhs
- ; if null eqs_for_me
+ ; if all (isWanted . eqCtEvidence) eqs_for_me
then tryFDEqns fam_tc work_args work_item $
mkTopBuiltinFamEqFDs fam_tc ops work_args work_rhs
else nopStage () }
@@ -492,38 +494,37 @@ tryFamEqFunDeps eqs_for_me fam_tc work_args
-- Only Wanted constraints below here
- | isOpenTypeFamilyTyCon fam_tc
- , Injective inj_flags <- tyConInjectivityInfo fam_tc
- = -- Open, injective type families
- do { -- Note [Do local fundeps before top-level instances]
- tryFDEqns fam_tc work_args work_item $
- mkLocalFamEqFDs eqs_for_me fam_tc inj_flags work_args work_rhs
-
- ; if null eqs_for_me
- then tryFDEqns fam_tc work_args work_item $
- mkTopOpenFamEqFDs fam_tc inj_flags work_args work_rhs
- else nopStage () }
-
- | Just ax <- isClosedFamilyTyCon_maybe fam_tc
- = -- Closed type families
- do { -- Note [Do local fundeps before top-level instances]
- simpleStage $ traceTcS "fundep closed" (ppr fam_tc)
-
- ; case tyConInjectivityInfo fam_tc of
+ | otherwise -- Wanted, user-defined type families
+ = do { -- Note [Do local fundeps before top-level instances]
+ case tyConInjectivityInfo fam_tc of
NotInjective -> nopStage()
Injective inj -> tryFDEqns fam_tc work_args work_item $
mkLocalFamEqFDs eqs_for_me fam_tc inj work_args work_rhs
- -- Now look at the top-level axioms; we effectively infer injectivity,
- -- so we don't need tyConInjectivtyInfo. This works fine for closed
- -- type families without injectivity info
- ; if null eqs_for_me
+ ; if all (isWanted . eqCtEvidence) eqs_for_me
then tryFDEqns fam_tc work_args work_item $
- mkTopClosedFamEqFDs ax work_args work_rhs
+ mkTopFamEqFDs fam_tc work_args work_rhs
else nopStage () }
- | otherwise -- Data families, abstract families
- = nopStage ()
+mkTopFamEqFDs :: TyCon -> [TcType] -> Xi -> TcS [FunDepEqns]
+mkTopFamEqFDs fam_tc work_args work_rhs
+ | isOpenTypeFamilyTyCon fam_tc
+ , Injective inj_flags <- tyConInjectivityInfo fam_tc
+ = -- Open, injective type families
+ mkTopOpenFamEqFDs fam_tc inj_flags work_args work_rhs
+
+ | Just ax <- isClosedFamilyTyCon_maybe fam_tc
+ = -- Closed type families
+ -- Look at the top-level axioms; we effectively infer injectivity,
+ -- so we don't need tyConInjectivtyInfo. This works fine for closed
+ -- type families without injectivity info
+ mkTopClosedFamEqFDs ax work_args work_rhs
+
+ | otherwise
+ = -- Data families, abstract families,
+ -- open families that are not injective,
+ -- closed type families with no equations (isClosedFamilyTyCon_maybe returns Nothing)
+ return []
tryFDEqns :: TyCon -> [TcType] -> EqCt -> TcS [FunDepEqns] -> SolverStage ()
tryFDEqns fam_tc work_args work_item@(EqCt { eq_ev = ev, eq_rhs= rhs }) mk_fd_eqns
@@ -542,6 +543,8 @@ tryFDEqns fam_tc work_args work_item@(EqCt { eq_ev = ev, eq_rhs= rhs }) mk_fd_eq
-----------------------------------------
mkTopClosedFamEqFDs :: CoAxiom Branched -> [TcType] -> Xi -> TcS [FunDepEqns]
mkTopClosedFamEqFDs ax work_args work_rhs
+ | Just tc <- tyConAppTyCon_maybe work_rhs -- Does RHS have anything useful to say?
+ , isGenerativeTyCon tc Nominal
= do { let branches = fromBranches (coAxiomBranches ax)
; traceTcS "mkTopClosed" (ppr branches $$ ppr work_args $$ ppr work_rhs)
; case getRelevantBranches ax work_args work_rhs of
@@ -549,6 +552,8 @@ mkTopClosedFamEqFDs ax work_args work_rhs
-> return [FDEqns { fd_qtvs = qtvs
, fd_eqs = zipWith Pair (rhs_ty:lhs_tys) (work_rhs:work_args) }]
_ -> return [] }
+ | otherwise
+ = return []
getRelevantBranches :: CoAxiom Branched -> [TcType] -> Xi -> [CoAxBranch]
@@ -727,12 +732,14 @@ mkInjectivityFDEqn inj_args qtvs lhs_args rhs_args
| (True, lhs_arg, rhs_arg) <- zip3 inj_args lhs_args rhs_args ]
getInertFamEqsFor :: TyCon -> [TcType] -> Xi -> TcS [EqCt]
--- Returns a mixture of Given and Wanted
-- Look in the InertSet, and return all inert equalities
-- F tys ~N# rhs
-- where F is the specified TyCon
--- But filter out ones that can't possibly help, is apart from the Wanted
--- Representational equalities don't interact with type family dependencies
+-- But filter out ones that can't possibly help;
+-- that is, ones that are "apart" from the Wanted
+-- Returns a mixture of Given and Wanted
+-- Nominal only, becaues Representational equalities don't interact
+-- with type family dependencies
getInertFamEqsFor fam_tc work_args work_rhs
= do { IC {inert_funeqs = funeqs } <- getInertCans
; return [ funeq_ct | equal_ct_list <- findFunEqsByTyCon funeqs fam_tc
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b8821d43e28488206daff9db6fb13e1…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b8821d43e28488206daff9db6fb13e1…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/io-manager-deadlock-detection] 25 commits: Make the IOManager API use CapIOManager rather than Capability
by Duncan Coutts (@dcoutts) 15 Nov '25
by Duncan Coutts (@dcoutts) 15 Nov '25
15 Nov '25
Duncan Coutts pushed to branch wip/io-manager-deadlock-detection at Glasgow Haskell Compiler / GHC
Commits:
6755737b by Duncan Coutts at 2025-11-15T21:18:33+00:00
Make the IOManager API use CapIOManager rather than Capability
This makes the API somewhat more self-contained and more consistent.
Now the IOManager API and each of the backends takes just the I/O
manager structure. Previously we had a bit of a mixture, depending on
whether the function needed access to the Capability or just the
CapIOManager.
We still need access to the cap, so we introduce a back reference to
reach the capability, via iomgr->cap.
Convert all uses in select and poll backends, but not win32 ones.
Convert callers in the scheduler and elsewhere.
Also convert the three CMM primops that call IOManager APIs. They just
need to use Capability_iomgr(MyCapability()).
- - - - -
c62f7d73 by Duncan Coutts at 2025-11-15T21:18:34+00:00
Split posix/MIO.c out of posix/Signals.c
The MIO I/O manager was secretly living inside the Signals file.
Now it gets its own file, like any other self-respecting I/O manager.
- - - - -
6a7e3be8 by Duncan Coutts at 2025-11-15T21:18:34+00:00
Rationalise some scheduler run queue utilities
Move them all to the same place in the file.
Make some static that were used only internally.
Also remove a redundant assignment after calling truncateRunQueue that
is already done within truncateRunQueue.
- - - - -
3bb8999e by Duncan Coutts at 2025-11-15T21:18:34+00:00
Rename initIOManager{AfterFork} to {re}startIOManager
These are more accurate names, since these actions happen after
initialisation and are really about starting (or restarting) background
threads.
- - - - -
64397059 by Duncan Coutts at 2025-11-15T21:18:34+00:00
Add a TODO to the MIO I/O manager
The direction of travel is to make I/O managers per-capability and have
all their state live in the struct CapIOManager. The MIO I/O manager
however still has a number of global variables.
It's not obvious how handle these globals however.
- - - - -
bc8a0ddc by Duncan Coutts at 2025-11-15T21:18:34+00:00
Free per-cap I/O managers during shutdown and forkProcess
Historically this was not strictly necessary. The select and win32
legacy I/O managers did not maintain any dynamically allocated
resources. The new poll one does (an auxillary table), and so this
should be freed.
After forkProcess, all threads get deleted. This includes threads
waiting on I/O or timers. So as of this patch, resetting the I/O
manager is just about tidying things up. For example, for the poll
I/O manager this will reset the size of the AIOP table (which
otherwise grows but never shrinks).
In future however the re-initialising will become neeecessary for
functionality, since some I/O managers will need to re-initialise
wakeup fds that are set CLOEXEC.
- - - - -
f23f321f by Duncan Coutts at 2025-11-15T21:18:34+00:00
Add an FdWakup module for posix I/O managers
This will be used to implement wakeupIOManager for in-RTS I/O managers.
It provides a notification/wakeup mechanism using FDs, suitable for
situations when I/O managers are blocked on a set of fds anyway.
- - - - -
35a9653d by Duncan Coutts at 2025-11-15T21:18:34+00:00
Add wakeupIOManager support for select I/O manager
Uses the FdWakup mechanism.
- - - - -
adf29463 by Duncan Coutts at 2025-11-15T21:18:34+00:00
Add wakeupIOManager support for poll I/O manager
Uses the FdWakup mechanism.
A quirk we have to cope with is that we now need to poll one more fd --
the wakeup_fd_r -- but this fd has no corresponding entry in the
aiop_table. This is awkward since we have set up our aiop_poll_table to
be an auxilliary table with matching indicies.
The solution this patch uses (and described in the comments) is to have
two tables: struct pollfd *aiop_poll_table, *full_poll_table;
and to have the aiop_poll_table alias the tail of the full_poll_table.
The head entry in the full_poll_table is the extra fd. So we poll the
full_poll_table, while the aiop_poll_table still has matching indicies
with the aiop_table.
Hurrah for C aliasing rules.
- - - - -
30b7fe6b by Duncan Coutts at 2025-11-15T21:18:34+00:00
Add wakeupIOManager support for win32 legacy I/O manager
- - - - -
14f56d0e by Duncan Coutts at 2025-11-15T21:18:34+00:00
wakeupIOManager is now required for all I/O managers
We are going to rely on it. Previously it could be a no-op. Update the
docs in the header file.
Also, temporarily disable awaitCompletedTimeoutsOrIO post-condition
assertion. It will become more complicated due to wakeupIOManager, and
it's not yet clear how to express it.
We will re-introduce a post condition after a few more changes.
- - - - -
2b8c1604 by Duncan Coutts at 2025-11-15T21:18:34+00:00
Make signal handling be a respondibility of the I/O manager(s)
Previously it was scattered between I/O managers and the scheduler, and
especially the scheduler's deadlock detection.
Previously the scheduler would poll for pending signals each iteration
of the scheduler loop. The scheduler also had some hairy signal
functionality in the deadlock detection: in the non-threaded RTS (only)
if there were still no threads running after deadlock detection then it
would block waiting for signals.
But signals can and (in my opinion) should be thought of as just a funny
kind of I/O, and thus should be a responsibility of the I/O manager.
So now we have the I/O managers poll for signals when they are polling
for I/O completion (and removing the separate poll in the scheduler).
And when I/O managers block waiting for I/O then they now also start
signal handlers if they get interrupted by a signal. Crucially, if there
is no pending I/O or timers, the awaitCompletedTimeoutsOrIO will still
block waiting for signals.
This patch puts us into an intermediate state: it temporarily breaks
deadlock detection in the non-threaded RTS. The waiting on I/O currently
happens before deadlock detection. This means we'll now wait forever on
signals before doing deadlock detection. We need to move waiting after
deadlock detection. We'll do that in a later patch.
- - - - -
c8f52a52 by Duncan Coutts at 2025-11-15T21:18:34+00:00
Clean up signal handling internal API
Now that the I/O manager is responsible for signals, we can simplify the
API we present for signal handling.
We now just need startPendingSignalHandlers, which is called from the
I/O managers. We can get rid of awaitUserSignals. We also don't need
RtsSignals.h to re-export the platform-specific posix/Signals.h or
win32/ConsoleHandler.h
We can also hide more of the implementation of signals. Less has to be
exposed in posix/Signals.h or win32/ConsoleHandler.h. Partly this is
because we don't need inline functions (or macros) in the interface.
Also remove signal_handlers from RTS ABI exported symbols list. It does
not appear to have any users in the core libs, and its really an
internal implementation detail. It should not be exposed unless its
really necessary.
- - - - -
626d112c by Duncan Coutts at 2025-11-15T21:18:34+00:00
In the scheduler, move I/O blocking after deadlock detection
To make deadlock detection effective in the non-threaded RTS when there
are deadlocked threads and other unrelated threads waiting on I/O, we
need to arrange to do deadlock detection before we block in scheduler
to wait on I/O.
The solution is to:
1. adjust scheduleFindWork, which runs before deadlock detection, to
only poll for I/O and not block; and
2. add a step after deadlock detection to wait on I/O if there are
still no threads to run (and there's any I/O or timeouts outstanding)
The scheduleCheckBlockedThreads is now so simple that it made more sense
to inline it into scheduleFindWork.
- - - - -
ea1b84b2 by Duncan Coutts at 2025-11-15T21:18:34+00:00
Remove bogus anyPendingTimeoutsOrIO guard from scheduleDetectDeadlock
The deadlock detection was only invoked if both of these conditions
hold:
1. the run queue is empty
2. there is no pending I/O or timeouts
The second condition is unnecessary. The deadlock detection mechanism
can find deadlocks even if there are other threads waiting on I/O or
timers. Having this extra condition means that we fail to detect
blocked threads if there are any threads waiting on I/O or timers.
Part of fixing issue #26408
- - - - -
eefcdfea by Duncan Coutts at 2025-11-15T21:18:34+00:00
Don't consider pending I/O for early context switch optimisation
Context switches are normally initiated by the timer signal. If however
the user specifies "context switch as often as possible", with +RTS -C0
then the scheduler arranges for an early context switch (when it's just
about to run a Haskell thread).
Context switching very often is expensive, so as an optimisation there
cases where we do not arrange an early context switch:
1. if there's no other threads to run
2. if there is no pending I/O or timers
This patch eliminates case 2, leaving only case 1.
The rationale is as follows. The use of this was inconsistent across
platforms and threaded/non-threaded RTS ways. It only worked on the
non-threaded RTS and on Windows only worked for the win32-legacy I/O
manager. On all other combinations anyPendingTimeoutsOrIO would always
return false. The fact that nobody noticed and complained about this
inconsistency suggests that the feature is not relied upon.
If however it turns out that applications do rely on this, then the
proper thing to do is not to restore this check, but to add a new I/O
manager hint function that returns if there is any pending events that
are likely to happen *soon*: for example timeouts expiring within one
timeslice, or I/O waits on things likely to complete soon like disk I/O,
but not for example socket/pipe I/O.
The motivation to avoid this use of anyPendingTimeoutsOrIO is to
allow us to eliminate anyPendingTimeoutsOrIO entirely. All other uses
of this are just guards on {await,poll}CompletedTimeoutsOrIO and
the guards can safely be folded into those functions. This will better
cope with some I/O managers having no proper implementation of
anyPendingTimeoutsOrIO.
Ultimately this will let us simplify the scheduler which currently has
to have special #ifdef mingw32_HOST_OS cases to cope with the lack of a
working anyPendingTimeoutsOrIO for some Windows I/O managers
- - - - -
2fee1ad9 by Duncan Coutts at 2025-11-15T21:18:34+00:00
Remove anyPendingTimeoutsOrIO guarding {poll,await}CompletedTimeoutsOrIO
Previously the API of the I/O manager used a two step process: check
anyPendingTimeoutsOrIO and then call {poll,await}CompletedTimeoutsOrIO.
This was primarily there as a performance thing, to cheaply check if we
need to do anything.
And then because anyPendingTimeoutsOrIO existed, it was used for other
things too. We have now eliminated the other uses, and are just left
with the performance pattern.
But this was problematic because not all I/O managers correctly
implement anyPendingTimeoutsOrIO (specifically the win32 ones), and now
that we also make I/O managers responsible for signals then we need to
poll/await even if there is no pending I/O or timeouts. If there is no
pending I/O or timeouts then poll/await needs to degenerate to just
waiting forever for any signals.
- - - - -
306c7616 by Duncan Coutts at 2025-11-15T21:18:34+00:00
Remove anyPendingTimeoutsOrIO, it is no longer used
And this avoids the problems arising from the win32 I/O managers having
had a bogus implementation.
- - - - -
edd9dbf9 by Duncan Coutts at 2025-11-15T21:18:34+00:00
Remove second scheduler call to awaitCompletedTimeoutsOrIO
Previously awaitCompletedTimeoutsOrIO was called both before and after
deadlock detection in the scheduler. The reason for that was that the
win32 I/O managers had a bogus implementation of anyPendingTimeoutsOrIO
and this was used to guard the call of awaitCompletedTimeoutsOrIO prior
to deadlock detection. This meant the first call site was never actually
called when using the win32 I/O managers. This was the reason for the
second call: the first one was never used. What a mess.
So now we have a simple design in the scheduler:
1. poll for completed I/O, timers or signals
2. if no runnable threads: do deadlock detection
3. if still no runnable threads: block waiting for I/O, timers or
signals.
- - - - -
27470f83 by Duncan Coutts at 2025-11-15T21:18:34+00:00
Lift emptyRunQueue guard out of scheduleDetectDeadlock
this improved the clarity of the logic when reading the scheduler code.
- - - - -
b927bf9c by Duncan Coutts at 2025-11-15T21:18:34+00:00
Make non-threaded deadlock detection also rely on idle GC
Only do deadlock detection GC when idle GC kicks in. This also relies on
using wakeUpRts, so now do this unconditionally. Previously wakeUpRts
was for the threaded rts only.
- - - - -
6f9d9d20 by Duncan Coutts at 2025-11-15T21:18:34+00:00
Enable idle GC by default on non-threaded RTS.
The behaviour is now uniform between threaded and non-threaded. The
deadlock detection now relies on idle GC for both threaded and
non-threaded ways. Previously deadlock detection did not rely on idle
GC for the non-threaded way.
- - - - -
3d4bc7d3 by Duncan Coutts at 2025-11-15T21:18:34+00:00
Add a long Note [Deadlock detection]
It describes the historical and modern designs and their trade-offs.
The point is we've now unified the code for deadlock detection between
the threaded and non-threaded ways, by changing the non-threaded to
follow the same design as the threaded.
- - - - -
4bc527ef by Duncan Coutts at 2025-11-15T21:18:34+00:00
Add a test for deadlock detection, issue #26408
- - - - -
eb13b6d4 by Duncan Coutts at 2025-11-15T21:18:34+00:00
Update the user guide with the revised idle GC behaviour
i.e. it's now not just for the threaded RTS, but general.
Also document the fact that disabling idle GC also disables deadlock
detection.
- - - - -
33 changed files:
- docs/users_guide/runtime_control.rst
- rts/Capability.c
- rts/IOManager.c
- rts/IOManager.h
- rts/IOManagerInternals.h
- rts/PrimOps.cmm
- rts/RaiseAsync.c
- rts/RtsFlags.c
- rts/RtsSignals.h
- rts/RtsStartup.c
- rts/RtsSymbols.c
- rts/Schedule.c
- rts/Schedule.h
- rts/Timer.c
- + rts/posix/FdWakeup.c
- + rts/posix/FdWakeup.h
- + rts/posix/MIO.c
- + rts/posix/MIO.h
- rts/posix/Poll.c
- rts/posix/Poll.h
- rts/posix/Select.c
- rts/posix/Select.h
- rts/posix/Signals.c
- rts/posix/Signals.h
- rts/posix/Timeout.c
- rts/posix/Timeout.h
- rts/rts.cabal
- rts/win32/AwaitEvent.c
- rts/win32/ConsoleHandler.c
- rts/win32/ConsoleHandler.h
- + testsuite/tests/rts/T26408.hs
- + testsuite/tests/rts/T26408.stderr
- testsuite/tests/rts/all.T
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7d601300898f314a7b9fe7164872ce…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7d601300898f314a7b9fe7164872ce…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 7 commits: Report all missing modules with -M
by Marge Bot (@marge-bot) 15 Nov '25
by Marge Bot (@marge-bot) 15 Nov '25
15 Nov '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
c0a1e574 by Georgios Karachalias at 2025-11-15T05:14:31-05:00
Report all missing modules with -M
We now report all missing modules at once in GHC.Driver.Makefile.processDeps,
as opposed to only reporting a single missing module. Fixes #26551.
- - - - -
c9fa3449 by Sylvain Henry at 2025-11-15T05:15:26-05:00
JS: fix array index for registers
We used to store R32 in h$regs[-1]. While it's correct in JavaScript,
fix this to store R32 in h$regs[0] instead.
- - - - -
9e469909 by Sylvain Henry at 2025-11-15T05:15:26-05:00
JS: support more than 128 registers (#26558)
The JS backend only supported 128 registers (JS variables/array slots
used to pass function arguments). It failed in T26537 when 129
registers were required.
This commit adds support for more than 128 registers: it is now limited to
maxBound :: Int (compiler's Int). If we ever go above this threshold the
compiler now panics with a more descriptive message.
A few built-in JS functions were assuming 128 registers and have been
rewritten to use loops. Note that loops are only used for "high"
registers that are stored in an array: the 31 "low" registers are still
handled with JS global variables and with explicit switch-cases to
maintain good performance in the most common cases (i.e. few registers
used). Adjusting the number of low registers is now easy: just one
constant to adjust (GHC.StgToJS.Regs.lowRegsCount).
No new test added: T26537 is used as a regression test instead.
- - - - -
38d82f38 by Sven Tennie at 2025-11-15T14:00:36-05:00
AArch64: Simplify CmmAssign and CmmStore
The special handling for floats was fake: The general case is always
used. So, the additional code path isn't needed (and only adds
complexity for the reader.)
- - - - -
e77ca589 by sheaf at 2025-11-15T14:00:42-05:00
SimpleOpt: refactor & push coercions into lambdas
This commit improves the simple optimiser (in GHC.Core.SimpleOpt)
in a couple of ways:
- The logic to push coercion lambdas is shored up.
The function 'pushCoercionIntoLambda' used to be called in 'finish_app',
but this meant we could not continue to optimise the program after
performing this transformation.
Now, we call 'pushCoercionIntoLambda' as part of 'simple_app'.
Doing so can be important when dealing with unlifted newtypes,
as explained in Note [Desugaring unlifted newtypes].
- The code is re-structured to avoid duplication and out-of-sync
code paths.
Now, 'simple_opt_expr' defers to 'simple_app' for the 'App', 'Var',
'Cast' and 'Lam' cases. This means all the logic for those is
centralised in a single place (e.g. the 'go_lam' helper function).
To do this, the general structure is brought a bit closer to the
full-blown simplifier, with a notion of 'continuation'
(see 'SimpleContItem').
This commit also modifies GHC.Core.Opt.Arity.pushCoercionIntoLambda to
apply a substitution (a slight generalisation of its existing implementation).
- - - - -
3a455f28 by sheaf at 2025-11-15T14:00:42-05:00
Improve typechecking of data constructors
This commit changes the way in which we perform typecheck data
constructors, in particular how we make multiplicities line up.
Now, impedance matching occurs as part of the existing subsumption
machinery. See the revamped Note [Typechecking data constructors] in
GHC.Tc.Gen.App, as well as Note [Polymorphisation of linear fields]
in GHC.Core.Multiplicity.
This allows us to get rid of a fair amount of hacky code that was
added with the introduction of LinearTypes; in particular the logic of
GHC.Tc.Gen.Head.tcInferDataCon.
-------------------------
Metric Decrease:
T10421
T14766
T15164
T15703
T19695
T5642
T9630
WWRec
-------------------------
- - - - -
7a962679 by sheaf at 2025-11-15T14:00:42-05:00
Handle unsaturated rep-poly newtypes
This commit allows GHC to handle unsaturated occurrences of unlifted
newtype constructors. The plan is detailed in
Note [Eta-expanding rep-poly unlifted newtypes]
in GHC.Tc.Utils.Concrete: for unsaturated unlifted newtypes, we perform
the appropriate representation-polymorphism check in tcInstFun.
- - - - -
77 changed files:
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Multiplicity.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/TyCo/FVs.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Driver/Config/Core/Lint.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Type.hs
- compiler/GHC/StgToJS/Apply.hs
- compiler/GHC/StgToJS/Expr.hs
- compiler/GHC/StgToJS/Regs.hs
- compiler/GHC/StgToJS/Rts/Rts.hs
- compiler/GHC/StgToJS/Rts/Types.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Expr.hs-boot
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Concrete.hs
- compiler/GHC/Tc/Utils/TcType.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/Types/Id/Make.hs
- testsuite/tests/codeGen/should_run/all.T
- testsuite/tests/diagnostic-codes/codes.stdout
- testsuite/tests/driver/Makefile
- + testsuite/tests/driver/T26551.hs
- + testsuite/tests/driver/T26551.stderr
- testsuite/tests/driver/all.T
- testsuite/tests/ghci/scripts/T8959b.stderr
- testsuite/tests/ghci/scripts/ghci051.stderr
- testsuite/tests/indexed-types/should_compile/T12538.stderr
- + testsuite/tests/linear/should_compile/LinearEtaExpansions.hs
- testsuite/tests/linear/should_compile/all.T
- testsuite/tests/linear/should_fail/TypeClass.hs
- testsuite/tests/linear/should_fail/TypeClass.stderr
- testsuite/tests/linear/should_run/LinearGhci.stdout
- testsuite/tests/numeric/should_compile/T16402.stderr-ws-64
- testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr
- testsuite/tests/perf/compiler/all.T
- testsuite/tests/rep-poly/RepPolyCase1.stderr
- − testsuite/tests/rep-poly/RepPolyCase2.stderr
- testsuite/tests/rep-poly/RepPolyRule3.stderr
- testsuite/tests/rep-poly/RepPolyTuple4.stderr
- testsuite/tests/rep-poly/T13233.stderr
- − testsuite/tests/rep-poly/T17021.stderr
- testsuite/tests/rep-poly/T20363b.stderr
- − testsuite/tests/rep-poly/T21650_a.stderr
- − testsuite/tests/rep-poly/T21650_b.stderr
- + testsuite/tests/rep-poly/T26072.hs
- testsuite/tests/rep-poly/UnliftedNewtypesLevityBinder.stderr
- testsuite/tests/rep-poly/all.T
- testsuite/tests/typecheck/should_fail/T15883e.stderr
- testsuite/tests/typecheck/should_fail/T2414.stderr
- testsuite/tests/typecheck/should_fail/T2534.stderr
- testsuite/tests/typecheck/should_fail/T7264.stderr
- utils/haddock/hypsrc-test/ref/src/Classes.html
- utils/haddock/hypsrc-test/ref/src/Quasiquoter.html
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d43cc50de15e4111caa68d4da72baa…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d43cc50de15e4111caa68d4da72baa…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/io-manager-deadlock-detection] 2 commits: FIXUP: Make the IOManager API use CapIOManager rather than Capability
by Duncan Coutts (@dcoutts) 15 Nov '25
by Duncan Coutts (@dcoutts) 15 Nov '25
15 Nov '25
Duncan Coutts pushed to branch wip/io-manager-deadlock-detection at Glasgow Haskell Compiler / GHC
Commits:
f9da9451 by Duncan Coutts at 2025-11-15T12:30:48+00:00
FIXUP: Make the IOManager API use CapIOManager rather than Capability
whitespace
- - - - -
7d601300 by Duncan Coutts at 2025-11-15T12:31:17+00:00
FIXUP: Add a long Note [Deadlock detection]
note definition syntax now needs a ~~~~ line
- - - - -
2 changed files:
- rts/IOManager.c
- rts/Schedule.c
Changes:
=====================================
rts/IOManager.c
=====================================
@@ -322,7 +322,7 @@ char * showIOManager(void)
CapIOManager *allocCapabilityIOManager(Capability *cap)
{
CapIOManager *iomgr = stgMallocBytes(sizeof(CapIOManager),
- "allocCapabilityIOManager");
+ "allocCapabilityIOManager");
iomgr->cap = cap; /* link back */
return iomgr;
}
=====================================
rts/Schedule.c
=====================================
@@ -851,6 +851,7 @@ schedulePushWork(Capability *cap USED_IF_THREADS,
* ------------------------------------------------------------------------- */
/* Note [Deadlock detection]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~
For the purpose of this explanation we define:
* a /partial deadlock/ to be a set of threads that are deadlocked; and
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a85a430addce3ad87a6d9906409a5e…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a85a430addce3ad87a6d9906409a5e…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] 2 commits: JS: fix array index for registers
by Marge Bot (@marge-bot) 15 Nov '25
by Marge Bot (@marge-bot) 15 Nov '25
15 Nov '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
c9fa3449 by Sylvain Henry at 2025-11-15T05:15:26-05:00
JS: fix array index for registers
We used to store R32 in h$regs[-1]. While it's correct in JavaScript,
fix this to store R32 in h$regs[0] instead.
- - - - -
9e469909 by Sylvain Henry at 2025-11-15T05:15:26-05:00
JS: support more than 128 registers (#26558)
The JS backend only supported 128 registers (JS variables/array slots
used to pass function arguments). It failed in T26537 when 129
registers were required.
This commit adds support for more than 128 registers: it is now limited to
maxBound :: Int (compiler's Int). If we ever go above this threshold the
compiler now panics with a more descriptive message.
A few built-in JS functions were assuming 128 registers and have been
rewritten to use loops. Note that loops are only used for "high"
registers that are stored in an array: the 31 "low" registers are still
handled with JS global variables and with explicit switch-cases to
maintain good performance in the most common cases (i.e. few registers
used). Adjusting the number of low registers is now easy: just one
constant to adjust (GHC.StgToJS.Regs.lowRegsCount).
No new test added: T26537 is used as a regression test instead.
- - - - -
6 changed files:
- compiler/GHC/StgToJS/Apply.hs
- compiler/GHC/StgToJS/Expr.hs
- compiler/GHC/StgToJS/Regs.hs
- compiler/GHC/StgToJS/Rts/Rts.hs
- compiler/GHC/StgToJS/Rts/Types.hs
- testsuite/tests/codeGen/should_run/all.T
Changes:
=====================================
compiler/GHC/StgToJS/Apply.hs
=====================================
@@ -185,7 +185,7 @@ genApp ctx i args
as' <- concatMapM genArg args
ei <- varForEntryId i
let ra = mconcat . reverse $
- zipWith (\r a -> toJExpr r |= a) [R1 ..] as'
+ zipWith (\r a -> toJExpr r |= a) regsFromR1 as'
p <- pushLneFrame n ctx
a <- adjSp 1 -- for the header (which will only be written when the thread is suspended)
return (ra <> p <> a <> returnS ei, ExprCont)
@@ -464,42 +464,31 @@ specTag spec = Bits.shiftL (specVars spec) 8 Bits..|. specArgs spec
specTagExpr :: ApplySpec -> JStgExpr
specTagExpr = toJExpr . specTag
--- | Build arrays to quickly lookup apply functions
+-- | Build functions to quickly lookup apply functions
--
--- h$apply[r << 8 | n] = function application for r regs, n args
--- h$paps[r] = partial application for r registers (number of args is in the object)
+-- h$apply(r << 8 | n) = function application for r regs, n args
+-- h$paps(r) = partial application for r registers (number of args is in the object)
mkApplyArr :: JSM JStgStat
mkApplyArr =
- do mk_ap_gens <- jFor (|= zero_) (.<. Int 65536) preIncrS
- \j -> hdApply .! j |= hdApGen
- mk_pap_gens <- jFor (|= zero_) (.<. Int 128) preIncrS
- \j -> hdPaps .! j |= hdPapGen
+ do paps_fun <- jFunction (name hdPapsStr) \(MkSolo i) -> pure $ SwitchStat i (map case_pap specPap) (returnS hdPapGen)
+ apply_fun <- jFunction (name hdApplyStr) \(MkSolo i) -> pure $ SwitchStat i (mapMaybe' case_apply applySpec) (returnS hdApGen)
return $ mconcat
- [ name hdApplyStr ||= toJExpr (JList [])
- , name hdPapsStr ||= toJExpr (JList [])
- , ApplStat (hdInitStatic .^ "push")
- [ jLam' $
- mconcat
- [ mk_ap_gens
- , mk_pap_gens
- , mconcat (map assignSpec applySpec)
- , mconcat (map assignPap specPap)
- ]
- ]
+ [ paps_fun
+ , apply_fun
]
where
- assignSpec :: ApplySpec -> JStgStat
- assignSpec spec = case specConv spec of
+ case_apply :: ApplySpec -> Maybe (JStgExpr,JStgStat)
+ case_apply spec = case specConv spec of
-- both fast/slow (regs/stack) specialized apply functions have the same
-- tags. We store the stack ones in the array because they are used as
-- continuation stack frames.
- StackConv -> hdApply .! specTagExpr spec |= specApplyExpr spec
- RegsConv -> mempty
+ StackConv -> Just (specTagExpr spec, returnS (specApplyExpr spec))
+ RegsConv -> Nothing
hdPap_ = unpackFS hdPapStr_
- assignPap :: Int -> JStgStat
- assignPap p = hdPaps .! toJExpr p |= global (mkFastString (hdPap_ ++ show p))
+ case_pap :: Int -> (JStgExpr, JStgStat)
+ case_pap p = (toJExpr p, returnS $ global (mkFastString (hdPap_ ++ show p)))
-- | Push a continuation on the stack
--
@@ -619,7 +608,7 @@ genericStackApply cfg = closure info body
-- compute new tag with consumed register values and args removed
, newTag |= ((given_regs-needed_regs).<<.8) .|. (given_args - needed_args)
-- find application function for the remaining regs/args
- , newAp |= hdApply .! newTag
+ , newAp |= ApplExpr hdApply [newTag]
, traceRts cfg (jString "h$ap_gen: next: " + (newAp .^ "n"))
-- Drop used registers from the stack.
@@ -643,7 +632,7 @@ genericStackApply cfg = closure info body
-----------------------------
[ traceRts cfg (jString "h$ap_gen: undersat")
-- find PAP entry function corresponding to given_regs count
- , p |= hdPaps .! given_regs
+ , p |= ApplExpr hdPaps [given_regs]
-- build PAP payload: R1 + tag + given register values
, newTag |= ((needed_regs-given_regs) .<<. 8) .|. (needed_args-given_args)
@@ -716,7 +705,7 @@ genericFastApply s =
do push_all_regs <- pushAllRegs tag
return $ mconcat $
[ push_all_regs
- , ap |= hdApply .! tag
+ , ap |= ApplExpr hdApply [tag]
, ifS (ap .===. hdApGen)
((sp |= sp + 2) <> (stack .! (sp-1) |= tag))
(sp |= sp + 1)
@@ -750,7 +739,7 @@ genericFastApply s =
, traceRts s (jString "h$ap_gen_fast: oversat " + sp)
, push_args
, newTag |= ((myRegs-( arity.>>.8)).<<.8).|.myAr-ar
- , newAp |= hdApply .! newTag
+ , newAp |= ApplExpr hdApply [newTag]
, ifS (newAp .===. hdApGen)
((sp |= sp + 2) <> (stack .! (sp - 1) |= newTag))
(sp |= sp + 1)
@@ -761,7 +750,7 @@ genericFastApply s =
-- else
[traceRts s (jString "h$ap_gen_fast: undersat: " + myRegs + jString " " + tag)
, jwhenS (tag .!=. 0) $ mconcat
- [ p |= hdPaps .! myRegs
+ [ p |= ApplExpr hdPaps [myRegs]
, dat |= toJExpr [r1, ((arity .>>. 8)-myRegs)*256+ar-myAr]
, get_regs
, r1 |= initClosure s p dat jCurrentCCS
@@ -773,14 +762,24 @@ genericFastApply s =
pushAllRegs :: JStgExpr -> JSM JStgStat
pushAllRegs tag =
jVar \regs ->
- return $ mconcat $
- [ regs |= tag .>>. 8
- , sp |= sp + regs
- , SwitchStat regs (map pushReg [65,64..2]) mempty
- ]
- where
- pushReg :: Int -> (JStgExpr, JStgStat)
- pushReg r = (toJExpr (r-1), stack .! (sp - toJExpr (r - 2)) |= jsReg r)
+ let max_low_reg = regNumber maxLowReg
+ low_regs = [max_low_reg, max_low_reg-1..2] -- R1 isn't used for arguments
+ pushReg :: Int -> (JStgExpr, JStgStat)
+ pushReg r = (toJExpr r, stack .! (sp - toJExpr (r - 2)) |= jsReg r)
+ in return $ mconcat $
+ [ regs |= tag .>>. 8
+ , sp |= sp + regs
+ -- increment the number of regs by 1, so that it matches register
+ -- numbers (R1 is not used for args)
+ , postIncrS regs
+ -- copy high registers with a loop
+ , WhileStat False (regs .>. toJExpr max_low_reg) $ mconcat
+ -- rN stored in stack[sp - N - 2] so that r2 is stored in stack[sp], etc.
+ [ stack .! (sp - regs - 2) |= highReg_expr regs
+ , postDecrS regs
+ ]
+ , SwitchStat regs (map pushReg low_regs) mempty
+ ]
pushArgs :: JStgExpr -> JStgExpr -> JSM JStgStat
pushArgs start end =
@@ -906,7 +905,7 @@ stackApply s fun_name nargs nvars =
[ rs |= (arity .>>. 8)
, loadRegs rs
, sp |= sp - rs
- , newAp |= (hdApply .! ((toJExpr nargs-arity0).|.((toJExpr nvars-rs).<<.8)))
+ , newAp |= ApplExpr hdApply [(toJExpr nargs-arity0).|.((toJExpr nvars-rs).<<.8)]
, stack .! sp |= newAp
, profStat s pushRestoreCCS
, traceRts s (toJExpr (fun_name <> ": new stack frame: ") + (newAp .^ "n"))
@@ -989,7 +988,7 @@ fastApply s fun_name nargs nvars = if nargs == 0 && nvars == 0
+ rsRemain)
, saveRegs rs
, sp |= sp + rsRemain + 1
- , stack .! sp |= hdApply .! ((rsRemain.<<.8).|. (toJExpr nargs - mask8 arity))
+ , stack .! sp |= ApplExpr hdApply [(rsRemain.<<.8).|. (toJExpr nargs - mask8 arity)]
, profStat s pushRestoreCCS
, returnS c
]
@@ -1238,14 +1237,30 @@ pap s r = closure (ClosureInfo
, profStat s (enterCostCentreFun currentCCS)
, extra |= (funOrPapArity c (Just f) .>>. 8) - toJExpr r
, traceRts s (toJExpr (funcName <> ": pap extra args moving: ") + extra)
- , moveBy extra
+ , case r of
+ 0 -> mempty -- in pap_0 we don't shift any register
+ _ -> moveBy extra
, loadOwnArgs d
, r1 |= c
, returnS f
]
- moveBy extra = SwitchStat extra
- (reverse $ map moveCase [1..maxReg-r-1]) mempty
- moveCase m = (toJExpr m, jsReg (m+r+1) |= jsReg (m+1))
+ moveBy extra =
+ let max_low_reg = regNumber maxLowReg
+ low_regs = [max_low_reg, max_low_reg-1..2] -- R1 isn't used for arguments
+ move_case m = (toJExpr m, jsReg (m+r) |= jsReg m)
+ in mconcat
+ [ -- increment the number of args by 1, so that it matches register
+ -- numbers (R1 is not used for args)
+ postIncrS extra
+ -- copy high registers with a loop
+ , WhileStat False (extra .>. toJExpr max_low_reg) $ mconcat
+ [ highReg_expr (extra + toJExpr r) |= highReg_expr extra
+ , postDecrS extra
+ ]
+ -- then copy low registers with a case
+ , SwitchStat extra (map move_case low_regs) mempty
+ ]
+
loadOwnArgs d = mconcat $ map (\r ->
jsReg (r+1) |= dField d (r+2)) [1..r]
dField d n = SelExpr d (name . mkFastString $ ('d':show (n-1)))
@@ -1274,7 +1289,9 @@ papGen cfg =
(jString "h$pap_gen: expected function or pap")
, profStat cfg (enterCostCentreFun currentCCS)
, traceRts cfg (jString "h$pap_gen: generic pap extra args moving: " + or)
+ -- shift newly applied arguments into appropriate registers
, appS hdMoveRegs2 [or, r]
+ -- load stored arguments into lowest argument registers (i.e. starting from R2)
, loadOwnArgs d r
, r1 |= c
, returnS f
@@ -1285,9 +1302,22 @@ papGen cfg =
funcIdent = name funcName
funcName = hdPapGenStr
loadOwnArgs d r =
- let prop n = d .^ ("d" <> mkFastString (show $ n+1))
- loadOwnArg n = (toJExpr n, jsReg (n+1) |= prop n)
- in SwitchStat r (map loadOwnArg [127,126..1]) mempty
+ let prop n = d .^ (mkFastString ("d" ++ show n))
+ loadOwnArg n = (toJExpr n, jsReg n |= prop n)
+ max_low_reg = regNumber maxLowReg
+ low_regs = [max_low_reg, max_low_reg-1..2] -- R1 isn't used for arguments
+ in mconcat
+ [ -- increment the number of args by 1, so that it matches register
+ -- numbers (R1 is not used for args) and PAP fields (starting from d2)
+ postIncrS r
+ -- copy high registers with a loop
+ , WhileStat False (r .>. toJExpr max_low_reg) $ mconcat
+ [ highReg_expr r |= (d .! (jString (fsLit "d") + r))
+ , postDecrS r
+ ]
+ -- then copy low registers with a case.
+ , SwitchStat r (map loadOwnArg low_regs) mempty
+ ]
-- general utilities
-- move the first n registers, starting at R2, m places up (do not use with negative m)
@@ -1301,7 +1331,7 @@ moveRegs2 = jFunction (name hdMoveRegs2) moveSwitch
switchCase n m = (toJExpr $
(n `Bits.shiftL` 8) Bits..|. m
, mconcat (map (`moveRegFast` m) [n+1,n..2])
- <> BreakStat Nothing {-[j| break; |]-})
+ <> BreakStat Nothing)
moveRegFast n m = jsReg (n+m) |= jsReg n
-- fallback
defaultCase n m =
=====================================
compiler/GHC/StgToJS/Expr.hs
=====================================
@@ -312,7 +312,7 @@ genBody ctx startReg args e typ = do
-- load arguments into local variables
la <- do
args' <- concatMapM genIdArgI args
- return (declAssignAll args' (fmap toJExpr [startReg..]))
+ return (declAssignAll args' (jsRegsFrom startReg))
-- assert that arguments have valid runtime reps
lav <- verifyRuntimeReps args
@@ -665,7 +665,7 @@ genCase ctx bnd e at alts l
| otherwise = do
rj <- genRet ctx bnd at alts l
let ctx' = ctxSetTop bnd
- $ ctxSetTarget (assocIdExprs bnd (map toJExpr [R1 ..]))
+ $ ctxSetTarget (assocIdExprs bnd jsRegsFromR1)
$ ctx
(ej, _r) <- genExpr ctx' e
return (rj <> ej, ExprCont)
@@ -730,7 +730,7 @@ genRet ctx e at as l = freshIdent >>= f
fun free = resetSlots $ do
decs <- declVarsForId e
- load <- flip assignAll (map toJExpr [R1 ..]) . map toJExpr <$> identsForId e
+ load <- flip assignAll jsRegsFromR1 . map toJExpr <$> identsForId e
loadv <- verifyRuntimeReps [e]
ras <- loadRetArgs free
rasv <- verifyRuntimeReps (map (\(x,_,_)->x) free)
=====================================
compiler/GHC/StgToJS/Regs.hs
=====================================
@@ -1,4 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE PatternSynonyms #-}
module GHC.StgToJS.Regs
( StgReg (..)
@@ -6,17 +7,25 @@ module GHC.StgToJS.Regs
, sp
, stack
, r1, r2, r3, r4
+ , pattern R1, pattern R2, pattern R3, pattern R4
, regsFromR1
, regsFromR2
+ , regsFromTo
+ , jsRegsFrom
, jsRegsFromR1
, jsRegsFromR2
, StgRet (..)
- , jsRegToInt
- , intToJSReg
+ , regNumber
, jsReg
+ , highReg
+ , highReg_expr
, maxReg
+ , maxLowReg
, minReg
+ , minHighReg
, lowRegs
+ , lowRegsCount
+ , lowRegsIdents
, retRegs
, register
, foreignRegister
@@ -32,6 +41,7 @@ import GHC.JS.Make
import GHC.StgToJS.Symbols
import GHC.Data.FastString
+import GHC.Utils.Panic.Plain
import Data.Array
import qualified Data.ByteString.Char8 as BSC
@@ -39,26 +49,15 @@ import Data.Char
import Data.Semigroup ((<>))
-- | General purpose "registers"
---
--- The JS backend arbitrarily supports 128 registers
-data StgReg
- = R1 | R2 | R3 | R4 | R5 | R6 | R7 | R8
- | R9 | R10 | R11 | R12 | R13 | R14 | R15 | R16
- | R17 | R18 | R19 | R20 | R21 | R22 | R23 | R24
- | R25 | R26 | R27 | R28 | R29 | R30 | R31 | R32
- | R33 | R34 | R35 | R36 | R37 | R38 | R39 | R40
- | R41 | R42 | R43 | R44 | R45 | R46 | R47 | R48
- | R49 | R50 | R51 | R52 | R53 | R54 | R55 | R56
- | R57 | R58 | R59 | R60 | R61 | R62 | R63 | R64
- | R65 | R66 | R67 | R68 | R69 | R70 | R71 | R72
- | R73 | R74 | R75 | R76 | R77 | R78 | R79 | R80
- | R81 | R82 | R83 | R84 | R85 | R86 | R87 | R88
- | R89 | R90 | R91 | R92 | R93 | R94 | R95 | R96
- | R97 | R98 | R99 | R100 | R101 | R102 | R103 | R104
- | R105 | R106 | R107 | R108 | R109 | R110 | R111 | R112
- | R113 | R114 | R115 | R116 | R117 | R118 | R119 | R120
- | R121 | R122 | R123 | R124 | R125 | R126 | R127 | R128
- deriving (Eq, Ord, Show, Enum, Bounded, Ix)
+newtype StgReg
+ = StgReg Int
+ deriving (Eq,Ord,Ix)
+
+pattern R1, R2, R3, R4 :: StgReg
+pattern R1 = StgReg 0
+pattern R2 = StgReg 1
+pattern R3 = StgReg 2
+pattern R4 = StgReg 3
-- | Stack registers
data Special
@@ -78,7 +77,7 @@ instance ToJExpr Special where
toJExpr Sp = hdStackPtr
instance ToJExpr StgReg where
- toJExpr r = registers ! r
+ toJExpr r = register r
instance ToJExpr StgRet where
toJExpr r = rets ! r
@@ -99,25 +98,42 @@ r2 = toJExpr R2
r3 = toJExpr R3
r4 = toJExpr R4
+-- | 1-indexed register number (R1 has index 1)
+regNumber :: StgReg -> Int
+regNumber (StgReg r) = r+1
-jsRegToInt :: StgReg -> Int
-jsRegToInt = (+1) . fromEnum
+-- | StgReg from 1-indexed number
+regFromNumber :: Int -> StgReg
+regFromNumber r = assert (r >= 1) $ StgReg (r-1)
-intToJSReg :: Int -> StgReg
-intToJSReg r = toEnum (r - 1)
+regsFromTo :: StgReg -> StgReg -> [StgReg]
+regsFromTo (StgReg x) (StgReg y) = map StgReg [x .. y]
+-- | Register expression from its 1-indexed index
jsReg :: Int -> JStgExpr
-jsReg r = toJExpr (intToJSReg r)
+jsReg r = toJExpr (regFromNumber r)
+
+minReg :: StgReg
+minReg = R1
-maxReg :: Int
-maxReg = jsRegToInt maxBound
+maxReg :: StgReg
+maxReg = regFromNumber maxBound
-minReg :: Int
-minReg = jsRegToInt minBound
+lowRegsCount :: Int
+lowRegsCount = 31
+
+maxLowReg :: StgReg
+maxLowReg = regFromNumber lowRegsCount
+
+-- | First register stored in h$regs array instead of having its own top-level
+-- variable
+minHighReg :: StgReg
+minHighReg = case maxLowReg of
+ StgReg r -> StgReg (r+1)
-- | List of registers, starting from R1
regsFromR1 :: [StgReg]
-regsFromR1 = enumFrom R1
+regsFromR1 = regsFromTo R1 maxReg ++ repeat (panic "StgToJS: code requires too many registers")
-- | List of registers, starting from R2
regsFromR2 :: [StgReg]
@@ -131,35 +147,59 @@ jsRegsFromR1 = fmap toJExpr regsFromR1
jsRegsFromR2 :: [JStgExpr]
jsRegsFromR2 = tail jsRegsFromR1
+-- | List of registers, starting from given reg as JExpr
+jsRegsFrom :: StgReg -> [JStgExpr]
+jsRegsFrom (StgReg n) = drop n jsRegsFromR1
+
+-- | High register
+highReg :: Int -> JStgExpr
+highReg r = assert (r >= regNumber minHighReg) $ IdxExpr hdRegs (toJExpr (r - regNumber minHighReg))
+
+-- | High register indexing with a JS expression
+highReg_expr :: JStgExpr -> JStgExpr
+highReg_expr r = IdxExpr hdRegs (r - toJExpr (regNumber minHighReg))
+
+
---------------------------------------------------
-- caches
---------------------------------------------------
-lowRegs :: [Ident]
-lowRegs = map reg_to_ident [R1 .. R31]
- where reg_to_ident = name . mkFastString . (unpackFS hdStr ++) . map toLower . show
+lowRegs :: [StgReg]
+lowRegs = regsFromTo minReg maxLowReg
+
+lowRegsIdents :: [Ident]
+lowRegsIdents = map reg_to_ident lowRegs
+ where
+ -- low regs are named h$r1, h$r2, etc.
+ reg_to_ident r = name (mkFastString (unpackFS hdStr ++ "r" ++ show (regNumber r)))
retRegs :: [Ident]
retRegs = [name . mkFastStringByteString
$ hdB <> BSC.pack (map toLower $ show n) | n <- enumFrom Ret1]
--- cache JExpr representing StgReg
-registers :: Array StgReg JStgExpr
-registers = listArray (minBound, maxBound) (map (global . identFS) lowRegs ++ map regN [R32 .. R128])
- where
- regN :: StgReg -> JStgExpr
- regN r = IdxExpr hdRegs (toJExpr (fromEnum r - 32))
-
-- cache JExpr representing StgRet
rets :: Array StgRet JStgExpr
rets = listArray (minBound, maxBound) (map retN (enumFrom Ret1))
where
retN = global . mkFastString . (unpackFS hdStr ++) . map toLower . show
--- | Given a register, return the JS syntax object representing that register
-register :: StgReg -> JStgExpr
-register i = registers ! i
-
-- | Given a register, return the JS syntax object representing that register
foreignRegister :: StgRet -> JStgExpr
foreignRegister i = rets ! i
+
+-- | Given a register, return the JS syntax object representing that register
+register :: StgReg -> JStgExpr
+register i
+ | i <= maxCachedReg = register_cache ! i -- Expressions of common registers are cached.
+ | otherwise = make_high_reg i -- Expression of higher registers are made on the fly
+
+maxCachedReg :: StgReg
+maxCachedReg = regFromNumber 128
+
+-- cache JExpr representing StgReg
+register_cache :: Array StgReg JStgExpr
+register_cache = listArray (minReg, maxCachedReg) (map (global . identFS) lowRegsIdents ++ map make_high_reg (regsFromTo minHighReg maxCachedReg))
+
+-- | Make h$regs[XXX] expression for the register
+make_high_reg :: StgReg -> JStgExpr
+make_high_reg r = highReg (regNumber r)
=====================================
compiler/GHC/StgToJS/Rts/Rts.hs
=====================================
@@ -54,7 +54,12 @@ import qualified Data.Bits as Bits
-- | The garbageCollector resets registers and result variables.
garbageCollector :: JSM JStgStat
garbageCollector = jBlock
- [ jFunction' hdResetRegisters (return $ mconcat $ map resetRegister [minBound..maxBound])
+ [ jFunction' hdResetRegisters $ return $ mconcat
+ [ -- reset low registers explicitly
+ mconcat (map resetRegister lowRegs)
+ -- reset the whole h$regs array with h$regs.fill(null)
+ , toStat $ ApplExpr (hdRegs .^ "fill") [null_]
+ ]
, jFunction' hdResetResultVars (return $ mconcat $ map resetResultVar [minBound..maxBound])
]
@@ -249,7 +254,7 @@ declRegs = do
loaders <- loadRegs
return $
mconcat [ hdRegsStr ||= toJExpr (JList [])
- , mconcat (map declReg lowRegs)
+ , mconcat (map declReg lowRegsIdents)
, getters_setters
, loaders
]
@@ -259,15 +264,15 @@ declRegs = do
-- | JS payload to define getters and setters on the registers.
regGettersSetters :: JSM JStgStat
regGettersSetters =
- do setters <- jFunction (name hdGetRegStr) (\(MkSolo n) -> return $ SwitchStat n getRegCases mempty)
- getters <- jFunction (name hdSetRegStr) (\(n,v) -> return $ SwitchStat n (setRegCases v) mempty)
+ do getters <- jFunction (name hdGetRegStr) (\(MkSolo n) -> return $ SwitchStat n getRegCases (defaultGetRegCase n))
+ setters <- jFunction (name hdSetRegStr) (\(n,v) -> return $ SwitchStat n (setRegCases v) (defaultSetRegCase n v))
return $ setters <> getters
where
- getRegCases =
- map (\r -> (toJExpr (jsRegToInt r) , returnS (toJExpr r))) regsFromR1
- setRegCases :: JStgExpr -> [(JStgExpr,JStgStat)]
- setRegCases v =
- map (\r -> (toJExpr (jsRegToInt r), (toJExpr r |= toJExpr v) <> returnS undefined_)) regsFromR1
+ getRegCases = map (\r -> (toJExpr (regNumber r) , returnS (toJExpr r))) lowRegs
+ defaultGetRegCase n = returnS (highReg_expr n)
+
+ setRegCases v = map (\r -> (toJExpr (regNumber r), (toJExpr r |= v) <> BreakStat Nothing)) lowRegs
+ defaultSetRegCase n v = highReg_expr n |= v
-- | JS payload that defines the functions to load each register
loadRegs :: JSM JStgStat
=====================================
compiler/GHC/StgToJS/Rts/Types.hs
=====================================
@@ -69,12 +69,3 @@ stackFrameSize tgt f =
(tgt |= mask8 tag + 1) -- else set to mask'd tag + 1
]
))
-
- --------------------------------------------------------------------------------
--- Register utilities
---------------------------------------------------------------------------------
-
--- | Perform the computation 'f', on the range of registers bounded by 'start'
--- and 'end'.
-withRegs :: StgReg -> StgReg -> (StgReg -> JStgStat) -> JStgStat
-withRegs start end f = mconcat $ fmap f [start..end]
=====================================
testsuite/tests/codeGen/should_run/all.T
=====================================
@@ -256,4 +256,4 @@ test('T24893', normal, compile_and_run, ['-O'])
test('CCallConv', [req_c], compile_and_run, ['CCallConv_c.c'])
test('T25364', normal, compile_and_run, [''])
test('T26061', normal, compile_and_run, [''])
-test('T26537', js_broken(26558), compile_and_run, ['-O2 -fregs-graph'])
+test('T26537', normal, compile_and_run, ['-O2 -fregs-graph'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c0a1e5748d90c1cbd2e6a90ccbe7d9…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c0a1e5748d90c1cbd2e6a90ccbe7d9…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
15 Nov '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
c0a1e574 by Georgios Karachalias at 2025-11-15T05:14:31-05:00
Report all missing modules with -M
We now report all missing modules at once in GHC.Driver.Makefile.processDeps,
as opposed to only reporting a single missing module. Fixes #26551.
- - - - -
5 changed files:
- compiler/GHC/Driver/MakeFile.hs
- testsuite/tests/driver/Makefile
- + testsuite/tests/driver/T26551.hs
- + testsuite/tests/driver/T26551.stderr
- testsuite/tests/driver/all.T
Changes:
=====================================
compiler/GHC/Driver/MakeFile.hs
=====================================
@@ -55,6 +55,7 @@ import Data.IORef
import qualified Data.Set as Set
import GHC.Iface.Errors.Types
import Data.Either
+import GHC.Data.Bag (listToBag)
-----------------------------------------------------------------
--
@@ -237,19 +238,6 @@ processDeps dflags hsc_env excl_mods root hdl (AcyclicSCC (ModuleNode _ (ModuleN
obj_file = msObjFilePath node
obj_files = insertSuffixes obj_file extra_suffixes
- do_imp loc is_boot pkg_qual imp_mod
- = do { mb_hi <- findDependency hsc_env loc pkg_qual imp_mod
- is_boot include_pkg_deps
- ; case mb_hi of {
- Nothing -> return () ;
- Just hi_file -> do
- { let hi_files = insertSuffixes hi_file extra_suffixes
- write_dep (obj,hi) = writeDependency root hdl [obj] hi
-
- -- Add one dependency for each suffix;
- -- e.g. A.o : B.hi
- -- A.x_o : B.x_hi
- ; mapM_ write_dep (obj_files `zip` hi_files) }}}
-- Emit std dependency of the object(s) on the source file
@@ -280,15 +268,33 @@ processDeps dflags hsc_env excl_mods root hdl (AcyclicSCC (ModuleNode _ (ModuleN
-- Emit a dependency for each import
- ; let do_imps is_boot idecls = sequence_
- [ do_imp loc is_boot mb_pkg mod
+ ; let find_dep loc is_boot pkg_qual imp_mod = findDependency hsc_env loc pkg_qual imp_mod is_boot include_pkg_deps
+
+ find_deps is_boot idecls = sequence
+ [ find_dep loc is_boot mb_pkg mod
| (_lvl, mb_pkg, L loc mod) <- idecls,
mod `notElem` excl_mods ]
- ; do_imps IsBoot (map ((,,) NormalLevel NoPkgQual) (ms_srcimps node))
- ; do_imps NotBoot (ms_imps node)
- }
+ do_imp hi_file = do
+ let hi_files = insertSuffixes hi_file extra_suffixes
+ write_dep (obj,hi) = writeDependency root hdl [obj] hi
+
+ -- Add one dependency for each suffix;
+ -- e.g. A.o : B.hi
+ -- A.x_o : B.x_hi
+ mapM_ write_dep (obj_files `zip` hi_files)
+ ; (missing_boot_dep_errs, boot_deps) <- partitionEithers <$> find_deps IsBoot (map ((,,) NormalLevel NoPkgQual) (ms_srcimps node))
+ ; (missing_not_boot_dep_errs, not_boot_deps) <- partitionEithers <$> find_deps NotBoot (ms_imps node)
+
+ ; let all_missing_errors = missing_boot_dep_errs ++ missing_not_boot_dep_errs
+
+ ; if null all_missing_errors
+ then mapM_ (mapM_ do_imp) (boot_deps ++ not_boot_deps)
+ else do
+ let sec = initSourceErrorContext (hsc_dflags hsc_env)
+ throwErrors sec (mkMessages (listToBag all_missing_errors))
+ }
findDependency :: HscEnv
-> SrcSpan
@@ -296,7 +302,7 @@ findDependency :: HscEnv
-> ModuleName -- Imported module
-> IsBootInterface -- Source import
-> Bool -- Record dependency on package modules
- -> IO (Maybe FilePath) -- Interface file
+ -> IO (Either (MsgEnvelope GhcMessage) (Maybe FilePath)) -- Interface file
findDependency hsc_env srcloc pkg imp is_boot include_pkg_deps = do
-- Find the module; this will be fast because
-- we've done it once during downsweep
@@ -305,16 +311,15 @@ findDependency hsc_env srcloc pkg imp is_boot include_pkg_deps = do
Found loc _
-- Home package: just depend on the .hi or hi-boot file
| isJust (ml_hs_file loc) || include_pkg_deps
- -> return (Just (ml_hi_file loc))
+ -> return (Right (Just (ml_hi_file loc)))
-- Not in this package: we don't need a dependency
| otherwise
- -> return Nothing
+ -> return (Right Nothing)
fail ->
- let sec = initSourceErrorContext (hsc_dflags hsc_env)
- in
- throwOneError sec $
+ return $
+ Left $
mkPlainErrorMsgEnvelope srcloc $
GhcDriverMessage $ DriverInterfaceError $
(Can'tFindInterface (cannotFindModule hsc_env imp fail) (LookingForModule imp is_boot))
=====================================
testsuite/tests/driver/Makefile
=====================================
@@ -415,6 +415,10 @@ test200:
"$(TEST_HC)" $(TEST_HC_OPTS) -M -dep-suffix "" -dep-makefile $(DEPFILE200) D200.hs B200/C.hs A200.hs
test -f $(DEPFILE200)
+# Test that we produce "could not find module" errors for _all_ missing imports.
+T26551:
+ "$(TEST_HC)" $(TEST_HC_OPTS) -M T26551.hs || true
+
# -----------------------------------------------------------------------------
T2566::
=====================================
testsuite/tests/driver/T26551.hs
=====================================
@@ -0,0 +1,5 @@
+module Main where
+
+import Foo
+import Bar
+import Baz
=====================================
testsuite/tests/driver/T26551.stderr
=====================================
@@ -0,0 +1,11 @@
+T26551.hs:3:8: [GHC-87110]
+ Could not find module ‘Foo’.
+ Use -v to see a list of the files searched for.
+
+T26551.hs:4:8: [GHC-87110]
+ Could not find module ‘Bar’.
+ Use -v to see a list of the files searched for.
+
+T26551.hs:5:8: [GHC-87110]
+ Could not find module ‘Baz’.
+ Use -v to see a list of the files searched for.
=====================================
testsuite/tests/driver/all.T
=====================================
@@ -332,3 +332,4 @@ test('t25150', [extra_files(["t25150"])], multimod_compile, ['Main.hs', '-v0 -wo
test('T25382', normal, makefile_test, [])
test('T26018', req_c, makefile_test, [])
test('T24120', normal, compile, ['-Wunused-packages -hide-all-packages -package base -package system-cxx-std-lib'])
+test('T26551', [extra_files(['T26551.hs'])], makefile_test, [])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c0a1e5748d90c1cbd2e6a90ccbe7d96…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c0a1e5748d90c1cbd2e6a90ccbe7d96…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
15 Nov '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
a00840ea by Simon Peyton Jones at 2025-11-14T15:23:56+00:00
Make TYPE and CONSTRAINT apart again
This patch finally fixes #24279.
* The story started with #11715
* Then #21623 articulated a plan, which made Type and Constraint
not-apart; a horrible hack but it worked. The main patch was
commit 778c6adca2c995cd8a1b84394d4d5ca26b915dac
Author: Simon Peyton Jones <simonpj(a)microsoft.com>
Date: Wed Nov 9 10:33:22 2022 +0000
Type vs Constraint: finally nailed
* #24279 reported a bug in the above big commit; this small patch fixes it
commit af6932d6c068361c6ae300d52e72fbe13f8e1f18
Author: Simon Peyton Jones <simon.peytonjones(a)gmail.com>
Date: Mon Jan 8 10:49:49 2024 +0000
Make TYPE and CONSTRAINT not-apart
Issue #24279 showed up a bug in the logic in GHC.Core.Unify.unify_ty
which is supposed to make TYPE and CONSTRAINT be not-apart.
* Then !10479 implemented "unary classes".
* That change in turn allows us to make Type and Constraint apart again,
cleaning up the compiler and allowing a little bit more expressiveness.
It fixes the original hope in #24279, namely that `Type` and `Constraint`
should be distinct throughout.
- - - - -
14 changed files:
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/RoughMap.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Unify.hs
- compiler/GHC/Tc/Instance/Class.hs
- docs/users_guide/9.16.1-notes.rst
- testsuite/tests/indexed-types/should_fail/T21092.hs
- − testsuite/tests/indexed-types/should_fail/T21092.stderr
- testsuite/tests/indexed-types/should_fail/all.T
- testsuite/tests/typecheck/should_fail/T24279.hs
- − testsuite/tests/typecheck/should_fail/T24279.stderr
- testsuite/tests/typecheck/should_fail/all.T
Changes:
=====================================
compiler/GHC/Builtin/Types/Prim.hs
=====================================
@@ -752,8 +752,9 @@ Specifically (a ~# b) :: CONSTRAINT (TupleRep [])
Wrinkles
-(W1) Type and Constraint are considered distinct throughout GHC. But they
- are not /apart/: see Note [Type and Constraint are not apart]
+(W1) Type and Constraint are considered distinct throughout GHC.
+ That wasn't always the case:
+ see Historical Note [Type and Constraint are not apart]
(W2) We need two absent-error Ids, aBSENT_ERROR_ID for types of kind Type, and
aBSENT_CONSTRAINT_ERROR_ID for types of kind Constraint.
@@ -768,8 +769,24 @@ Wrinkles
of type TYPE rr. See (CPR2) in Note [Which types are unboxed?] in
GHC.Core.Opt.WorkWrap.Utils.
-Note [Type and Constraint are not apart]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+-------------------------------------------------------------
+Historical Note [Type and Constraint are not apart]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Nov 2025:
+ In the past, Type and Constraint were carefully coonsiderd to be
+ not /apart/. But the necessity for that vanished with unary classes
+ (see Note [Unary class magic]), done in
+
+ commit 9bd7fcc518111a1549c98720c222cdbabd32ed46
+ Author: Simon Peyton Jones <simon.peytonjones(a)gmail.com>
+ Date: Tue Apr 15 17:43:46 2025 +0100
+ Implement unary classes
+
+ So now Type and Constraint are simply distinct type constructors, just as
+ much as Int and Bool.
+
+ The rest of this Note is preserved for historical interest.
+
Type and Constraint are not equal (eqType) but they are not /apart/
either. Reason (c.f. #7451):
@@ -841,6 +858,9 @@ Wrinkles
So in GHC.Tc.Instance.Class.matchTypeable, Type and Constraint are
treated as separate TyCons; i.e. given no special treatment.
+End of Historical Note
+-------------------------------------------------------------
+
Note [RuntimeRep polymorphism]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Generally speaking, you can't be polymorphic in `RuntimeRep`. E.g
=====================================
compiler/GHC/Core/Coercion.hs
=====================================
@@ -641,11 +641,6 @@ eqTyConRole tc
-- | Given a coercion `co :: (t1 :: TYPE r1) ~ (t2 :: TYPE r2)`
-- produce a coercion `rep_co :: r1 ~ r2`
--- But actually it is possible that
--- co :: (t1 :: CONSTRAINT r1) ~ (t2 :: CONSTRAINT r2)
--- or co :: (t1 :: TYPE r1) ~ (t2 :: CONSTRAINT r2)
--- or co :: (t1 :: CONSTRAINT r1) ~ (t2 :: TYPE r2)
--- See Note [mkRuntimeRepCo]
mkRuntimeRepCo :: HasDebugCallStack => Coercion -> Coercion
mkRuntimeRepCo co
= assert (isTYPEorCONSTRAINT k1 && isTYPEorCONSTRAINT k2) $
@@ -654,26 +649,6 @@ mkRuntimeRepCo co
kind_co = mkKindCo co -- kind_co :: TYPE r1 ~ TYPE r2
Pair k1 k2 = coercionKind kind_co
-{- Note [mkRuntimeRepCo]
-~~~~~~~~~~~~~~~~~~~~~~~~
-Given
- class C a where { op :: Maybe a }
-we will get an axiom
- axC a :: (C a :: CONSTRAINT r1) ~ (Maybe a :: TYPE r2)
-(See Note [Type and Constraint are not apart] in GHC.Builtin.Types.Prim.)
-
-Then we may call mkRuntimeRepCo on (axC ty), and that will return
- mkSelCo (SelTyCon 0 Nominal) (Kind (axC ty)) :: r1 ~ r2
-
-So mkSelCo needs to be happy with decomposing a coercion of kind
- CONSTRAINT r1 ~ TYPE r2
-
-Hence the use of `tyConIsTYPEorCONSTRAINT` in the assertion `good_call`
-in `mkSelCo`. See #23018 for a concrete example. (In this context it's
-important that TYPE and CONSTRAINT have the same arity and kind, not
-merely that they are not-apart; otherwise SelCo would not make sense.)
--}
-
isReflCoVar_maybe :: Var -> Maybe Coercion
-- If cv :: t~t then isReflCoVar_maybe cv = Just (Refl t)
-- Works on all kinds of Vars, not just CoVars
@@ -1305,8 +1280,7 @@ mkSelCo_maybe cs co
, Just (tc2, tys2) <- splitTyConApp_maybe ty2
, let { len1 = length tys1
; len2 = length tys2 }
- = (tc1 == tc2 || (tyConIsTYPEorCONSTRAINT tc1 && tyConIsTYPEorCONSTRAINT tc2))
- -- tyConIsTYPEorCONSTRAINT: see Note [mkRuntimeRepCo]
+ = tc1 == tc2
&& len1 == len2
&& n < len1
&& r == tyConRole (coercionRole co) tc1 n
=====================================
compiler/GHC/Core/Lint.hs
=====================================
@@ -2891,13 +2891,9 @@ lint_branch ax_tc (CoAxBranch { cab_tvs = tvs, cab_cvs = cvs
hang (text "Inhomogeneous axiom")
2 (text "lhs:" <+> ppr lhs <+> dcolon <+> ppr lhs_kind $$
text "rhs:" <+> ppr rhs <+> dcolon <+> ppr rhs_kind) }
- -- Type and Constraint are not Apart, so this test allows
- -- the newtype axiom for a single-method class. Indeed the
- -- whole reason Type and Constraint are not Apart is to allow
- -- such axioms!
--- these checks do not apply to newtype axioms
lint_family_branch :: TyCon -> CoAxBranch -> LintM ()
+-- These checks do not apply to newtype axioms
lint_family_branch fam_tc br@(CoAxBranch { cab_tvs = tvs
, cab_eta_tvs = eta_tvs
, cab_cvs = cvs
=====================================
compiler/GHC/Core/RoughMap.hs
=====================================
@@ -36,7 +36,6 @@ import GHC.Core.Type
import GHC.Utils.Outputable
import GHC.Types.Name
import GHC.Types.Name.Env
-import GHC.Builtin.Types.Prim( cONSTRAINTTyConName, tYPETyConName )
import Control.Monad (join)
import Data.Data (Data)
@@ -347,16 +346,7 @@ typeToRoughMatchTc ty
roughMatchTyConName :: TyCon -> Name
roughMatchTyConName tc
- | tc_name == cONSTRAINTTyConName
- = tYPETyConName -- TYPE and CONSTRAINT are not apart, so they must use
- -- the same rough-map key. We arbitrarily use TYPE.
- -- See Note [Type and Constraint are not apart]
- -- wrinkle (W1) in GHC.Builtin.Types.Prim
- | otherwise
- = assertPpr (isGenerativeTyCon tc Nominal) (ppr tc) tc_name
- where
- tc_name = tyConName tc
-
+ = assertPpr (isGenerativeTyCon tc Nominal) (ppr tc) (tyConName tc)
-- | Trie of @[RoughMatchTc]@
--
=====================================
compiler/GHC/Core/Type.hs
=====================================
@@ -1421,8 +1421,6 @@ piResultTy ty arg = case piResultTy_maybe ty arg of
Nothing -> pprPanic "piResultTy" (ppr ty $$ ppr arg)
piResultTy_maybe :: Type -> Type -> Maybe Type
--- We don't need a 'tc' version, because
--- this function behaves the same for Type and Constraint
piResultTy_maybe ty arg = case coreFullView ty of
FunTy { ft_res = res } -> Just res
=====================================
compiler/GHC/Core/Unify.hs
=====================================
@@ -27,7 +27,6 @@ import GHC.Prelude
import GHC.Types.Var
import GHC.Types.Var.Env
import GHC.Types.Var.Set
-import GHC.Builtin.Names( tYPETyConKey, cONSTRAINTTyConKey )
import GHC.Core.Type hiding ( getTvSubstEnv )
import GHC.Core.Coercion hiding ( getCvSubstEnv )
import GHC.Core.Predicate( scopedSort )
@@ -98,8 +97,6 @@ of ways. Here we summarise, but see Note [Specification of unification].
See Note [Apartness and type families]
* MARInfinite (occurs check):
See Note [Infinitary substitutions]
- * MARTypeVsConstraint:
- See Note [Type and Constraint are not apart] in GHC.Builtin.Types.Prim
* MARCast (obscure):
See (KCU2) in Note [Kind coercions in Unify]
@@ -997,16 +994,12 @@ data UnifyResultM a = Unifiable a -- the subst that unifies the types
-- | Why are two types 'MaybeApart'? 'MARInfinite' takes precedence:
-- This is used (only) in Note [Infinitary substitution in lookup] in GHC.Core.InstEnv
--- As of Feb 2022, we never differentiate between MARTypeFamily and MARTypeVsConstraint;
--- it's really only MARInfinite that's interesting here.
+-- It's really only MARInfinite that's interesting here.
data MaybeApartReason
= MARTypeFamily -- ^ matching e.g. F Int ~? Bool
| MARInfinite -- ^ matching e.g. a ~? Maybe a
- | MARTypeVsConstraint -- ^ matching Type ~? Constraint or the arrow types
- -- See Note [Type and Constraint are not apart] in GHC.Builtin.Types.Prim
-
| MARCast -- ^ Very obscure.
-- See (KCU2) in Note [Kind coercions in Unify]
@@ -1015,13 +1008,11 @@ combineMAR :: MaybeApartReason -> MaybeApartReason -> MaybeApartReason
-- See (UR1) in Note [Unification result] for why MARInfinite wins
combineMAR MARInfinite _ = MARInfinite -- MARInfinite wins
combineMAR MARTypeFamily r = r -- Otherwise it doesn't really matter
-combineMAR MARTypeVsConstraint r = r
combineMAR MARCast r = r
instance Outputable MaybeApartReason where
ppr MARTypeFamily = text "MARTypeFamily"
ppr MARInfinite = text "MARInfinite"
- ppr MARTypeVsConstraint = text "MARTypeVsConstraint"
ppr MARCast = text "MARCast"
instance Semigroup MaybeApartReason where
@@ -1729,30 +1720,6 @@ unify_ty env ty1 ty2 kco
; unify_tc_app env tc1 tys1 tys2
}
- -- TYPE and CONSTRAINT are not Apart
- -- See Note [Type and Constraint are not apart] in GHC.Builtin.Types.Prim
- -- NB: at this point we know that the two TyCons do not match
- | Just (tc1,_) <- mb_tc_app1, let u1 = tyConUnique tc1
- , Just (tc2,_) <- mb_tc_app2, let u2 = tyConUnique tc2
- , (u1 == tYPETyConKey && u2 == cONSTRAINTTyConKey) ||
- (u2 == tYPETyConKey && u1 == cONSTRAINTTyConKey)
- = maybeApart MARTypeVsConstraint
- -- We don't bother to look inside; wrinkle (W3) in GHC.Builtin.Types.Prim
- -- Note [Type and Constraint are not apart]
-
- -- The arrow types are not Apart
- -- See Note [Type and Constraint are not apart] in GHC.Builtin.Types.Prim
- -- wrinkle (W2)
- -- NB1: at this point we know that the two TyCons do not match
- -- NB2: In the common FunTy/FunTy case you might wonder if we want to go via
- -- splitTyConApp_maybe. But yes we do: we need to look at those implied
- -- kind argument in order to satisfy (Unification Kind Invariant)
- | FunTy {} <- ty1
- , FunTy {} <- ty2
- = maybeApart MARTypeVsConstraint
- -- We don't bother to look inside; wrinkle (W3) in GHC.Builtin.Types.Prim
- -- Note [Type and Constraint are not apart]
-
where
mb_tc_app1 = splitTyConApp_maybe ty1
mb_tc_app2 = splitTyConApp_maybe ty2
=====================================
compiler/GHC/Tc/Instance/Class.hs
=====================================
@@ -963,11 +963,6 @@ matchTypeable clas [k,t] -- clas = Typeable
| k `eqType` naturalTy = doTyLit knownNatClassName t
| k `eqType` typeSymbolKind = doTyLit knownSymbolClassName t
| k `eqType` charTy = doTyLit knownCharClassName t
-
- -- TyCon applied to its kind args
- -- No special treatment of Type and Constraint; they get distinct TypeReps
- -- see wrinkle (W4) of Note [Type and Constraint are not apart]
- -- in GHC.Builtin.Types.Prim.
| Just (tc, ks) <- splitTyConApp_maybe t -- See Note [Typeable (T a b c)]
, onlyNamedBndrsApplied tc ks = doTyConApp clas t tc ks
=====================================
docs/users_guide/9.16.1-notes.rst
=====================================
@@ -16,6 +16,17 @@ Language
result, you may need to enable :extension:`DataKinds` in code that did not
previously require it.
+- ``Type`` and ``Constraint`` are now (at last) completely distinct types, just as much
+ as ``Int`` and ``Bool``. For example, you can now
+ write::
+
+ type family F a
+
+ type instance F Type = Int
+ type instance F Constraint = Bool
+
+ which was previously rejected with "Conflicting family instance declarations".
+
Compiler
~~~~~~~~
=====================================
testsuite/tests/indexed-types/should_fail/T21092.hs
=====================================
@@ -7,3 +7,5 @@ type family F a
type instance F Type = Int
type instance F Constraint = Bool
+
+-- Nov 2025: Type and Constraint are now Apart (#24279)
=====================================
testsuite/tests/indexed-types/should_fail/T21092.stderr deleted
=====================================
@@ -1,5 +0,0 @@
-
-T21092.hs:8:15: error: [GHC-34447]
- Conflicting family instance declarations:
- F (*) = Int -- Defined at T21092.hs:8:15
- F Constraint = Bool -- Defined at T21092.hs:9:15
=====================================
testsuite/tests/indexed-types/should_fail/all.T
=====================================
@@ -107,7 +107,7 @@ test('T8368', normal, compile_fail, [''])
test('T8368a', normal, compile_fail, [''])
test('T8518', normal, compile_fail, [''])
test('T9036', normal, compile_fail, [''])
-test('T21092', normal, compile_fail, [''])
+test('T21092', normal, compile, ['']) # Now compiles fine
test('T9167', normal, compile_fail, [''])
test('T9171', normal, compile_fail, [''])
test('T9097', normal, compile_fail, [''])
=====================================
testsuite/tests/typecheck/should_fail/T24279.hs
=====================================
@@ -13,7 +13,7 @@ type G :: Type -> RuntimeRep -> Type
type family G a where
G (a b) = a
--- Should be rejected
+-- Now (Nov 2025) accepted
foo :: (F (G Constraint)) -> Bool
foo x = x
@@ -22,10 +22,10 @@ type family H a b where
H a a = Int
H a b = Bool
--- Should be rejected
-bar1 :: H TYPE CONSTRAINT -> Int
+-- Now (Nov 2025) accepted
+bar1 :: H TYPE CONSTRAINT -> Bool
bar1 x = x
--- Should be rejected
-bar2 :: H Type Constraint -> Int
+-- Now (Nov 2025) accepted
+bar2 :: H Type Constraint -> Bool
bar2 x = x
=====================================
testsuite/tests/typecheck/should_fail/T24279.stderr deleted
=====================================
@@ -1,19 +0,0 @@
-
-T24279.hs:18:9: error: [GHC-83865]
- • Couldn't match type ‘F CONSTRAINT’ with ‘Bool’
- Expected: Bool
- Actual: F (G Constraint)
- • In the expression: x
- In an equation for ‘foo’: foo x = x
-
-T24279.hs:27:10: error: [GHC-83865]
- • Couldn't match expected type ‘Int’
- with actual type ‘H TYPE CONSTRAINT’
- • In the expression: x
- In an equation for ‘bar1’: bar1 x = x
-
-T24279.hs:31:10: error: [GHC-83865]
- • Couldn't match expected type ‘Int’
- with actual type ‘H (*) Constraint’
- • In the expression: x
- In an equation for ‘bar2’: bar2 x = x
=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -718,7 +718,7 @@ test('T24064', normal, compile_fail, [''])
test('T24090a', normal, compile_fail, [''])
test('T24090b', normal, compile, ['']) # scheduled to become an actual error in GHC 9.16
test('T24298', normal, compile_fail, [''])
-test('T24279', normal, compile_fail, [''])
+test('T24279', normal, compile, ['']) # Now accepted (Nov 2025)
test('T24318', normal, compile_fail, [''])
# all the various do expansion fail messages
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a00840eacb6e98f0cdc9867db4ebdc6…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a00840eacb6e98f0cdc9867db4ebdc6…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Make TYPE and CONSTRAINT apart again
by Marge Bot (@marge-bot) 15 Nov '25
by Marge Bot (@marge-bot) 15 Nov '25
15 Nov '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
a00840ea by Simon Peyton Jones at 2025-11-14T15:23:56+00:00
Make TYPE and CONSTRAINT apart again
This patch finally fixes #24279.
* The story started with #11715
* Then #21623 articulated a plan, which made Type and Constraint
not-apart; a horrible hack but it worked. The main patch was
commit 778c6adca2c995cd8a1b84394d4d5ca26b915dac
Author: Simon Peyton Jones <simonpj(a)microsoft.com>
Date: Wed Nov 9 10:33:22 2022 +0000
Type vs Constraint: finally nailed
* #24279 reported a bug in the above big commit; this small patch fixes it
commit af6932d6c068361c6ae300d52e72fbe13f8e1f18
Author: Simon Peyton Jones <simon.peytonjones(a)gmail.com>
Date: Mon Jan 8 10:49:49 2024 +0000
Make TYPE and CONSTRAINT not-apart
Issue #24279 showed up a bug in the logic in GHC.Core.Unify.unify_ty
which is supposed to make TYPE and CONSTRAINT be not-apart.
* Then !10479 implemented "unary classes".
* That change in turn allows us to make Type and Constraint apart again,
cleaning up the compiler and allowing a little bit more expressiveness.
It fixes the original hope in #24279, namely that `Type` and `Constraint`
should be distinct throughout.
- - - - -
b674971c by Georgios Karachalias at 2025-11-14T20:12:40-05:00
Report all missing modules with -M
We now report all missing modules at once in GHC.Driver.Makefile.processDeps,
as opposed to only reporting a single missing module. Fixes #26551.
- - - - -
23c9ebc9 by Sylvain Henry at 2025-11-14T20:13:08-05:00
JS: fix array index for registers
We used to store R32 in h$regs[-1]. While it's correct in JavaScript,
fix this to store R32 in h$regs[0] instead.
- - - - -
d43cc50d by Sylvain Henry at 2025-11-14T20:13:08-05:00
JS: support more than 128 registers (#26558)
The JS backend only supported 128 registers (JS variables/array slots
used to pass function arguments). It failed in T26537 when 129
registers were required.
This commit adds support for more than 128 registers: it is now limited to
maxBound :: Int (compiler's Int). If we ever go above this threshold the
compiler now panics with a more descriptive message.
A few built-in JS functions were assuming 128 registers and have been
rewritten to use loops. Note that loops are only used for "high"
registers that are stored in an array: the 31 "low" registers are still
handled with JS global variables and with explicit switch-cases to
maintain good performance in the most common cases (i.e. few registers
used). Adjusting the number of low registers is now easy: just one
constant to adjust (GHC.StgToJS.Regs.lowRegsCount).
No new test added: T26537 is used as a regression test instead.
- - - - -
25 changed files:
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/RoughMap.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Unify.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/StgToJS/Apply.hs
- compiler/GHC/StgToJS/Expr.hs
- compiler/GHC/StgToJS/Regs.hs
- compiler/GHC/StgToJS/Rts/Rts.hs
- compiler/GHC/StgToJS/Rts/Types.hs
- compiler/GHC/Tc/Instance/Class.hs
- docs/users_guide/9.16.1-notes.rst
- testsuite/tests/codeGen/should_run/all.T
- testsuite/tests/driver/Makefile
- + testsuite/tests/driver/T26551.hs
- + testsuite/tests/driver/T26551.stderr
- testsuite/tests/driver/all.T
- testsuite/tests/indexed-types/should_fail/T21092.hs
- − testsuite/tests/indexed-types/should_fail/T21092.stderr
- testsuite/tests/indexed-types/should_fail/all.T
- testsuite/tests/typecheck/should_fail/T24279.hs
- − testsuite/tests/typecheck/should_fail/T24279.stderr
- testsuite/tests/typecheck/should_fail/all.T
Changes:
=====================================
compiler/GHC/Builtin/Types/Prim.hs
=====================================
@@ -752,8 +752,9 @@ Specifically (a ~# b) :: CONSTRAINT (TupleRep [])
Wrinkles
-(W1) Type and Constraint are considered distinct throughout GHC. But they
- are not /apart/: see Note [Type and Constraint are not apart]
+(W1) Type and Constraint are considered distinct throughout GHC.
+ That wasn't always the case:
+ see Historical Note [Type and Constraint are not apart]
(W2) We need two absent-error Ids, aBSENT_ERROR_ID for types of kind Type, and
aBSENT_CONSTRAINT_ERROR_ID for types of kind Constraint.
@@ -768,8 +769,24 @@ Wrinkles
of type TYPE rr. See (CPR2) in Note [Which types are unboxed?] in
GHC.Core.Opt.WorkWrap.Utils.
-Note [Type and Constraint are not apart]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+-------------------------------------------------------------
+Historical Note [Type and Constraint are not apart]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Nov 2025:
+ In the past, Type and Constraint were carefully coonsiderd to be
+ not /apart/. But the necessity for that vanished with unary classes
+ (see Note [Unary class magic]), done in
+
+ commit 9bd7fcc518111a1549c98720c222cdbabd32ed46
+ Author: Simon Peyton Jones <simon.peytonjones(a)gmail.com>
+ Date: Tue Apr 15 17:43:46 2025 +0100
+ Implement unary classes
+
+ So now Type and Constraint are simply distinct type constructors, just as
+ much as Int and Bool.
+
+ The rest of this Note is preserved for historical interest.
+
Type and Constraint are not equal (eqType) but they are not /apart/
either. Reason (c.f. #7451):
@@ -841,6 +858,9 @@ Wrinkles
So in GHC.Tc.Instance.Class.matchTypeable, Type and Constraint are
treated as separate TyCons; i.e. given no special treatment.
+End of Historical Note
+-------------------------------------------------------------
+
Note [RuntimeRep polymorphism]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Generally speaking, you can't be polymorphic in `RuntimeRep`. E.g
=====================================
compiler/GHC/Core/Coercion.hs
=====================================
@@ -641,11 +641,6 @@ eqTyConRole tc
-- | Given a coercion `co :: (t1 :: TYPE r1) ~ (t2 :: TYPE r2)`
-- produce a coercion `rep_co :: r1 ~ r2`
--- But actually it is possible that
--- co :: (t1 :: CONSTRAINT r1) ~ (t2 :: CONSTRAINT r2)
--- or co :: (t1 :: TYPE r1) ~ (t2 :: CONSTRAINT r2)
--- or co :: (t1 :: CONSTRAINT r1) ~ (t2 :: TYPE r2)
--- See Note [mkRuntimeRepCo]
mkRuntimeRepCo :: HasDebugCallStack => Coercion -> Coercion
mkRuntimeRepCo co
= assert (isTYPEorCONSTRAINT k1 && isTYPEorCONSTRAINT k2) $
@@ -654,26 +649,6 @@ mkRuntimeRepCo co
kind_co = mkKindCo co -- kind_co :: TYPE r1 ~ TYPE r2
Pair k1 k2 = coercionKind kind_co
-{- Note [mkRuntimeRepCo]
-~~~~~~~~~~~~~~~~~~~~~~~~
-Given
- class C a where { op :: Maybe a }
-we will get an axiom
- axC a :: (C a :: CONSTRAINT r1) ~ (Maybe a :: TYPE r2)
-(See Note [Type and Constraint are not apart] in GHC.Builtin.Types.Prim.)
-
-Then we may call mkRuntimeRepCo on (axC ty), and that will return
- mkSelCo (SelTyCon 0 Nominal) (Kind (axC ty)) :: r1 ~ r2
-
-So mkSelCo needs to be happy with decomposing a coercion of kind
- CONSTRAINT r1 ~ TYPE r2
-
-Hence the use of `tyConIsTYPEorCONSTRAINT` in the assertion `good_call`
-in `mkSelCo`. See #23018 for a concrete example. (In this context it's
-important that TYPE and CONSTRAINT have the same arity and kind, not
-merely that they are not-apart; otherwise SelCo would not make sense.)
--}
-
isReflCoVar_maybe :: Var -> Maybe Coercion
-- If cv :: t~t then isReflCoVar_maybe cv = Just (Refl t)
-- Works on all kinds of Vars, not just CoVars
@@ -1305,8 +1280,7 @@ mkSelCo_maybe cs co
, Just (tc2, tys2) <- splitTyConApp_maybe ty2
, let { len1 = length tys1
; len2 = length tys2 }
- = (tc1 == tc2 || (tyConIsTYPEorCONSTRAINT tc1 && tyConIsTYPEorCONSTRAINT tc2))
- -- tyConIsTYPEorCONSTRAINT: see Note [mkRuntimeRepCo]
+ = tc1 == tc2
&& len1 == len2
&& n < len1
&& r == tyConRole (coercionRole co) tc1 n
=====================================
compiler/GHC/Core/Lint.hs
=====================================
@@ -2891,13 +2891,9 @@ lint_branch ax_tc (CoAxBranch { cab_tvs = tvs, cab_cvs = cvs
hang (text "Inhomogeneous axiom")
2 (text "lhs:" <+> ppr lhs <+> dcolon <+> ppr lhs_kind $$
text "rhs:" <+> ppr rhs <+> dcolon <+> ppr rhs_kind) }
- -- Type and Constraint are not Apart, so this test allows
- -- the newtype axiom for a single-method class. Indeed the
- -- whole reason Type and Constraint are not Apart is to allow
- -- such axioms!
--- these checks do not apply to newtype axioms
lint_family_branch :: TyCon -> CoAxBranch -> LintM ()
+-- These checks do not apply to newtype axioms
lint_family_branch fam_tc br@(CoAxBranch { cab_tvs = tvs
, cab_eta_tvs = eta_tvs
, cab_cvs = cvs
=====================================
compiler/GHC/Core/RoughMap.hs
=====================================
@@ -36,7 +36,6 @@ import GHC.Core.Type
import GHC.Utils.Outputable
import GHC.Types.Name
import GHC.Types.Name.Env
-import GHC.Builtin.Types.Prim( cONSTRAINTTyConName, tYPETyConName )
import Control.Monad (join)
import Data.Data (Data)
@@ -347,16 +346,7 @@ typeToRoughMatchTc ty
roughMatchTyConName :: TyCon -> Name
roughMatchTyConName tc
- | tc_name == cONSTRAINTTyConName
- = tYPETyConName -- TYPE and CONSTRAINT are not apart, so they must use
- -- the same rough-map key. We arbitrarily use TYPE.
- -- See Note [Type and Constraint are not apart]
- -- wrinkle (W1) in GHC.Builtin.Types.Prim
- | otherwise
- = assertPpr (isGenerativeTyCon tc Nominal) (ppr tc) tc_name
- where
- tc_name = tyConName tc
-
+ = assertPpr (isGenerativeTyCon tc Nominal) (ppr tc) (tyConName tc)
-- | Trie of @[RoughMatchTc]@
--
=====================================
compiler/GHC/Core/Type.hs
=====================================
@@ -1421,8 +1421,6 @@ piResultTy ty arg = case piResultTy_maybe ty arg of
Nothing -> pprPanic "piResultTy" (ppr ty $$ ppr arg)
piResultTy_maybe :: Type -> Type -> Maybe Type
--- We don't need a 'tc' version, because
--- this function behaves the same for Type and Constraint
piResultTy_maybe ty arg = case coreFullView ty of
FunTy { ft_res = res } -> Just res
=====================================
compiler/GHC/Core/Unify.hs
=====================================
@@ -27,7 +27,6 @@ import GHC.Prelude
import GHC.Types.Var
import GHC.Types.Var.Env
import GHC.Types.Var.Set
-import GHC.Builtin.Names( tYPETyConKey, cONSTRAINTTyConKey )
import GHC.Core.Type hiding ( getTvSubstEnv )
import GHC.Core.Coercion hiding ( getCvSubstEnv )
import GHC.Core.Predicate( scopedSort )
@@ -98,8 +97,6 @@ of ways. Here we summarise, but see Note [Specification of unification].
See Note [Apartness and type families]
* MARInfinite (occurs check):
See Note [Infinitary substitutions]
- * MARTypeVsConstraint:
- See Note [Type and Constraint are not apart] in GHC.Builtin.Types.Prim
* MARCast (obscure):
See (KCU2) in Note [Kind coercions in Unify]
@@ -997,16 +994,12 @@ data UnifyResultM a = Unifiable a -- the subst that unifies the types
-- | Why are two types 'MaybeApart'? 'MARInfinite' takes precedence:
-- This is used (only) in Note [Infinitary substitution in lookup] in GHC.Core.InstEnv
--- As of Feb 2022, we never differentiate between MARTypeFamily and MARTypeVsConstraint;
--- it's really only MARInfinite that's interesting here.
+-- It's really only MARInfinite that's interesting here.
data MaybeApartReason
= MARTypeFamily -- ^ matching e.g. F Int ~? Bool
| MARInfinite -- ^ matching e.g. a ~? Maybe a
- | MARTypeVsConstraint -- ^ matching Type ~? Constraint or the arrow types
- -- See Note [Type and Constraint are not apart] in GHC.Builtin.Types.Prim
-
| MARCast -- ^ Very obscure.
-- See (KCU2) in Note [Kind coercions in Unify]
@@ -1015,13 +1008,11 @@ combineMAR :: MaybeApartReason -> MaybeApartReason -> MaybeApartReason
-- See (UR1) in Note [Unification result] for why MARInfinite wins
combineMAR MARInfinite _ = MARInfinite -- MARInfinite wins
combineMAR MARTypeFamily r = r -- Otherwise it doesn't really matter
-combineMAR MARTypeVsConstraint r = r
combineMAR MARCast r = r
instance Outputable MaybeApartReason where
ppr MARTypeFamily = text "MARTypeFamily"
ppr MARInfinite = text "MARInfinite"
- ppr MARTypeVsConstraint = text "MARTypeVsConstraint"
ppr MARCast = text "MARCast"
instance Semigroup MaybeApartReason where
@@ -1729,30 +1720,6 @@ unify_ty env ty1 ty2 kco
; unify_tc_app env tc1 tys1 tys2
}
- -- TYPE and CONSTRAINT are not Apart
- -- See Note [Type and Constraint are not apart] in GHC.Builtin.Types.Prim
- -- NB: at this point we know that the two TyCons do not match
- | Just (tc1,_) <- mb_tc_app1, let u1 = tyConUnique tc1
- , Just (tc2,_) <- mb_tc_app2, let u2 = tyConUnique tc2
- , (u1 == tYPETyConKey && u2 == cONSTRAINTTyConKey) ||
- (u2 == tYPETyConKey && u1 == cONSTRAINTTyConKey)
- = maybeApart MARTypeVsConstraint
- -- We don't bother to look inside; wrinkle (W3) in GHC.Builtin.Types.Prim
- -- Note [Type and Constraint are not apart]
-
- -- The arrow types are not Apart
- -- See Note [Type and Constraint are not apart] in GHC.Builtin.Types.Prim
- -- wrinkle (W2)
- -- NB1: at this point we know that the two TyCons do not match
- -- NB2: In the common FunTy/FunTy case you might wonder if we want to go via
- -- splitTyConApp_maybe. But yes we do: we need to look at those implied
- -- kind argument in order to satisfy (Unification Kind Invariant)
- | FunTy {} <- ty1
- , FunTy {} <- ty2
- = maybeApart MARTypeVsConstraint
- -- We don't bother to look inside; wrinkle (W3) in GHC.Builtin.Types.Prim
- -- Note [Type and Constraint are not apart]
-
where
mb_tc_app1 = splitTyConApp_maybe ty1
mb_tc_app2 = splitTyConApp_maybe ty2
=====================================
compiler/GHC/Driver/MakeFile.hs
=====================================
@@ -55,6 +55,7 @@ import Data.IORef
import qualified Data.Set as Set
import GHC.Iface.Errors.Types
import Data.Either
+import GHC.Data.Bag (listToBag)
-----------------------------------------------------------------
--
@@ -237,19 +238,6 @@ processDeps dflags hsc_env excl_mods root hdl (AcyclicSCC (ModuleNode _ (ModuleN
obj_file = msObjFilePath node
obj_files = insertSuffixes obj_file extra_suffixes
- do_imp loc is_boot pkg_qual imp_mod
- = do { mb_hi <- findDependency hsc_env loc pkg_qual imp_mod
- is_boot include_pkg_deps
- ; case mb_hi of {
- Nothing -> return () ;
- Just hi_file -> do
- { let hi_files = insertSuffixes hi_file extra_suffixes
- write_dep (obj,hi) = writeDependency root hdl [obj] hi
-
- -- Add one dependency for each suffix;
- -- e.g. A.o : B.hi
- -- A.x_o : B.x_hi
- ; mapM_ write_dep (obj_files `zip` hi_files) }}}
-- Emit std dependency of the object(s) on the source file
@@ -280,15 +268,33 @@ processDeps dflags hsc_env excl_mods root hdl (AcyclicSCC (ModuleNode _ (ModuleN
-- Emit a dependency for each import
- ; let do_imps is_boot idecls = sequence_
- [ do_imp loc is_boot mb_pkg mod
+ ; let find_dep loc is_boot pkg_qual imp_mod = findDependency hsc_env loc pkg_qual imp_mod is_boot include_pkg_deps
+
+ find_deps is_boot idecls = sequence
+ [ find_dep loc is_boot mb_pkg mod
| (_lvl, mb_pkg, L loc mod) <- idecls,
mod `notElem` excl_mods ]
- ; do_imps IsBoot (map ((,,) NormalLevel NoPkgQual) (ms_srcimps node))
- ; do_imps NotBoot (ms_imps node)
- }
+ do_imp hi_file = do
+ let hi_files = insertSuffixes hi_file extra_suffixes
+ write_dep (obj,hi) = writeDependency root hdl [obj] hi
+
+ -- Add one dependency for each suffix;
+ -- e.g. A.o : B.hi
+ -- A.x_o : B.x_hi
+ mapM_ write_dep (obj_files `zip` hi_files)
+ ; (missing_boot_dep_errs, boot_deps) <- partitionEithers <$> find_deps IsBoot (map ((,,) NormalLevel NoPkgQual) (ms_srcimps node))
+ ; (missing_not_boot_dep_errs, not_boot_deps) <- partitionEithers <$> find_deps NotBoot (ms_imps node)
+
+ ; let all_missing_errors = missing_boot_dep_errs ++ missing_not_boot_dep_errs
+
+ ; if null all_missing_errors
+ then mapM_ (mapM_ do_imp) (boot_deps ++ not_boot_deps)
+ else do
+ let sec = initSourceErrorContext (hsc_dflags hsc_env)
+ throwErrors sec (mkMessages (listToBag all_missing_errors))
+ }
findDependency :: HscEnv
-> SrcSpan
@@ -296,7 +302,7 @@ findDependency :: HscEnv
-> ModuleName -- Imported module
-> IsBootInterface -- Source import
-> Bool -- Record dependency on package modules
- -> IO (Maybe FilePath) -- Interface file
+ -> IO (Either (MsgEnvelope GhcMessage) (Maybe FilePath)) -- Interface file
findDependency hsc_env srcloc pkg imp is_boot include_pkg_deps = do
-- Find the module; this will be fast because
-- we've done it once during downsweep
@@ -305,16 +311,15 @@ findDependency hsc_env srcloc pkg imp is_boot include_pkg_deps = do
Found loc _
-- Home package: just depend on the .hi or hi-boot file
| isJust (ml_hs_file loc) || include_pkg_deps
- -> return (Just (ml_hi_file loc))
+ -> return (Right (Just (ml_hi_file loc)))
-- Not in this package: we don't need a dependency
| otherwise
- -> return Nothing
+ -> return (Right Nothing)
fail ->
- let sec = initSourceErrorContext (hsc_dflags hsc_env)
- in
- throwOneError sec $
+ return $
+ Left $
mkPlainErrorMsgEnvelope srcloc $
GhcDriverMessage $ DriverInterfaceError $
(Can'tFindInterface (cannotFindModule hsc_env imp fail) (LookingForModule imp is_boot))
=====================================
compiler/GHC/StgToJS/Apply.hs
=====================================
@@ -185,7 +185,7 @@ genApp ctx i args
as' <- concatMapM genArg args
ei <- varForEntryId i
let ra = mconcat . reverse $
- zipWith (\r a -> toJExpr r |= a) [R1 ..] as'
+ zipWith (\r a -> toJExpr r |= a) regsFromR1 as'
p <- pushLneFrame n ctx
a <- adjSp 1 -- for the header (which will only be written when the thread is suspended)
return (ra <> p <> a <> returnS ei, ExprCont)
@@ -464,42 +464,31 @@ specTag spec = Bits.shiftL (specVars spec) 8 Bits..|. specArgs spec
specTagExpr :: ApplySpec -> JStgExpr
specTagExpr = toJExpr . specTag
--- | Build arrays to quickly lookup apply functions
+-- | Build functions to quickly lookup apply functions
--
--- h$apply[r << 8 | n] = function application for r regs, n args
--- h$paps[r] = partial application for r registers (number of args is in the object)
+-- h$apply(r << 8 | n) = function application for r regs, n args
+-- h$paps(r) = partial application for r registers (number of args is in the object)
mkApplyArr :: JSM JStgStat
mkApplyArr =
- do mk_ap_gens <- jFor (|= zero_) (.<. Int 65536) preIncrS
- \j -> hdApply .! j |= hdApGen
- mk_pap_gens <- jFor (|= zero_) (.<. Int 128) preIncrS
- \j -> hdPaps .! j |= hdPapGen
+ do paps_fun <- jFunction (name hdPapsStr) \(MkSolo i) -> pure $ SwitchStat i (map case_pap specPap) (returnS hdPapGen)
+ apply_fun <- jFunction (name hdApplyStr) \(MkSolo i) -> pure $ SwitchStat i (mapMaybe' case_apply applySpec) (returnS hdApGen)
return $ mconcat
- [ name hdApplyStr ||= toJExpr (JList [])
- , name hdPapsStr ||= toJExpr (JList [])
- , ApplStat (hdInitStatic .^ "push")
- [ jLam' $
- mconcat
- [ mk_ap_gens
- , mk_pap_gens
- , mconcat (map assignSpec applySpec)
- , mconcat (map assignPap specPap)
- ]
- ]
+ [ paps_fun
+ , apply_fun
]
where
- assignSpec :: ApplySpec -> JStgStat
- assignSpec spec = case specConv spec of
+ case_apply :: ApplySpec -> Maybe (JStgExpr,JStgStat)
+ case_apply spec = case specConv spec of
-- both fast/slow (regs/stack) specialized apply functions have the same
-- tags. We store the stack ones in the array because they are used as
-- continuation stack frames.
- StackConv -> hdApply .! specTagExpr spec |= specApplyExpr spec
- RegsConv -> mempty
+ StackConv -> Just (specTagExpr spec, returnS (specApplyExpr spec))
+ RegsConv -> Nothing
hdPap_ = unpackFS hdPapStr_
- assignPap :: Int -> JStgStat
- assignPap p = hdPaps .! toJExpr p |= global (mkFastString (hdPap_ ++ show p))
+ case_pap :: Int -> (JStgExpr, JStgStat)
+ case_pap p = (toJExpr p, returnS $ global (mkFastString (hdPap_ ++ show p)))
-- | Push a continuation on the stack
--
@@ -619,7 +608,7 @@ genericStackApply cfg = closure info body
-- compute new tag with consumed register values and args removed
, newTag |= ((given_regs-needed_regs).<<.8) .|. (given_args - needed_args)
-- find application function for the remaining regs/args
- , newAp |= hdApply .! newTag
+ , newAp |= ApplExpr hdApply [newTag]
, traceRts cfg (jString "h$ap_gen: next: " + (newAp .^ "n"))
-- Drop used registers from the stack.
@@ -643,7 +632,7 @@ genericStackApply cfg = closure info body
-----------------------------
[ traceRts cfg (jString "h$ap_gen: undersat")
-- find PAP entry function corresponding to given_regs count
- , p |= hdPaps .! given_regs
+ , p |= ApplExpr hdPaps [given_regs]
-- build PAP payload: R1 + tag + given register values
, newTag |= ((needed_regs-given_regs) .<<. 8) .|. (needed_args-given_args)
@@ -716,7 +705,7 @@ genericFastApply s =
do push_all_regs <- pushAllRegs tag
return $ mconcat $
[ push_all_regs
- , ap |= hdApply .! tag
+ , ap |= ApplExpr hdApply [tag]
, ifS (ap .===. hdApGen)
((sp |= sp + 2) <> (stack .! (sp-1) |= tag))
(sp |= sp + 1)
@@ -750,7 +739,7 @@ genericFastApply s =
, traceRts s (jString "h$ap_gen_fast: oversat " + sp)
, push_args
, newTag |= ((myRegs-( arity.>>.8)).<<.8).|.myAr-ar
- , newAp |= hdApply .! newTag
+ , newAp |= ApplExpr hdApply [newTag]
, ifS (newAp .===. hdApGen)
((sp |= sp + 2) <> (stack .! (sp - 1) |= newTag))
(sp |= sp + 1)
@@ -761,7 +750,7 @@ genericFastApply s =
-- else
[traceRts s (jString "h$ap_gen_fast: undersat: " + myRegs + jString " " + tag)
, jwhenS (tag .!=. 0) $ mconcat
- [ p |= hdPaps .! myRegs
+ [ p |= ApplExpr hdPaps [myRegs]
, dat |= toJExpr [r1, ((arity .>>. 8)-myRegs)*256+ar-myAr]
, get_regs
, r1 |= initClosure s p dat jCurrentCCS
@@ -773,14 +762,24 @@ genericFastApply s =
pushAllRegs :: JStgExpr -> JSM JStgStat
pushAllRegs tag =
jVar \regs ->
- return $ mconcat $
- [ regs |= tag .>>. 8
- , sp |= sp + regs
- , SwitchStat regs (map pushReg [65,64..2]) mempty
- ]
- where
- pushReg :: Int -> (JStgExpr, JStgStat)
- pushReg r = (toJExpr (r-1), stack .! (sp - toJExpr (r - 2)) |= jsReg r)
+ let max_low_reg = regNumber maxLowReg
+ low_regs = [max_low_reg, max_low_reg-1..2] -- R1 isn't used for arguments
+ pushReg :: Int -> (JStgExpr, JStgStat)
+ pushReg r = (toJExpr r, stack .! (sp - toJExpr (r - 2)) |= jsReg r)
+ in return $ mconcat $
+ [ regs |= tag .>>. 8
+ , sp |= sp + regs
+ -- increment the number of regs by 1, so that it matches register
+ -- numbers (R1 is not used for args)
+ , postIncrS regs
+ -- copy high registers with a loop
+ , WhileStat False (regs .>. toJExpr max_low_reg) $ mconcat
+ -- rN stored in stack[sp - N - 2] so that r2 is stored in stack[sp], etc.
+ [ stack .! (sp - regs - 2) |= highReg_expr regs
+ , postDecrS regs
+ ]
+ , SwitchStat regs (map pushReg low_regs) mempty
+ ]
pushArgs :: JStgExpr -> JStgExpr -> JSM JStgStat
pushArgs start end =
@@ -906,7 +905,7 @@ stackApply s fun_name nargs nvars =
[ rs |= (arity .>>. 8)
, loadRegs rs
, sp |= sp - rs
- , newAp |= (hdApply .! ((toJExpr nargs-arity0).|.((toJExpr nvars-rs).<<.8)))
+ , newAp |= ApplExpr hdApply [(toJExpr nargs-arity0).|.((toJExpr nvars-rs).<<.8)]
, stack .! sp |= newAp
, profStat s pushRestoreCCS
, traceRts s (toJExpr (fun_name <> ": new stack frame: ") + (newAp .^ "n"))
@@ -989,7 +988,7 @@ fastApply s fun_name nargs nvars = if nargs == 0 && nvars == 0
+ rsRemain)
, saveRegs rs
, sp |= sp + rsRemain + 1
- , stack .! sp |= hdApply .! ((rsRemain.<<.8).|. (toJExpr nargs - mask8 arity))
+ , stack .! sp |= ApplExpr hdApply [(rsRemain.<<.8).|. (toJExpr nargs - mask8 arity)]
, profStat s pushRestoreCCS
, returnS c
]
@@ -1238,14 +1237,30 @@ pap s r = closure (ClosureInfo
, profStat s (enterCostCentreFun currentCCS)
, extra |= (funOrPapArity c (Just f) .>>. 8) - toJExpr r
, traceRts s (toJExpr (funcName <> ": pap extra args moving: ") + extra)
- , moveBy extra
+ , case r of
+ 0 -> mempty -- in pap_0 we don't shift any register
+ _ -> moveBy extra
, loadOwnArgs d
, r1 |= c
, returnS f
]
- moveBy extra = SwitchStat extra
- (reverse $ map moveCase [1..maxReg-r-1]) mempty
- moveCase m = (toJExpr m, jsReg (m+r+1) |= jsReg (m+1))
+ moveBy extra =
+ let max_low_reg = regNumber maxLowReg
+ low_regs = [max_low_reg, max_low_reg-1..2] -- R1 isn't used for arguments
+ move_case m = (toJExpr m, jsReg (m+r) |= jsReg m)
+ in mconcat
+ [ -- increment the number of args by 1, so that it matches register
+ -- numbers (R1 is not used for args)
+ postIncrS extra
+ -- copy high registers with a loop
+ , WhileStat False (extra .>. toJExpr max_low_reg) $ mconcat
+ [ highReg_expr (extra + toJExpr r) |= highReg_expr extra
+ , postDecrS extra
+ ]
+ -- then copy low registers with a case
+ , SwitchStat extra (map move_case low_regs) mempty
+ ]
+
loadOwnArgs d = mconcat $ map (\r ->
jsReg (r+1) |= dField d (r+2)) [1..r]
dField d n = SelExpr d (name . mkFastString $ ('d':show (n-1)))
@@ -1274,7 +1289,9 @@ papGen cfg =
(jString "h$pap_gen: expected function or pap")
, profStat cfg (enterCostCentreFun currentCCS)
, traceRts cfg (jString "h$pap_gen: generic pap extra args moving: " + or)
+ -- shift newly applied arguments into appropriate registers
, appS hdMoveRegs2 [or, r]
+ -- load stored arguments into lowest argument registers (i.e. starting from R2)
, loadOwnArgs d r
, r1 |= c
, returnS f
@@ -1285,9 +1302,22 @@ papGen cfg =
funcIdent = name funcName
funcName = hdPapGenStr
loadOwnArgs d r =
- let prop n = d .^ ("d" <> mkFastString (show $ n+1))
- loadOwnArg n = (toJExpr n, jsReg (n+1) |= prop n)
- in SwitchStat r (map loadOwnArg [127,126..1]) mempty
+ let prop n = d .^ (mkFastString ("d" ++ show n))
+ loadOwnArg n = (toJExpr n, jsReg n |= prop n)
+ max_low_reg = regNumber maxLowReg
+ low_regs = [max_low_reg, max_low_reg-1..2] -- R1 isn't used for arguments
+ in mconcat
+ [ -- increment the number of args by 1, so that it matches register
+ -- numbers (R1 is not used for args) and PAP fields (starting from d2)
+ postIncrS r
+ -- copy high registers with a loop
+ , WhileStat False (r .>. toJExpr max_low_reg) $ mconcat
+ [ highReg_expr r |= (d .! (jString (fsLit "d") + r))
+ , postDecrS r
+ ]
+ -- then copy low registers with a case.
+ , SwitchStat r (map loadOwnArg low_regs) mempty
+ ]
-- general utilities
-- move the first n registers, starting at R2, m places up (do not use with negative m)
@@ -1301,7 +1331,7 @@ moveRegs2 = jFunction (name hdMoveRegs2) moveSwitch
switchCase n m = (toJExpr $
(n `Bits.shiftL` 8) Bits..|. m
, mconcat (map (`moveRegFast` m) [n+1,n..2])
- <> BreakStat Nothing {-[j| break; |]-})
+ <> BreakStat Nothing)
moveRegFast n m = jsReg (n+m) |= jsReg n
-- fallback
defaultCase n m =
=====================================
compiler/GHC/StgToJS/Expr.hs
=====================================
@@ -312,7 +312,7 @@ genBody ctx startReg args e typ = do
-- load arguments into local variables
la <- do
args' <- concatMapM genIdArgI args
- return (declAssignAll args' (fmap toJExpr [startReg..]))
+ return (declAssignAll args' (jsRegsFrom startReg))
-- assert that arguments have valid runtime reps
lav <- verifyRuntimeReps args
@@ -665,7 +665,7 @@ genCase ctx bnd e at alts l
| otherwise = do
rj <- genRet ctx bnd at alts l
let ctx' = ctxSetTop bnd
- $ ctxSetTarget (assocIdExprs bnd (map toJExpr [R1 ..]))
+ $ ctxSetTarget (assocIdExprs bnd jsRegsFromR1)
$ ctx
(ej, _r) <- genExpr ctx' e
return (rj <> ej, ExprCont)
@@ -730,7 +730,7 @@ genRet ctx e at as l = freshIdent >>= f
fun free = resetSlots $ do
decs <- declVarsForId e
- load <- flip assignAll (map toJExpr [R1 ..]) . map toJExpr <$> identsForId e
+ load <- flip assignAll jsRegsFromR1 . map toJExpr <$> identsForId e
loadv <- verifyRuntimeReps [e]
ras <- loadRetArgs free
rasv <- verifyRuntimeReps (map (\(x,_,_)->x) free)
=====================================
compiler/GHC/StgToJS/Regs.hs
=====================================
@@ -1,4 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE PatternSynonyms #-}
module GHC.StgToJS.Regs
( StgReg (..)
@@ -6,17 +7,25 @@ module GHC.StgToJS.Regs
, sp
, stack
, r1, r2, r3, r4
+ , pattern R1, pattern R2, pattern R3, pattern R4
, regsFromR1
, regsFromR2
+ , regsFromTo
+ , jsRegsFrom
, jsRegsFromR1
, jsRegsFromR2
, StgRet (..)
- , jsRegToInt
- , intToJSReg
+ , regNumber
, jsReg
+ , highReg
+ , highReg_expr
, maxReg
+ , maxLowReg
, minReg
+ , minHighReg
, lowRegs
+ , lowRegsCount
+ , lowRegsIdents
, retRegs
, register
, foreignRegister
@@ -32,6 +41,7 @@ import GHC.JS.Make
import GHC.StgToJS.Symbols
import GHC.Data.FastString
+import GHC.Utils.Panic.Plain
import Data.Array
import qualified Data.ByteString.Char8 as BSC
@@ -39,26 +49,15 @@ import Data.Char
import Data.Semigroup ((<>))
-- | General purpose "registers"
---
--- The JS backend arbitrarily supports 128 registers
-data StgReg
- = R1 | R2 | R3 | R4 | R5 | R6 | R7 | R8
- | R9 | R10 | R11 | R12 | R13 | R14 | R15 | R16
- | R17 | R18 | R19 | R20 | R21 | R22 | R23 | R24
- | R25 | R26 | R27 | R28 | R29 | R30 | R31 | R32
- | R33 | R34 | R35 | R36 | R37 | R38 | R39 | R40
- | R41 | R42 | R43 | R44 | R45 | R46 | R47 | R48
- | R49 | R50 | R51 | R52 | R53 | R54 | R55 | R56
- | R57 | R58 | R59 | R60 | R61 | R62 | R63 | R64
- | R65 | R66 | R67 | R68 | R69 | R70 | R71 | R72
- | R73 | R74 | R75 | R76 | R77 | R78 | R79 | R80
- | R81 | R82 | R83 | R84 | R85 | R86 | R87 | R88
- | R89 | R90 | R91 | R92 | R93 | R94 | R95 | R96
- | R97 | R98 | R99 | R100 | R101 | R102 | R103 | R104
- | R105 | R106 | R107 | R108 | R109 | R110 | R111 | R112
- | R113 | R114 | R115 | R116 | R117 | R118 | R119 | R120
- | R121 | R122 | R123 | R124 | R125 | R126 | R127 | R128
- deriving (Eq, Ord, Show, Enum, Bounded, Ix)
+newtype StgReg
+ = StgReg Int
+ deriving (Eq,Ord,Ix)
+
+pattern R1, R2, R3, R4 :: StgReg
+pattern R1 = StgReg 0
+pattern R2 = StgReg 1
+pattern R3 = StgReg 2
+pattern R4 = StgReg 3
-- | Stack registers
data Special
@@ -78,7 +77,7 @@ instance ToJExpr Special where
toJExpr Sp = hdStackPtr
instance ToJExpr StgReg where
- toJExpr r = registers ! r
+ toJExpr r = register r
instance ToJExpr StgRet where
toJExpr r = rets ! r
@@ -99,25 +98,42 @@ r2 = toJExpr R2
r3 = toJExpr R3
r4 = toJExpr R4
+-- | 1-indexed register number (R1 has index 1)
+regNumber :: StgReg -> Int
+regNumber (StgReg r) = r+1
-jsRegToInt :: StgReg -> Int
-jsRegToInt = (+1) . fromEnum
+-- | StgReg from 1-indexed number
+regFromNumber :: Int -> StgReg
+regFromNumber r = assert (r >= 1) $ StgReg (r-1)
-intToJSReg :: Int -> StgReg
-intToJSReg r = toEnum (r - 1)
+regsFromTo :: StgReg -> StgReg -> [StgReg]
+regsFromTo (StgReg x) (StgReg y) = map StgReg [x .. y]
+-- | Register expression from its 1-indexed index
jsReg :: Int -> JStgExpr
-jsReg r = toJExpr (intToJSReg r)
+jsReg r = toJExpr (regFromNumber r)
+
+minReg :: StgReg
+minReg = R1
-maxReg :: Int
-maxReg = jsRegToInt maxBound
+maxReg :: StgReg
+maxReg = regFromNumber maxBound
-minReg :: Int
-minReg = jsRegToInt minBound
+lowRegsCount :: Int
+lowRegsCount = 31
+
+maxLowReg :: StgReg
+maxLowReg = regFromNumber lowRegsCount
+
+-- | First register stored in h$regs array instead of having its own top-level
+-- variable
+minHighReg :: StgReg
+minHighReg = case maxLowReg of
+ StgReg r -> StgReg (r+1)
-- | List of registers, starting from R1
regsFromR1 :: [StgReg]
-regsFromR1 = enumFrom R1
+regsFromR1 = regsFromTo R1 maxReg ++ repeat (panic "StgToJS: code requires too many registers")
-- | List of registers, starting from R2
regsFromR2 :: [StgReg]
@@ -131,35 +147,59 @@ jsRegsFromR1 = fmap toJExpr regsFromR1
jsRegsFromR2 :: [JStgExpr]
jsRegsFromR2 = tail jsRegsFromR1
+-- | List of registers, starting from given reg as JExpr
+jsRegsFrom :: StgReg -> [JStgExpr]
+jsRegsFrom (StgReg n) = drop n jsRegsFromR1
+
+-- | High register
+highReg :: Int -> JStgExpr
+highReg r = assert (r >= regNumber minHighReg) $ IdxExpr hdRegs (toJExpr (r - regNumber minHighReg))
+
+-- | High register indexing with a JS expression
+highReg_expr :: JStgExpr -> JStgExpr
+highReg_expr r = IdxExpr hdRegs (r - toJExpr (regNumber minHighReg))
+
+
---------------------------------------------------
-- caches
---------------------------------------------------
-lowRegs :: [Ident]
-lowRegs = map reg_to_ident [R1 .. R31]
- where reg_to_ident = name . mkFastString . (unpackFS hdStr ++) . map toLower . show
+lowRegs :: [StgReg]
+lowRegs = regsFromTo minReg maxLowReg
+
+lowRegsIdents :: [Ident]
+lowRegsIdents = map reg_to_ident lowRegs
+ where
+ -- low regs are named h$r1, h$r2, etc.
+ reg_to_ident r = name (mkFastString (unpackFS hdStr ++ "r" ++ show (regNumber r)))
retRegs :: [Ident]
retRegs = [name . mkFastStringByteString
$ hdB <> BSC.pack (map toLower $ show n) | n <- enumFrom Ret1]
--- cache JExpr representing StgReg
-registers :: Array StgReg JStgExpr
-registers = listArray (minBound, maxBound) (map (global . identFS) lowRegs ++ map regN [R32 .. R128])
- where
- regN :: StgReg -> JStgExpr
- regN r = IdxExpr hdRegs (toJExpr (fromEnum r - 32))
-
-- cache JExpr representing StgRet
rets :: Array StgRet JStgExpr
rets = listArray (minBound, maxBound) (map retN (enumFrom Ret1))
where
retN = global . mkFastString . (unpackFS hdStr ++) . map toLower . show
--- | Given a register, return the JS syntax object representing that register
-register :: StgReg -> JStgExpr
-register i = registers ! i
-
-- | Given a register, return the JS syntax object representing that register
foreignRegister :: StgRet -> JStgExpr
foreignRegister i = rets ! i
+
+-- | Given a register, return the JS syntax object representing that register
+register :: StgReg -> JStgExpr
+register i
+ | i <= maxCachedReg = register_cache ! i -- Expressions of common registers are cached.
+ | otherwise = make_high_reg i -- Expression of higher registers are made on the fly
+
+maxCachedReg :: StgReg
+maxCachedReg = regFromNumber 128
+
+-- cache JExpr representing StgReg
+register_cache :: Array StgReg JStgExpr
+register_cache = listArray (minReg, maxCachedReg) (map (global . identFS) lowRegsIdents ++ map make_high_reg (regsFromTo minHighReg maxCachedReg))
+
+-- | Make h$regs[XXX] expression for the register
+make_high_reg :: StgReg -> JStgExpr
+make_high_reg r = highReg (regNumber r)
=====================================
compiler/GHC/StgToJS/Rts/Rts.hs
=====================================
@@ -54,7 +54,12 @@ import qualified Data.Bits as Bits
-- | The garbageCollector resets registers and result variables.
garbageCollector :: JSM JStgStat
garbageCollector = jBlock
- [ jFunction' hdResetRegisters (return $ mconcat $ map resetRegister [minBound..maxBound])
+ [ jFunction' hdResetRegisters $ return $ mconcat
+ [ -- reset low registers explicitly
+ mconcat (map resetRegister lowRegs)
+ -- reset the whole h$regs array with h$regs.fill(null)
+ , toStat $ ApplExpr (hdRegs .^ "fill") [null_]
+ ]
, jFunction' hdResetResultVars (return $ mconcat $ map resetResultVar [minBound..maxBound])
]
@@ -249,7 +254,7 @@ declRegs = do
loaders <- loadRegs
return $
mconcat [ hdRegsStr ||= toJExpr (JList [])
- , mconcat (map declReg lowRegs)
+ , mconcat (map declReg lowRegsIdents)
, getters_setters
, loaders
]
@@ -259,15 +264,15 @@ declRegs = do
-- | JS payload to define getters and setters on the registers.
regGettersSetters :: JSM JStgStat
regGettersSetters =
- do setters <- jFunction (name hdGetRegStr) (\(MkSolo n) -> return $ SwitchStat n getRegCases mempty)
- getters <- jFunction (name hdSetRegStr) (\(n,v) -> return $ SwitchStat n (setRegCases v) mempty)
+ do getters <- jFunction (name hdGetRegStr) (\(MkSolo n) -> return $ SwitchStat n getRegCases (defaultGetRegCase n))
+ setters <- jFunction (name hdSetRegStr) (\(n,v) -> return $ SwitchStat n (setRegCases v) (defaultSetRegCase n v))
return $ setters <> getters
where
- getRegCases =
- map (\r -> (toJExpr (jsRegToInt r) , returnS (toJExpr r))) regsFromR1
- setRegCases :: JStgExpr -> [(JStgExpr,JStgStat)]
- setRegCases v =
- map (\r -> (toJExpr (jsRegToInt r), (toJExpr r |= toJExpr v) <> returnS undefined_)) regsFromR1
+ getRegCases = map (\r -> (toJExpr (regNumber r) , returnS (toJExpr r))) lowRegs
+ defaultGetRegCase n = returnS (highReg_expr n)
+
+ setRegCases v = map (\r -> (toJExpr (regNumber r), (toJExpr r |= v) <> BreakStat Nothing)) lowRegs
+ defaultSetRegCase n v = highReg_expr n |= v
-- | JS payload that defines the functions to load each register
loadRegs :: JSM JStgStat
=====================================
compiler/GHC/StgToJS/Rts/Types.hs
=====================================
@@ -69,12 +69,3 @@ stackFrameSize tgt f =
(tgt |= mask8 tag + 1) -- else set to mask'd tag + 1
]
))
-
- --------------------------------------------------------------------------------
--- Register utilities
---------------------------------------------------------------------------------
-
--- | Perform the computation 'f', on the range of registers bounded by 'start'
--- and 'end'.
-withRegs :: StgReg -> StgReg -> (StgReg -> JStgStat) -> JStgStat
-withRegs start end f = mconcat $ fmap f [start..end]
=====================================
compiler/GHC/Tc/Instance/Class.hs
=====================================
@@ -963,11 +963,6 @@ matchTypeable clas [k,t] -- clas = Typeable
| k `eqType` naturalTy = doTyLit knownNatClassName t
| k `eqType` typeSymbolKind = doTyLit knownSymbolClassName t
| k `eqType` charTy = doTyLit knownCharClassName t
-
- -- TyCon applied to its kind args
- -- No special treatment of Type and Constraint; they get distinct TypeReps
- -- see wrinkle (W4) of Note [Type and Constraint are not apart]
- -- in GHC.Builtin.Types.Prim.
| Just (tc, ks) <- splitTyConApp_maybe t -- See Note [Typeable (T a b c)]
, onlyNamedBndrsApplied tc ks = doTyConApp clas t tc ks
=====================================
docs/users_guide/9.16.1-notes.rst
=====================================
@@ -16,6 +16,17 @@ Language
result, you may need to enable :extension:`DataKinds` in code that did not
previously require it.
+- ``Type`` and ``Constraint`` are now (at last) completely distinct types, just as much
+ as ``Int`` and ``Bool``. For example, you can now
+ write::
+
+ type family F a
+
+ type instance F Type = Int
+ type instance F Constraint = Bool
+
+ which was previously rejected with "Conflicting family instance declarations".
+
Compiler
~~~~~~~~
=====================================
testsuite/tests/codeGen/should_run/all.T
=====================================
@@ -256,4 +256,4 @@ test('T24893', normal, compile_and_run, ['-O'])
test('CCallConv', [req_c], compile_and_run, ['CCallConv_c.c'])
test('T25364', normal, compile_and_run, [''])
test('T26061', normal, compile_and_run, [''])
-test('T26537', js_broken(26558), compile_and_run, ['-O2 -fregs-graph'])
+test('T26537', normal, compile_and_run, ['-O2 -fregs-graph'])
=====================================
testsuite/tests/driver/Makefile
=====================================
@@ -415,6 +415,10 @@ test200:
"$(TEST_HC)" $(TEST_HC_OPTS) -M -dep-suffix "" -dep-makefile $(DEPFILE200) D200.hs B200/C.hs A200.hs
test -f $(DEPFILE200)
+# Test that we produce "could not find module" errors for _all_ missing imports.
+T26551:
+ "$(TEST_HC)" $(TEST_HC_OPTS) -M T26551.hs || true
+
# -----------------------------------------------------------------------------
T2566::
=====================================
testsuite/tests/driver/T26551.hs
=====================================
@@ -0,0 +1,5 @@
+module Main where
+
+import Foo
+import Bar
+import Baz
=====================================
testsuite/tests/driver/T26551.stderr
=====================================
@@ -0,0 +1,11 @@
+T26551.hs:3:8: [GHC-87110]
+ Could not find module ‘Foo’.
+ Use -v to see a list of the files searched for.
+
+T26551.hs:4:8: [GHC-87110]
+ Could not find module ‘Bar’.
+ Use -v to see a list of the files searched for.
+
+T26551.hs:5:8: [GHC-87110]
+ Could not find module ‘Baz’.
+ Use -v to see a list of the files searched for.
=====================================
testsuite/tests/driver/all.T
=====================================
@@ -332,3 +332,4 @@ test('t25150', [extra_files(["t25150"])], multimod_compile, ['Main.hs', '-v0 -wo
test('T25382', normal, makefile_test, [])
test('T26018', req_c, makefile_test, [])
test('T24120', normal, compile, ['-Wunused-packages -hide-all-packages -package base -package system-cxx-std-lib'])
+test('T26551', [extra_files(['T26551.hs'])], makefile_test, [])
=====================================
testsuite/tests/indexed-types/should_fail/T21092.hs
=====================================
@@ -7,3 +7,5 @@ type family F a
type instance F Type = Int
type instance F Constraint = Bool
+
+-- Nov 2025: Type and Constraint are now Apart (#24279)
=====================================
testsuite/tests/indexed-types/should_fail/T21092.stderr deleted
=====================================
@@ -1,5 +0,0 @@
-
-T21092.hs:8:15: error: [GHC-34447]
- Conflicting family instance declarations:
- F (*) = Int -- Defined at T21092.hs:8:15
- F Constraint = Bool -- Defined at T21092.hs:9:15
=====================================
testsuite/tests/indexed-types/should_fail/all.T
=====================================
@@ -107,7 +107,7 @@ test('T8368', normal, compile_fail, [''])
test('T8368a', normal, compile_fail, [''])
test('T8518', normal, compile_fail, [''])
test('T9036', normal, compile_fail, [''])
-test('T21092', normal, compile_fail, [''])
+test('T21092', normal, compile, ['']) # Now compiles fine
test('T9167', normal, compile_fail, [''])
test('T9171', normal, compile_fail, [''])
test('T9097', normal, compile_fail, [''])
=====================================
testsuite/tests/typecheck/should_fail/T24279.hs
=====================================
@@ -13,7 +13,7 @@ type G :: Type -> RuntimeRep -> Type
type family G a where
G (a b) = a
--- Should be rejected
+-- Now (Nov 2025) accepted
foo :: (F (G Constraint)) -> Bool
foo x = x
@@ -22,10 +22,10 @@ type family H a b where
H a a = Int
H a b = Bool
--- Should be rejected
-bar1 :: H TYPE CONSTRAINT -> Int
+-- Now (Nov 2025) accepted
+bar1 :: H TYPE CONSTRAINT -> Bool
bar1 x = x
--- Should be rejected
-bar2 :: H Type Constraint -> Int
+-- Now (Nov 2025) accepted
+bar2 :: H Type Constraint -> Bool
bar2 x = x
=====================================
testsuite/tests/typecheck/should_fail/T24279.stderr deleted
=====================================
@@ -1,19 +0,0 @@
-
-T24279.hs:18:9: error: [GHC-83865]
- • Couldn't match type ‘F CONSTRAINT’ with ‘Bool’
- Expected: Bool
- Actual: F (G Constraint)
- • In the expression: x
- In an equation for ‘foo’: foo x = x
-
-T24279.hs:27:10: error: [GHC-83865]
- • Couldn't match expected type ‘Int’
- with actual type ‘H TYPE CONSTRAINT’
- • In the expression: x
- In an equation for ‘bar1’: bar1 x = x
-
-T24279.hs:31:10: error: [GHC-83865]
- • Couldn't match expected type ‘Int’
- with actual type ‘H (*) Constraint’
- • In the expression: x
- In an equation for ‘bar2’: bar2 x = x
=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -718,7 +718,7 @@ test('T24064', normal, compile_fail, [''])
test('T24090a', normal, compile_fail, [''])
test('T24090b', normal, compile, ['']) # scheduled to become an actual error in GHC 9.16
test('T24298', normal, compile_fail, [''])
-test('T24279', normal, compile_fail, [''])
+test('T24279', normal, compile, ['']) # Now accepted (Nov 2025)
test('T24318', normal, compile_fail, [''])
# all the various do expansion fail messages
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a604dd877075ec803abb2f0f286905…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a604dd877075ec803abb2f0f286905…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T26425] 17 commits: Preserve user-written kinds in data declarations
by Simon Peyton Jones (@simonpj) 14 Nov '25
by Simon Peyton Jones (@simonpj) 14 Nov '25
14 Nov '25
Simon Peyton Jones pushed to branch wip/T26425 at Glasgow Haskell Compiler / GHC
Commits:
3c2f4bb4 by sheaf at 2025-11-11T11:47:28-05:00
Preserve user-written kinds in data declarations
This commit ensures that we preserve the user-written kind for data
declarations, e.g. in
type T2T = Type -> Type
type D :: T2T
data D a where { .. }
that we preserve the user-written kind of D as 'T2T', instead of
expanding the type synonym 'T2T' during kind checking.
We do this by storing 'tyConKind' separately from 'tyConResKind'. This
means that 'tyConKind' is not necessarily equal to
'mkTyConKind binders res_kind', as e.g. in the above example the former
is 'T2T' while the latter is 'Type -> Type'.
This is explained in Note [Preserve user-written TyCon kind] in GHC.Core.TyCon.
This is particularly important for Haddock, as the kinds stored in
interface files affect the generated documentation, and we want to
preserve the user-written types as much as possible.
- - - - -
19859584 by sheaf at 2025-11-11T11:47:28-05:00
Store user-written datacon tvs in interface files
This commit ensures we store the user-written quantified type variables
of data constructors in interface files, e.g. in
data D a where
MkD1 :: forall x. x -> D x
MkD2 :: forall u v. u -> v -> D v
The previous behaviour was to rename the universal variables to match
the universal variables of the data constructor. This was undesirable
because the names that end up in interface files end up mattering for
generated Haddock documentation; it's better to preserve the user-written
type variables.
Moreover, the universal variables may not have been user-written at all,
e.g. in an example such as:
type T2T = Type -> Type
data G :: T2T where
MkG :: forall x. D x
Here GHC will invent the type variable name 'a' for the first binder of
the TyCon G. We really don't want to then rename the user-written 'x'
into the generated 'a'.
- - - - -
034b2056 by sheaf at 2025-11-11T11:47:28-05:00
DataCon univ_tvs names: pick TyCon over inferred
This commit changes how we compute the names of universal type variables
in GADT data constructors. This augments the existing logic that chose
which type variable name to use, in GHC.Tc.TyCl.mkGADTVars. We continue
to prefer DataCon tv names for user-written binders, but we now prefer
TyCon tv names for inferred (non-user-written) DataCon binders.
This makes a difference in examples such as:
type (:~~:) :: k1 -> k2 -> Type
data a :~~: b where
HRefl :: a :~~: a
Before this patch, we ended up giving HRefl the type:
forall {k2}. forall (a :: k2). a :~~: a
whereas we now give it the type:
forall {k1}. forall (a :: k1). a :~~: a
The important part isn't really 'k1' or 'k2', but more that the inferred
type variable names of the DataCon can be arbitrary/unpredictable (as
they are chosen by GHC and depend on how unification proceeds), so it's
much better to use the more predictable TyCon type variable names.
- - - - -
95078d00 by sheaf at 2025-11-11T11:47:28-05:00
Backpack Rename: use explicit record construction
This commit updates the Backpack boilerplate in GHC.Iface.Rename to
use explicit record construction rather than record update. This makes
sure that the code stays up to date when the underlying constructors
change (e.g. new fields are added). The rationale is further explained
in Note [Prefer explicit record construction].
- - - - -
2bf36263 by sheaf at 2025-11-11T11:47:28-05:00
Store # eta binders in TyCon and use for Haddock
This commit stores the number of TyCon binders that were introduced by
eta-expansion (by the function GHC.Tc.Gen.HsType.splitTyConKind).
This is then used to pretty-print the TyCon as the user wrote it, e.g.
for
type Effect :: (Type -> Type) -> Type -> Type
data State s :: Effect where {..} -- arity 3
GHC will eta-expand the data declaration to
data State s a b where {..}
but also store in the 'TyCon' that the number of binders introduced by
this eta expansion is 2. This allows us, in
'Haddock.Convert.synifyTyConKindSig', to recover the original user-written
syntax, preserving the user's intent in Haddock documentation.
See Note [Inline kind signatures with GADTSyntax] in Haddock.Convert.
- - - - -
6c91582f by Matthew Pickering at 2025-11-11T11:48:12-05:00
driver: Properly handle errors during LinkNode steps
Previously we were not properly catching errors during the LinkNode step
(see T9930fail test).
This is fixed by wrapping the `LinkNode` action in `wrapAction`, the
same handler which is used for module compilation.
Fixes #26496
- - - - -
e1e1eb32 by Matthew Pickering at 2025-11-11T11:48:54-05:00
driver: Remove unecessary call to hscInsertHPT
This call was left-over from e9445c013fbccf9318739ca3d095a3e0a2e1be8a
If you follow the functions which call `upsweep_mod`, they immediately
add the interface to the HomePackageTable when `upsweep_mod` returns.
- - - - -
b22777d4 by ARATA Mizuki at 2025-11-11T11:49:44-05:00
LLVM backend: Pass the +evex512 attribute to LLVM 18+ if -mavx512f is set
The newer LLVM requires the +evex512 attribute to enable use of ZMM registers.
LLVM exhibits a backward-compatible behavior if the cpu is `x86-64`, but not if `penryn`.
Therefore, on macOS, where the cpu is set to `penryn`, we need to explicitly pass +evex512.
Fixes #26410
- - - - -
6ead7d06 by Vladislav Zavialov at 2025-11-11T11:50:26-05:00
Comments only in GHC.Parser.PostProcess.Haddock
Remove outdated Note [Register keyword location], as the issue it describes
was addressed by commit 05eb50dff2fcc78d025e77b9418ddb369db49b9f.
- - - - -
43fa8be8 by sheaf at 2025-11-11T11:51:18-05:00
localRegistersConflict: account for assignment LHS
This commit fixes a serious oversight in GHC.Cmm.Sink.conflicts,
specifically the code that computes which local registers conflict
between an assignment and a Cmm statement.
If we have:
assignment: <local_reg> = <expr>
node: <local_reg> = <other_expr>
then clearly the two conflict, because we cannot move one statement past
the other, as they assign two different values to the same local
register. (Recall that 'conflicts (local_reg,expr) node' is False if and
only if the assignment 'local_reg = expr' can be safely commuted past
the statement 'node'.)
The fix is to update 'GHC.Cmm.Sink.localRegistersConflict' to take into
account the following two situations:
(1) 'node' defines the LHS local register of the assignment,
(2) 'node' defines a local register used in the RHS of the assignment.
The bug is precisely that we were previously missing condition (1).
Fixes #26550
- - - - -
79dfcfe0 by sheaf at 2025-11-11T11:51:18-05:00
Update assigned register format when spilling
When we come to spilling a register to put new data into it, in
GHC.CmmToAsm.Reg.Linear.allocRegsAndSpill_spill, we need to:
1. Spill the data currently in the register. That is, do a spill
with a format that matches what's currently in the register.
2. Update the register assignment, allocating a virtual register to
this real register, but crucially **updating the format** of this
assignment.
Due to shadowing in the Haskell code for allocRegsAndSpill_spill, we
were mistakenly re-using the old format. This could lead to a situation
where:
a. We were using xmm6 to store a Double#.
b. We want to store a DoubleX2# into xmm6, so we spill the current
content of xmm6 to the stack using a scalar move (correct).
c. We update the register assignment, but we fail to update the format
of the assignment, so we continue to think that xmm6 stores a
Double# and not a DoubleX2#.
d. Later on, we need to spill xmm6 because it is getting clobbered by
another instruction. We then decide to only spill the lower 64 bits
of the register, because we still think that xmm6 only stores a
Double# and not a DoubleX2#.
Fixes #26542
- - - - -
aada5db9 by ARATA Mizuki at 2025-11-11T11:52:07-05:00
Fix the order of spill/reload instructions
The AArch64 NCG could emit multiple instructions for a single spill/reload,
but their order was not consistent between the definition and a use.
Fixes #26537
Co-authored-by: sheaf <sam.derbyshire(a)gmail.com>
- - - - -
64ec82ff by Andreas Klebinger at 2025-11-11T11:52:48-05:00
Add hpc to release script
- - - - -
741da00c by Ben Gamari at 2025-11-12T03:38:20-05:00
template-haskell: Better describe getQ semantics
Clarify that the state is a type-indexed map, as suggested by #26484.
- - - - -
8b080e04 by ARATA Mizuki at 2025-11-12T03:39:11-05:00
Fix incorrect markups in the User's Guide
* Correct markup for C--: "C-\-" in reST
* Fix internal links
* Fix code highlighting
* Fix inline code: Use ``code`` rather than `code`
* Remove extra backslashes
Fixes #16812
Co-authored-by: sheaf <sam.derbyshire(a)gmail.com>
- - - - -
3aef97ac by Simon Peyton Jones at 2025-11-14T23:40:18+00:00
Add a fast-path for args=[] to occAnalApp
In the common case of having not arguments, occAnalApp
was doing redundant work.
- - - - -
769ebde8 by Simon Peyton Jones at 2025-11-14T23:48:08+00:00
Fix a performance hole in the occurrence analyser
As #26425 showed, the clever stuff in
Note [Occurrence analysis for join points]
does a lot of duplication of usage details. This patch
improved matters with a little fancy footwork. It is
described in the new (W4) of the same Note.
Compile-time allocations go down slightly. Here are the changes
of +/- 0.5% or more:
T13253(normal) 329,369,244 326,395,544 -0.9%
T13253-spj(normal) 66,410,496 66,095,864 -0.5%
T15630(normal) 129,797,200 128,663,136 -0.9%
T15630a(normal) 129,212,408 128,027,560 -0.9%
T16577(normal) 6,756,706,896 6,723,028,512 -0.5%
T18282(normal) 128,462,070 125,808,584 -2.1% GOOD
T18698a(normal) 208,418,305 202,037,336 -3.1% GOOD
T18730(optasm) 136,981,756 136,208,136 -0.6%
T18923(normal) 58,103,088 57,745,840 -0.6%
T19695(normal) 1,386,306,272 1,365,609,416 -1.5%
T26425(normal) 3,344,402,957 2,457,811,664 -26.5% GOOD
T6048(optasm) 79,763,816 79,212,760 -0.7%
T9020(optasm) 225,278,408 223,682,440 -0.7%
T9961(normal) 303,810,717 300,729,168 -1.0% GOOD
geo. mean -0.5%
minimum -26.5%
maximum +0.4%
Metric Decrease:
T18282
T18698a
T26425
T9961
- - - - -
115 changed files:
- .gitlab/rel_eng/upload_ghc_libs.py
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Literals.hs
- compiler/GHC/Cmm/Sink.hs
- compiler/GHC/CmmToAsm/Reg/Linear.hs
- compiler/GHC/CmmToAsm/Reg/Liveness.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Rename.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Types/Basic.hs
- compiler/GHC/Types/Unique/FM.hs
- compiler/GHC/Types/Unique/Set.hs
- compiler/GHC/Types/Var/Env.hs
- docs/users_guide/bugs.rst
- docs/users_guide/debug-info.rst
- docs/users_guide/debugging.rst
- docs/users_guide/extending_ghc.rst
- docs/users_guide/exts/arrows.rst
- docs/users_guide/exts/derive_any_class.rst
- docs/users_guide/exts/deriving_extra.rst
- docs/users_guide/exts/deriving_inferred.rst
- docs/users_guide/exts/deriving_strategies.rst
- docs/users_guide/exts/gadt.rst
- docs/users_guide/exts/generics.rst
- docs/users_guide/exts/overloaded_labels.rst
- docs/users_guide/exts/overloaded_strings.rst
- docs/users_guide/exts/pattern_synonyms.rst
- docs/users_guide/exts/poly_kinds.rst
- docs/users_guide/exts/primitives.rst
- docs/users_guide/exts/rank_polymorphism.rst
- docs/users_guide/exts/rebindable_syntax.rst
- docs/users_guide/exts/required_type_arguments.rst
- docs/users_guide/exts/scoped_type_variables.rst
- docs/users_guide/exts/standalone_deriving.rst
- docs/users_guide/exts/template_haskell.rst
- docs/users_guide/exts/tuple_sections.rst
- docs/users_guide/exts/type_data.rst
- docs/users_guide/exts/type_defaulting.rst
- docs/users_guide/gone_wrong.rst
- docs/users_guide/hints.rst
- docs/users_guide/javascript.rst
- docs/users_guide/phases.rst
- docs/users_guide/profiling.rst
- docs/users_guide/separate_compilation.rst
- docs/users_guide/using.rst
- docs/users_guide/wasm.rst
- docs/users_guide/win32-dlls.rst
- libraries/ghc-internal/src/GHC/Internal/TH/Monad.hs
- libraries/os-string
- libraries/unix
- testsuite/tests/backpack/should_fail/T19244a.stderr
- + testsuite/tests/codeGen/should_run/T26537.hs
- + testsuite/tests/codeGen/should_run/T26537.stdout
- testsuite/tests/codeGen/should_run/all.T
- testsuite/tests/dependent/should_fail/T11334b.stderr
- testsuite/tests/generics/T10604/T10604_deriving.stderr
- testsuite/tests/ghc-e/should_fail/T9930fail.stderr
- testsuite/tests/ghc-e/should_fail/all.T
- testsuite/tests/ghci.debugger/scripts/print012.stdout
- testsuite/tests/ghci/scripts/T10321.stdout
- testsuite/tests/ghci/scripts/T24459.stdout
- testsuite/tests/ghci/scripts/T7730.stdout
- testsuite/tests/ghci/scripts/ghci065.stdout
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.hs
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/rename/should_fail/rnfail055.stderr
- testsuite/tests/saks/should_compile/saks023.stdout
- testsuite/tests/saks/should_compile/saks034.stdout
- testsuite/tests/saks/should_compile/saks035.stdout
- testsuite/tests/showIface/Makefile
- + testsuite/tests/showIface/T26246a.hs
- + testsuite/tests/showIface/T26246a.stdout
- testsuite/tests/showIface/all.T
- + testsuite/tests/simd/should_run/T26410_ffi.hs
- + testsuite/tests/simd/should_run/T26410_ffi.stdout
- + testsuite/tests/simd/should_run/T26410_ffi_c.c
- + testsuite/tests/simd/should_run/T26410_prim.hs
- + testsuite/tests/simd/should_run/T26410_prim.stdout
- + testsuite/tests/simd/should_run/T26542.hs
- + testsuite/tests/simd/should_run/T26542.stdout
- + testsuite/tests/simd/should_run/T26550.hs
- + testsuite/tests/simd/should_run/T26550.stdout
- testsuite/tests/simd/should_run/all.T
- testsuite/tests/typecheck/T16127/T16127.stderr
- testsuite/tests/typecheck/should_compile/T22560d.stdout
- testsuite/tests/typecheck/should_fail/T15629.stderr
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/html-test/ref/Bug1004.html
- utils/haddock/html-test/ref/Bug1050.html
- + utils/haddock/html-test/ref/Bug26246.html
- utils/haddock/html-test/ref/Bug85.html
- utils/haddock/html-test/ref/Bug923.html
- utils/haddock/html-test/ref/BundledPatterns.html
- utils/haddock/html-test/ref/BundledPatterns2.html
- utils/haddock/html-test/ref/ConstructorPatternExport.html
- utils/haddock/html-test/ref/GADTRecords.html
- utils/haddock/html-test/ref/LinearTypes.html
- utils/haddock/html-test/ref/PromotedTypes.html
- + utils/haddock/html-test/src/Bug26246.hs
- utils/haddock/latex-test/ref/LinearTypes/LinearTypes.tex
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dfa7915ac104c4d94a003b7f274582…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dfa7915ac104c4d94a003b7f274582…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/io-manager-deadlock-detection] 191 commits: Handle heap allocation failure in I/O primops
by Duncan Coutts (@dcoutts) 14 Nov '25
by Duncan Coutts (@dcoutts) 14 Nov '25
14 Nov '25
Duncan Coutts pushed to branch wip/io-manager-deadlock-detection at Glasgow Haskell Compiler / GHC
Commits:
62ae97de by Duncan Coutts at 2025-09-12T13:23:33-04:00
Handle heap allocation failure in I/O primops
The current I/O managers do not use allocateMightFail, but future ones
will. To support this properly we need to be able to return to the
primop with a failure. We simply use a bool return value.
Currently however, we will just throw an exception rather than calling
the GC because that's what all the other primops do too.
For the general issue of primops invoking GC and retrying, see
https://gitlab.haskell.org/ghc/ghc/-/issues/24105
- - - - -
cb9093f5 by Duncan Coutts at 2025-09-12T13:23:33-04:00
Move (and rename) scheduleStartSignalHandlers into RtsSignals.h
Previously it was a local helper (static) function in Schedule.c.
Rename it to startPendingSignalHandlers and deifine it as an inline
header function in RtsSignals.h. So it should still be fast.
Each (new style) I/O manager is going to need to do the same, so eliminating
the duplication now makes sense.
- - - - -
9736d44a by Duncan Coutts at 2025-09-12T13:23:33-04:00
Reduce detail in printThreadBlockage I/O blocking cases
The printThreadBlockage is used in debug tracing output.
For the cases BlockedOn{Read,Write,Delay} the output previously included
the fd that was being waited on, and the delay target wake time.
Superficially this sounds useful, but it's clearly not that useful
because it was already wrong for the Win32 non-threaded I/O manager. In
that situation it will print garbage (the async_result pointer, cast to
a fd or a time).
So given that it apparently never mattered that the information was
accurate, then it's hardly a big jump to say it doesn't matter if it is
present at all.
A good reason to remove it is that otherwise we have to make a new
API and a per-I/O manager implementation to fetch the information. And
for some I/O manager implementations, this information is not available.
It is not available in the win32 non-threaded I/O manager. And for some
future Linux ones, there is no need for the fd to be stored, so storing
it would be just extra space used for very little gain.
So the simplest thing is to just remove the detail.
- - - - -
bc0f2d5d by Duncan Coutts at 2025-09-12T13:23:33-04:00
Add TimeoutQueue.{c,h} and corresponding tests
A data structure used to efficiently manage a collection of timeouts.
It is a priority queue based on absolute expiry time. It uses 64bit
high-precision Time for the keys. The values are normal closures which
allows for example using MVars for unblocking.
It is common in many applications for timeouts to be created and then
deleted or altered before they expire. Thus the choice of data structure
for timeouts should support this efficiently. The implementation choice
here is a leftist heap with the extra feature that it supports deleting
arbitrary elements, provided the caller retain a pointer to the element.
While the deleteMin operation takes O(log n) time, as in all heap
structures, the delete operation for arbitrary elements /typically/
takes O(1), and only O(log n) in the worst case. In practice, when
managing thousands of timeouts it can be a factor of 10 faster to delete
a random timeout queue element than to remove the minimum element. This
supports the common use case.
The plan is to use it in some of the RTS-side I/O managers to support
their timer functionality. In this use case the heap value will be an
MVar used for each timeout to unblock waiting threads.
- - - - -
d1679c9d by Duncan Coutts at 2025-09-12T13:23:33-04:00
Add ClosureTable.{c,h} and corresponding tests
A table of pointers to closures on the GC heap with stable indexes.
It provides O(1) alloc, free and lookup. The table can be expanded
using a simple doubling strategy: in which case allocation is typically
O(1) and occasionally O(n) for overall amortised O(1). No shrinking is
used.
The table itself is heap allocated, and points to other heap objects.
As such it's necessary to use markClosureTable to ensure the table is
used as a GC root to keep the table entries alive, and maintain proper
pointers to them as the GC moves heap objects about.
It is designed to be allocated and accesses exclusively from a single
capability, enabling it to work without any locking. It is thus similar
to the StablePtr table, but per-capability which removes the need for
locking. It _should_ also provide lower GC pause times with the
non-moving GC by spending only O(1) time in markClosureTable, vs O(n)
for markStablePtrTable.
The plan is to use it in some of the I/O managers to keep track of
in-flight I/O operations (but not timers). This allows the tracking
info to be kept on the (unpinned) GC heap, and shared with Haskell
code, and by putting a pointer to the tracking information in a table,
the index remains stable and can be passed via foreign code (like the
kernel).
- - - - -
78cb8dd5 by Duncan Coutts at 2025-09-12T13:23:33-04:00
Add the StgAsyncIOOp closure type
This is intended to be used by multiple I/O managers to help with
tracking in-flight I/O operations.
It is called asynchronous because from the point of view of the RTS we
have many such operations in progress at once. From the point of view of
a Haskell thread of course it can look synchronous.
- - - - -
a2839896 by Duncan Coutts at 2025-09-12T13:23:33-04:00
Add StgAsyncIOOp and StgTimeoutQueue to tso->block_info
These will be used by new I/O managers, for threads blocked on I/O or
timeouts.
- - - - -
fdc2451c by Duncan Coutts at 2025-09-12T13:23:33-04:00
Add a new I/O manager based on poll()
This is a proof of concept I/O manager, to show how to add new ones
neatly, using the ClosureTable and TimeoutQueue infrastructure.
It uses the old unix poll() API, so it is of course limited in
performance by that, but it should have the benefit of wide
compatibility. Also we neatly avoid a name clash with the existing
select() I/O manager.
Compared to the select() I/O manager:
1. beause it uses poll() it is not limited to 1024 file descriptors
(but it's still O(n) so don't expect great performance);
2. it should have much faster threadDelay (when using it in lots of
threads at once) because it's based on the new TimeoutQueue which is
O(log n) rather than O(n).
Some of the code related to timers/timouts is put into a shared module
rts/posix/Timeout.{h,c} since it is intended to be shared with other
similar I/O managers.
- - - - -
6c273b76 by Duncan Coutts at 2025-09-12T13:23:34-04:00
Document the I/O managers in the user guide
and note the new poll I/O manager in the release notes.
- - - - -
824fab74 by Duncan Coutts at 2025-09-12T13:23:34-04:00
Use the poll() I/O manager by default
That is, for the non-threaded RTS, prefer the poll I/O manager over the
legacy select() one, if both can be enabled.
This patch is primarily for CI testing, so we should probably remove
this patch before merging. We can change defaults later after wider
testing and feedback.
- - - - -
39392532 by Luite Stegeman at 2025-09-12T13:24:16-04:00
Support larger unboxed sums
Change known constructor encoding for sums in interfaces to use
11 bits for both the arity and the alternative (up from 8 and 6,
respectively)
- - - - -
2af12e21 by Luite Stegeman at 2025-09-12T13:24:16-04:00
Decompose padding smallest-first in Cmm toplevel data constructors
This makes each individual padding value aligned
- - - - -
418fa78f by Luite Stegeman at 2025-09-12T13:24:16-04:00
Use slots smaller than word as tag for smaller unboxed sums
This packs unboxed sums more efficiently by allowing
Word8, Word16 and Word32 for the tag field if the number of
constructors is small enough
- - - - -
8d7e912f by Rodrigo Mesquita at 2025-09-12T17:57:24-04:00
ghc-toolchain: Use ByteOrder rather than new Endianness
Don't introduce a duplicate datatype when the previous one is equivalent
and already used elsewhere. This avoids unnecessary translation between
the two.
- - - - -
7d378476 by Rodrigo Mesquita at 2025-09-12T17:57:24-04:00
Read Toolchain.Target files rather than 'settings'
This commit makes GHC read `lib/targets/default.target`, a file with a
serialized value of `ghc-toolchain`'s `GHC.Toolchain.Target`.
Moreover, it removes all the now-redundant entries from `lib/settings`
that are configured as part of a `Target` but were being written into
`settings`.
This makes it easier to support multiple targets from the same compiler
(aka runtime retargetability). `ghc-toolchain` can be re-run many times
standalone to produce a `Target` description for different targets, and,
in the future, GHC will be able to pick at runtime amongst different
`Target` files.
This commit only makes it read the default `Target` configured in-tree
or configured when installing the bindist.
The remaining bits of `settings` need to be moved to `Target` in follow
up commits, but ultimately they all should be moved since they are
per-target relevant.
Fixes #24212
On Windows, the constant overhead of parsing a slightly more complex
data structure causes some small-allocation tests to wiggle around 1 to
2 extra MB (1-2% in these cases).
-------------------------
Metric Increase:
MultiLayerModulesTH_OneShot
T10421
T10547
T12234
T12425
T13035
T18140
T18923
T9198
TcPlugin_RewritePerf
-------------------------
- - - - -
e0780a16 by Rodrigo Mesquita at 2025-09-12T17:57:24-04:00
ghc-toolchain: Move TgtHasLibm to per-Target file
TargetHasLibm is now part of the per-target configuration
Towards #26227
- - - - -
8235dd8c by Rodrigo Mesquita at 2025-09-12T17:57:24-04:00
ghc-toolchain: Move UseLibdw to per-Target file
To support DWARF unwinding, the RTS must be built with the -f+libdw flag
and with the -DUSE_LIBDW macro definition. These flags are passed on
build by Hadrian when --enable-dwarf-unwinding is specified at configure
time.
Whether the RTS was built with support for DWARF is a per-target
property, and as such, it was moved to the per-target
GHC.Toolchain.Target.Target file.
Additionally, we keep in the target file the include and library paths
for finding libdw, since libdw should be checked at configure time (be
it by configure, or ghc-toolchain, that libdw is properly available).
Preserving the user-given include paths for libdw facilitates in the
future building the RTS on demand for a given target (if we didn't keep
that user input, we couldn't)
Towards #26227
- - - - -
d5ecf2e8 by Rodrigo Mesquita at 2025-09-12T17:57:25-04:00
ghc-toolchain: Make "Support SMP" a query on a Toolchain.Target
"Support SMP" is merely a function of target, so we can represent it as
such in `ghc-toolchain`.
Hadrian queries the Target using this predicate to determine how to
build GHC, and GHC queries the Target similarly to report under --info
whether it "Support SMP"
Towards #26227
- - - - -
e07b031a by Rodrigo Mesquita at 2025-09-12T17:57:25-04:00
ghc-toolchain: Make "tgt rts linker only supports shared libs" function on Target
Just like with "Support SMP", "target RTS linker only supports shared
libraries" is a predicate on a `Target` so we can just compute it when
necessary from the given `Target`.
Towards #26227
- - - - -
14123ee6 by Simon Peyton Jones at 2025-09-12T17:58:07-04:00
Solve forall-constraints via an implication, again
In this earlier commit:
commit 953fd8f1dc080f1c56e3a60b4b7157456949be29
Author: Simon Peyton Jones <simon.peytonjones(a)gmail.com>
Date: Mon Jul 21 10:06:43 2025 +0100
Solve forall-constraints immediately, or not at all
I used a all-or-nothing strategy for quantified constraints
(aka forall-constraints). But alas that fell foul of #26315,
and #26376.
So this MR goes back to solving a quantified constraint by
turning it into an implication; UNLESS we are simplifying
constraints from a SPECIALISE pragma, in which case the
all-or-nothing strategy is great. See:
Note [Solving a Wanted forall-constraint]
Other stuff in this MR:
* TcSMode becomes a record of flags, rather than an enumeration
type; much nicer.
* Some fancy footwork to avoid error messages worsening again
(The above MR made them better; we want to retain that.)
See `GHC.Tc.Errors.Ppr.pprQCOriginExtra`.
-------------------------
Metric Decrease:
T24471
-------------------------
- - - - -
e6c192e2 by Simon Peyton Jones at 2025-09-12T17:58:07-04:00
Add a test case for #26396
...same bug ast #26315
- - - - -
8f3d80ff by Luite Stegeman at 2025-09-13T08:43:09+02:00
Use mkVirtHeapOffsets for reconstructing terms in RTTI
This makes mkVirtHeapOffsets the single source of truth for
finding field offsets in closures.
- - - - -
eb389338 by Luite Stegeman at 2025-09-13T08:43:09+02:00
Sort non-pointer fields by size for more efficient packing
This sorts non-pointer fields in mkVirtHeapOffsets, always
storing the largest field first. The relative order of
equally sized fields remains unchanged.
This reduces wasted padding/alignment space in closures with
differently sized fields.
- - - - -
99b233f4 by Alison at 2025-09-13T16:51:04-04:00
ghc-heap: Fix race condition with profiling builds
Apply the same fix from Closures.hs (64fd0fac83) to Heap.hs by adding
empty imports to make way-dependent dependencies visible to `ghc -M`.
Fixes #15197, #26407
- - - - -
77deaa7a by Cheng Shao at 2025-09-14T21:29:45-04:00
hadrian: build in-tree gmp with -fvisibility=hidden
When hadrian builds in-tree gmp, it should build the shared objects
with -fvisibility=hidden. The gmp symbols are only used by bignum
logic in ghc-internal and shouldn't be exported by the ghc-internal
shared library. We should always strive to keep shared library symbol
table lean, which benefits platforms with slow dynamic linker or even
hard limits about how many symbols can be exported (e.g. macos dyld,
win32 dll and wasm dyld).
- - - - -
42a18960 by Cheng Shao at 2025-09-14T21:30:26-04:00
Revert "wasm: add brotli compression for ghci browser mode"
This reverts commit 731217ce68a1093b5f9e26a07d5bd2cdade2b352.
Benchmarks show non-negligible overhead when browser runs on the same
host, which is the majority of actual use cases.
- - - - -
e6755b9f by Cheng Shao at 2025-09-14T21:30:26-04:00
wasm: remove etag logic in ghci browser mode web server
This commit removes the etag logic in dyld script's ghci browser mode
web server. It was meant to support caching logic of wasm shared
libraries, but even if the port is manually specified to make caching
even relevant, for localhost the extra overhead around etag logic is
simply not worth it according to benchmarks.
- - - - -
ac5859b9 by sheaf at 2025-09-16T14:58:38-04:00
Add 'Outputable Natural' instance
This commit adds an Outputable instance for the Natural natural-number type,
as well as a "natural :: Natural -> SDoc" function that mirrors the existing
"integer" function.
- - - - -
d48ebc23 by Cheng Shao at 2025-09-16T14:59:18-04:00
autoconf: emit warning instead of error for FIND_PYTHON logic
This patch makes FIND_PYTHON logic emit warning instead of error, so
when the user doesn't expect to run the testsuite driver (especially
when installing a bindist), python would not be mandatory. Fixes #26347.
- - - - -
54b5950e by Sylvain Henry at 2025-09-17T04:45:18-04:00
Print fully qualified unit names in name mismatch
It's more user-friendly to directly print the right thing instead of
requiring the user to retry with the additional `-dppr-debug` flag.
- - - - -
403cb665 by Ben Gamari at 2025-09-17T04:46:00-04:00
configure: Fix consistency between distrib and source CC check
Previously distrib/configure.ac did not
include `cc`.
Closes #26394.
- - - - -
2dcd4cb9 by Oleg Grenrus at 2025-09-17T04:46:41-04:00
Use isPrint in showUnique
The comment say
```
-- Avoid emitting non-printable characters in pretty uniques. See #25989.
```
so let the code do exactly that.
There are tags (at least : and 0 .. 9) which weren't in A .. z range.
- - - - -
e5dd754b by Oleg Grenrus at 2025-09-17T04:46:42-04:00
Shorten in-module links in hyperlinked source
Instead of href="This.Module#ident" to just "#ident"
- - - - -
63189b2c by Oleg Grenrus at 2025-09-17T04:46:42-04:00
Use showUnique in internalAnchorIdent
Showing the key of Unique as a number is generally not a great idea.
GHC Unique has a tag in high bits, so the raw number is unnecessarily
big.
So now we have
```html
<a href="#l-rvgK"><span class="hs-identifier hs-var hs-var">bar</span></a>
```
instead of
```html
<a href="#local-6989586621679015689"><span class="hs-identifier hs-var hs-var">bar</span></a>
```
Together with previous changes of shorter intra-module links the effect
on compressed files is not huge, that is expected as we simply remove
repetitive contents which pack well.
```
12_694_206 Agda-2.9.0-docs-orig.tar.gz
12_566_065 Agda-2.9.0-docs.tar.gz
```
However when unpacked, the difference can be significant,
e.g. Agda's largest module source got 5% reduction:
```
14_230_117 Agda.Syntax.Parser.Parser.html
13_422_109 Agda.Syntax.Parser.Parser.html
```
The whole hyperlinked source code directory got similar reduction
```
121M Agda-2.9.0-docs-orig/src
114M Agda-2.9.0-docs/src
```
For the reference, sources are about 2/3 of the generated haddocks
```
178M Agda-2.9.0-docs-old
172M Agda-2.9.0-docs
```
so we get around 3.5% size reduction overall. Not bad for a small local
changes.
- - - - -
6f63f57b by Stefan Schulze Frielinghaus at 2025-09-17T04:47:22-04:00
rts: Fix alignment for gen_workspace #26334
After a0fa4941903272c48b050d24e93eec819eff51bd bootstrap is broken on
s390x and errors out with
rts/sm/GCThread.h:207:5: error:
error: alignment of array elements is greater than element size
207 | gen_workspace gens[];
| ^~~~~~~~~~~~~
The alignment constraint is applied via the attribute to the type
gen_workspace and leaves the underlying type struct gen_workspace_
untouched. On Aarch64, x86, and s390x the struct has a size of 128
bytes. On Aarch64 and x86 the alignments of 128 and 64 are divisors of
the size, respectively, which is why the type is a viable member type
for an array. However, on s390x, the alignment is 256 and therefore is
not a divisor of the size and hence cannot be used for arrays.
Basically I see two fixes here. Either decrease the alignment
requirement on s390x, or by applying the alignment constraint on the
struct itself. The former might affect performance as noted in
a0fa4941903272c48b050d24e93eec819eff51bd. The latter introduces padding
bits whenever necessary in order to ensure that
sizeof(gen_workspace[N])==N*sizeof(gen_workspace) holds which is done by
this patch.
- - - - -
06d25623 by Cheng Shao at 2025-09-17T19:32:27-04:00
ghci: add :shell command
This patch adds a new :shell command to ghci which works similarly to
:!, except it guarantees to run the command via sh -c. On POSIX hosts
the behavior is identical to :!, but on Windows it uses the msys2
shell instead of system cmd.exe shell. This is convenient when writing
simple ghci scripts that run simple POSIX commands, and the behavior
can be expected to be coherent on both Windows and POSIX.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
186054f7 by Cheng Shao at 2025-09-17T19:32:27-04:00
testsuite: remove legacy :shell trick
This commit makes use of the built-in :shell functionality in ghci in
the test cases, and remove the legacy :shell trick.
- - - - -
0a3a4aa3 by Cheng Shao at 2025-09-17T19:32:27-04:00
docs: document :shell in ghci
This commit documents the :shell command in ghci.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
a4ff12bb by Cheng Shao at 2025-09-17T19:33:09-04:00
ghc-internal: fix codepages program
codepages was not properly updated during the base -> ghc-internal
migration, this commit fixes it.
- - - - -
7e094def by Cheng Shao at 2025-09-17T19:33:09-04:00
ghc-internal: relax ucd2haskell cabal upper bounds
This commit relaxes ucd2haskell cabal upper bounds to make it runnable
via ghc 9.12/9.14.
- - - - -
7077c9f7 by Cheng Shao at 2025-09-17T19:33:09-04:00
ghc-internal: update to unicode 17.0.0
This commit updates the generated code in ghc-internal to match
unicode 17.0.0.
- - - - -
cef8938f by sheaf at 2025-09-17T19:34:09-04:00
Bad record update msg: allow out-of-scope datacons
This commit ensures that, when we encounter an invalid record update
(because no constructor exists which contains all of the record fields
mentioned in the record update), we graciously handle the situation in
which the constructors themselves are not in scope. In that case,
instead of looking up the constructors in the GlobalRdrEnv, directly
look up their GREInfo using the lookupGREInfo function.
Fixes #26391
- - - - -
a2d9d7c2 by sheaf at 2025-09-17T19:34:09-04:00
Improve Notes about disambiguating record updates
This commit updates the notes [Disambiguating record updates] and
[Type-directed record disambiguation], in particular adding more
information about the deprecation status of type-directed disambiguation
of record updates.
- - - - -
de44e69e by sheaf at 2025-09-19T05:16:51-04:00
Enable TcM plugins in initTc
This commit ensures that we run typechecker plugins and defaulting
plugins whenever we call initTc.
In particular, this ensures that the pattern-match checker, which calls
'initTcDsForSolver' which calls 'initTc', runs with typechecker plugins
enabled. This matters for situations like:
merge :: Vec n a -> Vec n a -> Vec (2 * n) a
merge Nil Nil = Nil
merge (a <: as) (b <: bs) = a :< (b <: merge as bs)
in which we need the typechecker plugin to run in order to tell us that
the Givens would be inconsistent in the additional equation
merge (_ <: _) Nil
and thus that the equation is not needed.
Fixes #26395
- - - - -
2c378ad2 by Cheng Shao at 2025-09-19T05:17:33-04:00
rel-eng: update fedora image to 42
This patch is a part of #25876 and updates fedora image to 42.
- - - - -
0a9d9ffc by Sylvain Henry at 2025-09-19T13:12:14-04:00
Fix output of T14999 (#23685)
Fix output of T14999 to:
- take into account the +1 offset to DW_AT_low_pc (see Note [Info Offset])
- always use Intel's syntax to force consistency: it was reported that
sometimes GDB prints `jmpq` instead of `jmp` with the AT&T syntax
- - - - -
1480872a by Vladislav Zavialov at 2025-09-19T13:12:54-04:00
Fix PREP_MAYBE_LIBRARY in prep_target_file.m4
This change fixes a configure error introduced in:
commit 8235dd8c4945db9cb03e3be3c388d729d576ed1e
ghc-toolchain: Move UseLibdw to per-Target file
Now the build no longer fails with:
acghc-toolchain: Failed to read a valid Target value from hadrian/cfg/default.target
- - - - -
d1d9e39e by Ben Gamari at 2025-09-19T18:24:52-04:00
StgToByteCode: Don't assume that data con workers are nullary
Previously StgToByteCode assumed that all data-con workers were of a
nullary representation. This is not a valid assumption, as seen
in #23210, where an unsaturated application of a unary data
constructor's worker resulted in invalid bytecode. Sadly, I have not yet
been able to reduce a minimal testcase for this.
Fixes #23210.
- - - - -
3eeecd50 by Ben Gamari at 2025-09-19T18:24:53-04:00
testsuite: Mark T23146* as unbroken
- - - - -
2e73f342 by sheaf at 2025-09-19T18:24:53-04:00
Add test for #26216
- - - - -
c2efb912 by Sven Tennie at 2025-09-19T18:25:36-04:00
Generate correct test header
This increases convenience when copying & pasting...
- - - - -
d2fb811e by Sven Tennie at 2025-09-19T18:25:36-04:00
foundation test: Fix shift amount (#26248)
Shift primops' results are only defined for shift amounts of 0 to word
size - 1. The approach is similar to testing div-like operations (which
have a constraint regarding zero operands.)
This was partly vibe coded (https://github.com/supersven/ghc/pull/1) but
then heavily refactored.
- - - - -
a62ce115 by Andreas Klebinger at 2025-09-19T18:26:18-04:00
Tweak jspace test
I've given it a longer timeout, and tweaked the test file generation
to speed it up a bit. Hopefully that is enough to make it constentily pass.
Last but not least it now also always uses three threads.
- - - - -
0f034942 by Cheng Shao at 2025-09-19T18:26:59-04:00
rts: remove obsolete CC_SUPPORTS_TLS logic
This patch removes obsolete CC_SUPPORTS_TLS logic throughout the rts,
given __thread is now uniformly supported by C toolchains of all
platforms we currently support.
- - - - -
ef705655 by Cheng Shao at 2025-09-19T18:27:41-04:00
rts: remove obsolete HAS_VISIBILITY_HIDDEN logic
This patch removes obsolete HAS_VISIBILITY_HIDDEN logic throughout the
rts, given __attribute__((visibility("hidden"))) is uniformly
supported by C toolchains of all platforms we currently support.
- - - - -
9fdc1f7d by Cheng Shao at 2025-09-19T18:28:21-04:00
rts: remove -O3 pragma hack in Hash.c
This patch removes an obsolete gcc pragma to specify -O3 in Hash.c.
Hadrian already passes the right flag.
- - - - -
b8cfa8f7 by Cheng Shao at 2025-09-19T18:29:01-04:00
rts: remove obsolete COMPILING_WINDOWS_DLL logic
This patch removes obsolete COMPILING_WINDOWS_DLL logic throughout the
rts. They were once used for compiling to win32 DLLs, but we haven't
been able to compile Haskell units to win32 DLLs for many years now,
due to PE format's restriction of no more than 65536 exported symbols
in a single DLL.
- - - - -
bb760611 by Cheng Shao at 2025-09-19T18:29:42-04:00
wasm: bump browser_wasi_shim to 0.4.2
This patch bumps the browser_wasi_shim dependency of wasm dyld script
to 0.4.2.
- - - - -
8b0940db by Cheng Shao at 2025-09-20T06:48:05-04:00
compiler: move Binary instance of Map to GHC.Utils.Binary
This patch moves `Binary` instance of `Map` from `haddock-api` to
`GHC.Utils.Binary`. This also allows us to remove a redundant instance
defined for `NameEntityInfo`, which is a type synonym for `Map`.
- - - - -
4a8fed75 by Vladislav Zavialov at 2025-09-20T06:48:47-04:00
Fix keyword in ExplicitNamespaces error message (#26418)
Consider this module header and the resulting error:
{-# LANGUAGE NoExplicitNamespaces #-}
module T26418 (data HeadC) where
-- error: [GHC-47007]
-- Illegal keyword 'type'
Previously, the error message would mention 'type' (as shown above),
even though the user wrote 'data'. This has now been fixed.
The error location has also been corrected: it is now reported at the
keyword position rather than at the position of the associated
import/export item.
- - - - -
867c2675 by Cheng Shao at 2025-09-20T06:49:28-04:00
wasm: fix dyld handling for forward declared GOT.func items
This patch fixes wasm shared linker's handling of forward declared
GOT.func items, see linked issue for details. Also adds T26430 test to
witness the fix. Fixes #26430.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
e7df6cc0 by Simon Peyton Jones at 2025-09-23T14:34:39-04:00
Improve pretty printer for HsExpr
Given a very deeply-nested application, it just kept printing
deeper and deeper. This small change makes it cut off.
Test is in #26330, but we also get a dramatic decrease in compile
time for perf/compiler/InstanceMatching:
InstanceMatching 4,086,884,584 1,181,767,232 -71.1% GOOD
Why? Because before we got a GIGANTIC error message that took
ages to pretty-print; now we get this much more civilised message
(I have removed some whitespace.)
Match.hs:1007:1: error:
• No instance for ‘Show (F001 a)’ arising from a use of ‘showsPrec’
• In the second argument of ‘showString’, namely
‘(showsPrec
11 b1
(GHC.Internal.Show.showSpace
(showsPrec
11 b2
(GHC.Internal.Show.showSpace
(showsPrec
11 b3
(GHC.Internal.Show.showSpace
(showsPrec
11 b4
(GHC.Internal.Show.showSpace
(showsPrec
11 b5
(GHC.Internal.Show.showSpace
(showsPrec
11 b6
(GHC.Internal.Show.showSpace (showsPrec ...)))))))))))))’
-----------------------
The main payload is
* At the start of `pprExpr`
* In the defn of `pprApp`
A little bit of refactoring:
* It turned out that we were setting the default cut-off depth to a
fixed value in two places, so changing one didn't change the other.
See defaultSDocDepth and defaultSDocCols
* I refactored `pprDeeperList` a bit so I could understand it better.
Because the depth calculation has changed, there are lots of small
error message wibbles.
Metric Decrease:
InstanceMatching
- - - - -
209f0158 by Simon Peyton Jones at 2025-09-23T14:34:39-04:00
Use Outputable.ellipsis rather than text "..."
- - - - -
64bb0e37 by Sylvain Henry at 2025-09-23T14:35:56-04:00
deriveConstants: automatically pass -fcommon CC flag (#26393)
By mistake we tried to use deriveConstants without passing
`--gcc-flag -fcommon` (which Hadrian does) and it failed.
This patch:
1. adds parsing support for constants stored in the .bss section (i.e.
when -fcommon isn't passed)
2. enables passing `-fcommon` automatically to the C compiler because
Windows requires this for subtle reasons
3. Documents the subtle reasons
(1) isn't strictly necessary because we always do (2) but it does no
harm and it is still useful if the CC flags ever contain -fno-common
- - - - -
afcdf92f by Oleg Grenrus at 2025-09-23T14:36:41-04:00
Don't wrap spaces in <span>s
Doing similar comparison as in 63189b2ceca07edf4e179f4180ca60d470c62cb3
With this change the gzipped documentation is now 2% smaller (previously 1%)
12_694_206 Agda-2.9.0-docs-orig.tar.gz
12_436_829 Agda-2.9.0-docs.tar.gz
Unzipped docs are 5% smaller (previously 3%)
178M Agda-2.9.0-docs-orig
169M Agda-2.9.0-docs
Individual hyperlinked sources are around 7-10% smaller (previously 5%)
(`Parser` module is generated by happy and has relatively little whitespace)
14_230_117 Agda.Syntax.Parser.Parser.html
13_220_758 Agda.Syntax.Parser.Parser.html
Agda's hyperlinked sources are 9% smaller now:
121M Agda-2.9.0-docs-orig/src
110M Agda-2.9.0-docs/src
- - - - -
67de53a6 by Cheng Shao at 2025-09-23T14:37:31-04:00
rts: remove obsolete __GNUC__ related logic
This patch removes obsolete `__GNUC__` related logic, given on any
currently supported platform and toolchain, `__GNUC__ >= 4` is
universally true. Also pulls some other weeds and most notably, use
`__builtin___clear_cache` for clang as well, since clang has supported
this gcc intrinsic since 2014, see
https://github.com/llvm/llvm-project/commit/c491a8d4577052bc6b3b4c72a7db6a7….
- - - - -
c4d32493 by Sven Tennie at 2025-09-23T20:40:57-04:00
RV64: Fix: Add missing truncation to MO_S_Shr (#26248)
Sub-double word (<W64) registers need to be truncated after the
operation.
- - - - -
41dce477 by Sven Tennie at 2025-09-23T20:40:57-04:00
RV64: Cleanup shift emitting cases/code
Remove overlapping cases to make the shift logic easier to understand.
- - - - -
0a601c30 by Alex Washburn at 2025-09-23T20:41:41-04:00
Correcting LLVM linking of Intel BMI intrinsics pdep{8,16} and pext{8,16}.
This patch fixes #26065.
The LLVM interface does not expose bindings to:
- llvm.x86.bmi.pdep.8
- llvm.x86.bmi.pdep.16
- llvm.x86.bmi.pext.8
- llvm.x86.bmi.pext.16
So calls are instead made to llvm.x86.bmi.{pdep,pext}.32 in these cases,
with pre/post-operation truncation to constrain the logical value range.
- - - - -
89e8ff3d by Peng Fan at 2025-09-23T20:42:37-04:00
NCG/LA64: Implement MO_BSwap and MO_BRev with bit-manipulation Instructions
- - - - -
50f6be09 by Sylvain Henry at 2025-09-23T20:43:29-04:00
Allow Core plugins to access unoptimized Core (#23337)
Make the first simple optimization pass after desugaring a real CoreToDo
pass. This allows CorePlugins to decide whether they want to be executed
before or after this pass.
- - - - -
30ef0aac by Simon Hengel at 2025-09-23T20:44:12-04:00
docs: Fix typo in scoped_type_variables.rst
- - - - -
f8919262 by Cheng Shao at 2025-09-23T20:44:54-04:00
ghci: fix bootstrapping with 9.12.3-rc1 and above
This patch fixes bootstrapping GHC with 9.12.3-rc1 and above. ghci
defines `Binary` instance for `HalfWord` in `ghc-heap`, which is a
proper `newtype` in 9.14 and starting from 9.12.3. Given we don't
build `ghc-heap` in stage0, we need to fix this predicate so that it
corresponds to the boot ghc versions that contain the right version of
`ghc-heap`.
- - - - -
a7f15858 by sheaf at 2025-09-24T09:49:53-04:00
User's guide: clarify optimisation of INLINABLE unfoldings
This updates the user's guide section on INLINABLE pragmas to explain how
the unfoldings of inlineable functions are optimised. The user's guide incorrectly
stated that the RHS was not optimised at all, but this is not true. Instead, GHC
is careful about phase control to optmise the RHS while retaining the guarantee
that GHC behaves as if the original RHS had been written.
- - - - -
495886d9 by Rodrigo Mesquita at 2025-09-24T09:50:35-04:00
cleanup: Delete historical artifact of COMPILING_WINDOWS_DLL
Namely, drop the obsolete
- DLL_IMPORT_RTS
- DLL_IMPORT_DATA_VAR
- DLL_IMPORT_DATA_VARNAME
- DLL_IMPORT_DATA_REF
These macros were not doing anything and placed inconsistently
Looking at the git logs reveal these macros were used to support
dynamic libraries on Win32, a feature that was dropped
in b8cfa8f741729ef123569fb321c4b2ab4a1a941c
This allows us to get rid of the rts/DLL.h file too.
- - - - -
5ae89054 by Sylvain Henry at 2025-09-24T17:07:00-04:00
Allow disabling builtin rules (#20298)
Add a way to disable built-in rules programmatically and with a debug flag.
I also took the opportunity to add a debug flag to disable bignum rules,
which was only possible programmatically (e.g. in a plugin).
- - - - -
135242ca by Rodrigo Mesquita at 2025-09-24T17:07:44-04:00
Don't use build CFLAGS and friends as target settings
In the GHC in tree configure, `CFLAGS`, `CXXFLAGS`, and similar tool
configuration flags apply to the BUILD phase of the compiler, i.e. to
the tools run to compile GHC itself.
Notably, they should /not/ be carried over to the Target settings, i.e.
these flags should /not/ apply to the tool which GHC invokes at runtime.
Fixes #25637
- - - - -
b418408b by Irene Knapp at 2025-09-25T09:47:54-04:00
Document etymology of "bind" as the name for `>>=`
It took me twenty years of contemplation to realize why it's called that.
I therefore feel that it may not be obvious to beginners.
- - - - -
e9c5e46f by Brandon Chinn at 2025-09-25T09:48:36-04:00
Fix tabs in string gaps (#26415)
Tabs in string gaps were broken in bb030d0d because previously, string gaps were manually parsed, but now it's lexed by the usual Alex grammar and post-processed after successful lexing.
It broke because of a discrepancy between GHC's lexer grammar and the Haskell Report. The Haskell Report includes tabs in whitechar:
whitechar → newline | vertab | space | tab | uniWhite
$whitechar used to include tabs until 18 years ago, when it was removed in order to exclude tabs from $white_no_nl in order to warn on tabs: 6e202120. In this MR, I'm adding \t back into $whitechar, and explicitly excluding \t from the $white_no_nl+ rule ignoring all whitespace in source code, which more accurately colocates the "ignore all whitespace except tabs, which is handled in the next line" logic.
As a side effect of this MR, tabs are now allowed in pragmas; currently, a pragma written as {-# \t LANGUAGE ... #-} is interpreted as the tab character being the pragma name, and GHC warns "Unrecognized pragma". With this change, tabs are ignored as whitespace, which more closely matches the Report anyway.
- - - - -
8bf5b309 by Cheng Shao at 2025-09-25T09:49:18-04:00
wasm: remove the --no-turbo-fast-api-calls hack from dynamic linker shebang
This patch removes the `--no-turbo-fast-api-calls` hack from the dyld
script shebang; it was used to workaround v8 fast call coredumps in
nodejs and no longer needed, and comes with a performance penalty,
hence the removal.
- - - - -
c1cab0c3 by Sylvain Henry at 2025-09-26T10:36:30-04:00
Revert "Add necessary flag for js linking"
This reverts commit 84f68e2231b2eddb2e1dc4e90af394ef0f2e803f.
This commit didn't have the expected effect. See discussion in #26290.
Instead we export HEAP8 and HEAPU8 from rts/js/mem.js
- - - - -
0a434a80 by Sylvain Henry at 2025-09-26T10:36:30-04:00
JS: export HEAPU8 (#26290)
This is now required by newer Emscripten versions.
- - - - -
b10296a9 by Andreas Klebinger at 2025-09-26T10:37:11-04:00
sizeExpr: Improve Tick handling.
When determining if we scrutinize a function argument we
now properly look through ticks. Fixes #26444.
- - - - -
d9e2a9a7 by mniip at 2025-09-26T16:00:50-04:00
rts: Refactor parsing of -h flags
We have a nontrivial amount of heap profiling flags available in the
non-profiled runtime, so it makes sense to reuse the parsing code
between the profiled and the non-profiled runtime, only restricting
which flags are allowed.
- - - - -
089e45aa by mniip at 2025-09-26T16:00:50-04:00
rts: Fix parsing of -h options with braces
When the "filter by" -h options were introduced in
bc210f7d267e8351ccb66972f4b3a650eb9338bb, the braces were mandatory.
Then in 3c22fb21fb18e27ce8d941069a6915fce584a526, the braces were made
optional. Then in d1ce35d2271ac8b79cb5e37677b1a989749e611c the brace
syntax stopped working, and no one seems to have noticed.
- - - - -
423f1472 by mniip at 2025-09-26T16:00:50-04:00
rts: add -hT<type> and -hi<table id> heap filtering options (#26361)
They are available in non-profiled builds.
Along the way fixed a bug where combining -he<era> and -hr<retainer>
would ignore whether the retainer matches or not.
- - - - -
4cda4785 by mniip at 2025-09-26T16:00:50-04:00
docs: Document -hT<type> and -hi<addr>
- - - - -
982ad30f by mniip at 2025-09-26T16:00:50-04:00
rts: Refactor dumping the heap census
Always do the printing of the total size right next to where the bucket
label is printed. This prevents accidentally printing a label without
the corresponding amount.
Fixed a bug where exactly this happened for -hi profile and the 0x0
(uncategorized) info table.
There is now also much more symmetry between fprintf(hp_file,...) and
the corresponding traceHeapProfSampleString.
- - - - -
8cbe006a by Cheng Shao at 2025-09-26T16:01:34-04:00
hadrian: fix GHC.Platform.Host generation for cross stage1
This patch fixes incorrectly GHC.Platform.Host generation logic for
cross stage1 in hadrian (#26449). Also adds T26449 test case to
witness the fix.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
0ddd0fdc by soulomoon at 2025-09-28T19:24:10-04:00
Remove hptAllInstances usage during upsweep
Previously, during the upsweep phase when
checking safe imports, we were loading the module
interface with runTcInteractive, which in turn calls
hptAllInstances. This accesses non-below modules
from the home package table.
Change the implementation of checkSafeImports
to use initTcWithGbl and loadSysInterface to load the
module interface, since we already have TcGblEnv at hand.
This eliminates the unnecessary use of runTcInteractive
and hptAllInstances during the upsweep phase.
- - - - -
e05c496c by Ben Gamari at 2025-09-28T19:24:59-04:00
base: Update changelog to reflect timing of IOPort# removal
This change will make 9.14 afterall.
- - - - -
bdc9d130 by Cheng Shao at 2025-09-28T19:25:45-04:00
rts: fix wasm JSFFI initialization constructor code
This commit fixes wasm JSFFI initialization constructor code so that
the constructor is self-contained and avoids invoking a fake
__main_argc_argv function. The previous approach of reusing
__main_void logic in wasi-libc saves a tiny bit of code, at the
expense of link-time trouble whenever GHC links a wasm module without
-no-hs-main, in which case the driver-generated main function would
clash with the definition here, resulting in a linker error. It's
simply better to avoid messing with the main function, and it would
additionally allow linking wasm32-wasi command modules that does make
use of synchronous JSFFI.
- - - - -
5d59fc8f by Cheng Shao at 2025-09-28T19:26:27-04:00
rts: provide stub implementations of ExecPage functions for wasm
This patch provides stub implementations of ExecPage functions for
wasm. They are never actually invoked at runtime for any non-TNTC
platform, yet they can cause link-time errors of missing symbols when
the GHCi.InfoTable module gets linked into the final wasm module (e.g.
a GHC API program).
- - - - -
a4d664c7 by Cheng Shao at 2025-09-29T17:29:22+02:00
compiler/ghci: replace the LoadDLL message with LoadDLLs
As a part of #25407, this commit changes the LoadDLL message to
LoadDLLs, which takes a list of DLL paths to load and returns the list
of remote pointer handles. The wasm dyld is refactored to take
advantage of LoadDLLs and harvest background parallelism. On other
platforms, LoadDLLs is based on a fallback codepath that does
sequential loading.
The driver is not actually emitting singular LoadDLLs message with
multiple DLLs yet, this is left in subsequent commits.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
c7fc4bae by Cheng Shao at 2025-09-29T17:29:22+02:00
driver: separate downsweep/upsweep phase in loadPackages'
This commit refactors GHC.Linker.Loader.loadPackages' to be separated
into downsweep/upsweep phases:
- The downsweep phase performs dependency analysis and generates a
list of topologically sorted packages to load
- The upsweep phase sequentially loads these packages by calling
loadPackage
This is a necessary refactoring to make it possible to make loading of
DLLs concurrent.
- - - - -
ab180104 by Cheng Shao at 2025-09-29T17:57:19+02:00
driver: emit single LoadDLLs message to load multiple DLLs
This commit refactors the driver so that it emits a single LoadDLLs
message to load multiple DLLs in GHC.Linker.Loader.loadPackages'.
Closes #25407.
-------------------------
Metric Increase:
MultiLayerModulesTH_OneShot
TcPlugin_RewritePerf
-------------------------
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
9c304ec0 by Sean D. Gillespie at 2025-09-29T19:57:07-04:00
Fix SIZED_BIN_OP_TY_INT casts in RTS interpreter
Correct `SIZED_BIN_OP_TY_INT` cast to integer. Previously, it cast
its second operand as its parameter `ty`. This does not currently
cause any issues, since we are only using it for bit shifts.
Fixes #26287
- - - - -
a1de535f by Luite Stegeman at 2025-09-30T18:40:28-04:00
rts: Fix lost wakeups in threadPaused for threads blocked on black holes
The lazy blackholing code in threadPaused could overwrite closures
that were already eagerly blackholed, and as such wouldn't have a
marked update frame. If the black hole was overwritten by its
original owner, this would lead to an undetected collision, and
the contents of any existing blocking queue being lost.
This adds a check for eagerly blackholed closures and avoids
overwriting their contents.
Fixes #26324
- - - - -
b7e21e49 by Luite Stegeman at 2025-09-30T18:40:28-04:00
rts: push the correct update frame in stg_AP_STACK
The frame contains an eager black hole (__stg_EAGER_BLACKHOLE_info) so
we should push an stg_bh_upd_frame_info instead of an stg_upd_frame_info.
- - - - -
02a7c18a by Cheng Shao at 2025-09-30T18:41:27-04:00
ghci: fix lookupSymbolInDLL behavior on wasm
This patch fixes lookupSymbolInDLL behavior on wasm to return Nothing
instead of throwing. On wasm, we only have lookupSymbol, and the
driver would attempt to call lookupSymbolInDLL first before falling
back to lookupSymbol, so lookupSymbolInDLL needs to return Nothing
gracefully for the fallback behavior to work.
- - - - -
aa0ca5e3 by Cheng Shao at 2025-09-30T18:41:27-04:00
hadrian/compiler: enable internal-interpreter for ghc library in wasm stage1
This commit enables the internal-interpreter flag for ghc library in
wasm stage1, as well as other minor adjustments to make it actually
possible to launch a ghc api session that makes use of the internal
interpreter. Closes #26431 #25400.
- - - - -
69503668 by Cheng Shao at 2025-09-30T18:41:27-04:00
testsuite: add T26431 test case
This commit adds T26431 to testsuite/tests/ghci-wasm which goes
through the complete bytecode compilation/linking/running pipeline in
wasm, so to witness that the ghc shared library in wasm have full
support for internal-interpreter.
- - - - -
e9445c01 by Matthew Pickering at 2025-09-30T18:42:23-04:00
driver: Load bytecode static pointer entries during linking
Previously the entries were loaded too eagerly, during upsweep, but we
should delay loading them until we know that the relevant bytecode
object is demanded.
Towards #25230
- - - - -
b8307eab by Cheng Shao at 2025-09-30T18:43:14-04:00
autoconf/ghc-toolchain: remove obsolete C99 check
This patch removes obsolete c99 check from autoconf/ghc-toolchain. For
all toolchain & platform combination we support, gnu11 or above is
already supported without any -std flag required, and our RTS already
required C11 quite a few years ago, so the C99 check is completely
pointless.
- - - - -
9c293544 by Simon Peyton Jones at 2025-10-01T09:36:10+01:00
Fix buglet in GHC.Core.Unify.uVarOrFam
We were failing to match two totally-equal types!
This led to #26457.
- - - - -
554487a7 by Rodrigo Mesquita at 2025-10-01T23:04:43-04:00
cleanup: Drop obsolete comment about HsConDetails
HsConDetails used to have an argument representing the type of the
tyargs in a list:
data HsConDetails tyarg arg rec
= PrefixCon [tyarg] [arg]
This datatype was shared across 3 synonyms: HsConPatDetails,
HsConDeclH98Details, HsPatSynDetails. In the latter two cases, `tyarg`
was instanced to `Void` meaning the list was always empty for these
cases.
In 7b84c58867edca57a45945a20a9391724db6d9e4, this was refactored such
that HsConDetails no longer needs a type of tyargs by construction. The
first case now represents the type arguments in the args type itself,
with something like:
ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2]
So the deleted comment really is just obsolete.
Fixes #26461
- - - - -
6992ac09 by Cheng Shao at 2025-10-02T07:27:55-04:00
testsuite: remove unused expected output files
This patch removes unused expected output files in the testsuites on
platforms that we no longer support.
- - - - -
39eaaaba by Ben Gamari at 2025-10-02T07:28:45-04:00
rts: Dynamically initialize built-in closures
To resolve #26166 we need to eliminate references to undefined symbols
in the runtime system. One such source of these is the runtime's
static references to `I#` and `C#` due the `stg_INTLIKE` and
`stg_CHARLIKE` arrays.
To avoid this we make these dynamic, initializing them during RTS
start-up.
- - - - -
c254c54b by Cheng Shao at 2025-10-02T07:29:33-04:00
compiler: only invoke keepCAFsForGHCi if internal-interpreter is enabled
This patch makes the ghc library only invoke keepCAFsForGHCi if
internal-interpreter is enabled. For cases when it's not (e.g. the
host build of a cross ghc), this avoids unnecessarily retaining all
CAFs in the heap. Also fixes the type signature of c_keepCAFsForGHCi
to match the C ABI.
- - - - -
c9ec4d43 by Simon Hengel at 2025-10-02T18:42:20-04:00
Update copyright in documentation
- - - - -
da9633a9 by Matthew Pickering at 2025-10-02T18:43:04-04:00
loader: Unify loadDecls and loadModuleLinkables functions
These two functions nearly did the same thing. I have refactored them so
that `loadDecls` now calls `loadModuleLinkables`.
Fixes #26459
- - - - -
5db98d80 by Simon Hengel at 2025-10-02T18:43:53-04:00
Fix typo
- - - - -
1275d360 by Matthew Pickering at 2025-10-03T06:05:56-04:00
testsuite: Use ghci_ways to set ways in PackedDataCon/UnboxedTuples/UnliftedDataTypeInterp tests
These tests reimplemented the logic from `valid_way` in order to
determine what ways to run. It's easier to use this combination of
`only_ways` and `extra_ways` to only run in GHCi ways and always run in
GHCi ways.
- - - - -
c06b534b by Matthew Pickering at 2025-10-03T06:06:40-04:00
Rename interpreterBackend to bytecodeBackend
This is preparation for creating bytecode files.
The "interpreter" is one way in which we can run bytecode objects. It is
more accurate to describe that the backend produces bytecode, rather
than the means by which the code will eventually run.
The "interpreterBackend" binding is left as a deprecated alias.
- - - - -
41bdb16f by Andreas Klebinger at 2025-10-06T18:04:34-04:00
Add a perf test for #26425
- - - - -
1da0c700 by Andreas Klebinger at 2025-10-06T18:05:14-04:00
Testsuite: Silence warnings about Wx-partial in concprog001
- - - - -
7471eb6a by sheaf at 2025-10-07T21:39:43-04:00
Improve how we detect user type errors in types
This commit cleans up all the code responsible for detecting whether a
type contains "TypeError msg" applications nested inside it. All the
logic is now in 'userTypeError_maybe', which is always deep. Whether
it looks inside type family applications is determined by the passed-in
boolean flag:
- When deciding whether a constraint is definitely insoluble, don't
look inside type family applications, as they may still reduce -- in
which case the TypeError could disappear.
- When reporting unsolved constraints, look inside type family
applications: they had the chance to reduce but didn't, and the
custom type error might contain valuable information.
All the details are explained in Note [Custom type errors in constraints]
in GHC.Tc.Types.Constraint.
Another benefit of this change is that it allows us to get rid of the
deeply dodgy 'getUserTypeErrorMsg' function.
This commit also improves the detection of custom type errors, for
example in equality constraints:
TypeError blah ~# rhs
It used to be the case that we didn't detect the TypeError on the LHS,
because we never considered that equality constraints could be insoluble
due to the presence of custom type errors. Addressing this oversight
improves detection of redundant pattern match warnings, fixing #26400.
- - - - -
29955267 by Rodrigo Mesquita at 2025-10-07T21:40:25-04:00
cleanup: Drop obsolete settings from config.mk.in
These values used to be spliced into the bindist's `config.mk` s.t. when
`make` was run, the values were read and written into the bindist installation `settings` file.
However, we now carry these values to the bindist directly in the
default.target toolchain file, and `make` writes almost nothing to
`settings` now (see #26227)
The entries deleted in this MR were already unused.
Fixes #26478
- - - - -
f7adfed2 by ARATA Mizuki at 2025-10-08T08:37:24-04:00
T22033 is only relevant if the word size is 64-bit
Fixes #25497
- - - - -
ff1650c9 by Ben Gamari at 2025-10-08T08:38:07-04:00
rts/posix: Enforce iteration limit on heap reservation logic
Previously we could loop indefinitely when attempting to get an address
space reservation for our heap. Limit the logic to 8 iterations to
ensure we instead issue a reasonable error message.
Addresses #26151.
- - - - -
01844557 by Ben Gamari at 2025-10-08T08:38:07-04:00
rts/posix: Hold on to low reservations when reserving heap
Previously when the OS gave us an address space reservation in low
memory we would immediately release it and try again. However, on some
platforms this meant that we would get the same allocation again in the
next iteration (since mmap's `hint` argument is just that, a hint).
Instead we now hold on to low reservations until we have found a
suitable heap reservation.
Fixes #26151.
- - - - -
b2c8d052 by Sven Tennie at 2025-10-08T08:38:47-04:00
Build terminfo only in upper stages in cross-builds (#26288)
Currently, there's no way to provide library paths for [n]curses for
both - build and target - in cross-builds. As stage0 is only used to
build upper stages, it should be fine to build terminfo only for them.
This re-enables building cross-compilers with terminfo.
- - - - -
c58f9a61 by Julian Ospald at 2025-10-08T08:39:36-04:00
ghc-toolchain: Drop `ld.gold` from merge object command
It's deprecated.
Also see #25716
- - - - -
2b8baada by sheaf at 2025-10-08T18:23:37-04:00
Improvements to 'mayLookIdentical'
This commit makes significant improvements to the machinery that decides
when we should pretty-print the "invisible bits" of a type, such as:
- kind applications, e.g. '@k' in 'Proxy @k ty'
- RuntimeReps, e.g. 'TYPE r'
- multiplicities and linear arrows 'a %1 -> b'
To do this, this commit refactors 'mayLookIdentical' to return **which**
of the invisible bits don't match up, e.g. in
(a %1 -> b) ~ (a %Many -> b)
we find that the invisible bit that doesn't match up is a multiplicity,
so we should set 'sdocLinearTypes = True' when pretty-printing, and with
e.g.
Proxy @k1 ~ Proxy @k2
we find that the invisible bit that doesn't match up is an invisible
TyCon argument, so we set 'sdocPrintExplicitKinds = True'.
We leverage these changes to remove the ad-hoc treatment of linearity
of data constructors with 'dataConDisplayType' and 'dataConNonLinearType'.
This is now handled by the machinery of 'pprWithInvisibleBits'.
Fixes #26335 #26340
- - - - -
129ce32d by sheaf at 2025-10-08T18:23:37-04:00
Store SDoc context in SourceError
This commits modifies the SourceError datatype which is used for
throwing and then reporting exceptions by storing all the info we need
to be able to print the SDoc, including whether we should print with
explicit kinds, explicit runtime-reps, etc.
This is done using the new datatype:
data SourceErrorContext
= SEC
!DiagOpts
!(DiagnosticOpts GhcMessage)
Now, when we come to report an error (by handling the exception), we
have access to the full context we need.
Fixes #26387
- - - - -
f9790ca8 by Ben Gamari at 2025-10-08T18:24:19-04:00
gitlab-ci: Make RELEASE_JOB an input
Rather than an undocumented variable.
- - - - -
14281a22 by Ben Gamari at 2025-10-11T14:06:47-04:00
rts/nonmoving: Fix comment spelling
- - - - -
bedd38b0 by Ben Gamari at 2025-10-11T14:06:47-04:00
rts/nonmoving: Use atomic operations to update bd->flags
- - - - -
215d6841 by Ben Gamari at 2025-10-11T14:06:47-04:00
nonmoving: Use get_itbl instead of explicit loads
This is cleaner and also fixes unnecessary (and unsound) use of
`volatile`.
- - - - -
2c94aa3a by Ben Gamari at 2025-10-11T14:06:47-04:00
rts/Scav: Handle WHITEHOLEs in scavenge_one
`scavenge_one`, used to scavenge mutable list entries, may encounter
`WHITEHOLE`s when the non-moving GC is in use via two paths:
1. when an MVAR is being marked concurrently
2. when the object belongs to a chain of selectors being short-cutted.
Fixes #26204.
- - - - -
6bd8155c by Matthew Pickering at 2025-10-11T14:07:29-04:00
Add support for generating bytecode objects
This commit adds the `-fwrite-byte-code` option which makes GHC emit a
`.gbc` file which contains a serialised representation of bytecode.
The bytecode can be loaded by the compiler to avoid having to
reinterpret a module when using the bytecode interpreter (for example,
in GHCi).
There are also the new options:
* -gbcdir=<DIR>: Specify the directory to place the gbc files
* -gbcsuf=<suffix>: Specify the suffix for gbc files
The option `-fbyte-code-and-object-code` now implies
`-fwrite-byte-code`.
These performance tests fail due to https://github.com/haskell/directory/issues/204
-------------------------
Metric Increase:
MultiComponentModules
MultiLayerModules
MultiComponentModulesRecomp
MultiLayerModulesRecomp
MultiLayerModulesTH_Make
MultiLayerModulesTH_OneShot
T13701
-------------------------
The bytecode serialisation part was implemented by Cheng Shao
Co-authored-by: Cheng Shao <terrorjack(a)type.dance>
- - - - -
dc8f9599 by Matthew Pickering at 2025-10-11T14:07:30-04:00
Revert "Add a perf test for #26425"
This test has a large memory spike currently, which makes the test
sensitive, since if you allocate a little more or less, the precise
location where GC happens shifts and you observe a different part of the
spike.
Andreas told me to revert the patch for now, and he will add it back
when he fixes the memory spike.
This reverts commit 41bdb16fd083110a06507248f648c507a2feb4af.
- - - - -
e10dcd65 by Sven Tennie at 2025-10-12T10:24:56+00:00
T22859: Increase threadDelay for small machines
The previously used thread delay led to failures on my RISC-V test
setups.
- - - - -
d59ef6b6 by Hai / @BestYeen at 2025-10-14T21:51:14-04:00
Change Alex and Happy m4 scripts to display which version was found in the system, adapt small formatting details in Happy script to be more like the Alex script again.
- - - - -
c98abb6a by Hai / @BestYeen at 2025-10-14T21:52:08-04:00
Update occurrences of return to pure and add a sample for redefining :m to mean :main
- - - - -
70ee825a by Cheng Shao at 2025-10-14T21:52:50-04:00
testsuite: fix T3586 for non-SSE3 platforms
`T3586.hs` contains `-fvia-C -optc-msse3` which I think is a
best-effort basis to harvest the C compiler's auto vectorization
optimizations via the C backend back when the test was added. The
`-fvia-C` part is now a deprecated no-op because GHC can't fall back
to the C backend on a non-unregisterised build, and `-optc-msse3`
might actually cause the test to fail on non x86/x64 platforms, e.g.
recent builds of wasi-sdk would report `wasm32-wasi-clang: error:
unsupported option '-msse3' for target 'wasm32-unknown-wasi'`.
So this patch cleans up this historical cruft. `-fvia-C` is removed,
and `-optc-msse3` is only passed when cpuid contains `pni` (which
indicates support of SSE3).
- - - - -
4be32153 by Teo Camarasu at 2025-10-15T08:06:09-04:00
Add submodules for template-haskell-lift and template-haskell-quasiquoter
These two new boot libraries expose stable subsets of the
template-haskell interface.
This is an implemenation of the GHC proposal https://github.com/ghc-proposals/ghc-proposals/pull/696
Work towards #25262
- - - - -
0c00c9c3 by Ben Gamari at 2025-10-15T08:06:51-04:00
rts: Eliminate uses of implicit constant arrays
Folding of `const`-sized variable-length arrays to a constant-length
array is a gnu extension which clang complains about.
Closes #26502.
- - - - -
bf902a1d by Fendor at 2025-10-15T16:00:59-04:00
Refactor distinct constructor tables map construction
Adds `GHC.Types.Unique.FM.alterUFM_L`, `GHC.Types.Unique.DFM.alterUDFM_L`
`GHC.Data.Word64Map.alterLookup` to support fusion of distinct
constructor data insertion and lookup during the construction of the `DataCon`
map in `GHC.Stg.Debug.numberDataCon`.
Co-authored-by: Fendor <fendor(a)posteo.de>
Co-authored-by: Finley McIlwaine <finleymcilwaine(a)gmail.com>
- - - - -
b3585ba1 by Fendor at 2025-10-15T16:00:59-04:00
Allow per constructor refinement of distinct-constructor-tables
Introduce `-fno-distinct-constructor-tables`. A distinct constructor table
configuration is built from the combination of flags given, in order. For
example, to only generate distinct constructor tables for a few specific
constructors and no others, just pass
`-fdistinct-constructor-tables-only=C1,...,CN`.
This flag can be supplied multiple times to extend the set of
constructors to generate a distinct info table for.
You can disable generation of distinct constructor tables for all
configurations by passing `-fno-distinct-constructor-tables`.
The various configurations of these flags is included in the `DynFlags`
fingerprints, which should result in the expected recompilation logic.
Adds a test that checks for distinct tables for various given or omitted
constructors.
Updates CountDepsAst and CountDepsParser tests to account for new dependencies.
Fixes #23703
Co-authored-by: Fendor <fendor(a)posteo.de>
Co-authored-by: Finley McIlwaine <finleymcilwaine(a)gmail.com>
- - - - -
e17dc695 by fendor at 2025-10-15T16:01:41-04:00
Fix typos in haddock documentation for stack annotation API
- - - - -
f85058d3 by Zubin Duggal at 2025-10-17T13:50:52+05:30
compiler: Attempt to systematize Unique tags by introducing an ADT for each different tag
Fixes #26264
Metric Decrease:
T9233
- - - - -
c85c845d by sheaf at 2025-10-17T22:35:32-04:00
Don't prematurely final-zonk PatSyn declarations
This commit makes GHC hold off on the final zonk for pattern synonym
declarations, in 'GHC.Tc.TyCl.PatSyn.tc_patsyn_finish'.
This accommodates the fact that pattern synonym declarations without a
type signature can contain unfilled metavariables, e.g. if the RHS of
the pattern synonym involves view-patterns whose type mentions promoted
(level 0) metavariables. Just like we do for ordinary function bindings,
we should allow these metavariables to be settled later, instead of
eagerly performing a final zonk-to-type.
Now, the final zonking-to-type for pattern synonyms is performed in
GHC.Tc.Module.zonkTcGblEnv.
Fixes #26465
- - - - -
ba3e5bdd by Rodrigo Mesquita at 2025-10-18T16:57:18-04:00
Move code-gen aux symbols from ghc-internal to rts
These symbols were all previously defined in ghc-internal and made the
dependency structure awkward, where the rts may refer to some of these
symbols and had to work around that circular dependency the way
described in #26166.
Moreover, the code generator will produce code that uses these symbols!
Therefore, they should be available in the rts:
PRINCIPLE: If the code generator may produce code which uses this
symbol, then it should be defined in the rts rather than, say,
ghc-internal.
That said, the main motivation is towards fixing #26166.
Towards #26166. Pre-requisite of !14892
- - - - -
f31de2a9 by Ben Gamari at 2025-10-18T16:57:18-04:00
rts: Avoid static symbol references to ghc-internal
This resolves #26166, a bug due to new constraints placed by Apple's
linker on undefined references.
One source of such references in the RTS is the many symbols referenced
in ghc-internal. To mitigate #26166, we make these references dynamic,
as described in Note [RTS/ghc-internal interface].
Fixes #26166
Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita(a)gmail.com>
Co-authored-by: Cheng Shao <terrorjack(a)type.dance>
- - - - -
43fdfddc by Ben Gamari at 2025-10-18T16:57:18-04:00
compiler: Rename isMathFun -> isLibcFun
This set includes more than just math functions.
- - - - -
4ed5138f by Ben Gamari at 2025-10-18T16:57:18-04:00
compiler: Add libc allocator functions to libc_funs
Prototypes for these are now visible from `Prim.h`, resulting in
multiple-declaration warnings in the unregisterised job.
- - - - -
9a0a076b by Ben Gamari at 2025-10-18T16:57:18-04:00
rts: Minimize header dependencies of Prim.h
Otherwise we will end up with redundant and incompatible declarations
resulting in warnings during the unregisterised build.
- - - - -
26b8a414 by Diego Antonio Rosario Palomino at 2025-10-18T16:58:10-04:00
Cmm Parser: Fix incorrect example in comment
The Parser.y file contains a comment with an incorrect example of textual
Cmm (used in .cmm files). This commit updates the comment to ensure it
reflects valid textual Cmm syntax.
Fixes #26313
- - - - -
d4a9d6d6 by ARATA Mizuki at 2025-10-19T18:43:47+09:00
Handle implications between x86 feature flags
This includes:
* Multiple -msse* options can be specified
* -mavx implies -msse4.2
* -mavx2 implies -mavx
* -mfma implies -mavx
* -mavx512f implies -mavx2 and -mfma
* -mavx512{cd,er,pf} imply -mavx512f
Closes #24989
Co-authored-by: sheaf <sam.derbyshire(a)gmail.com>
- - - - -
c9b8465c by Cheng Shao at 2025-10-20T10:16:00-04:00
wasm: workaround WebKit bug in dyld
This patch works around a WebKit bug and allows dyld to run on WebKit
based platforms as well. See added note for detailed explanation.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
91b6be10 by Julian Ospald at 2025-10-20T18:21:03-04:00
Improve error handling in 'getPackageArchives'
When the library dirs in the package conf files are not set up correctly,
the JS linker will happily ignore such packages and not link against them,
although they're part of the link plan.
Fixes #26383
- - - - -
6c5269da by Sven Tennie at 2025-10-20T18:21:44-04:00
Align coding style
Improve readability by using the same style for all constructor calls in
this function.
- - - - -
3d305889 by Sven Tennie at 2025-10-20T18:21:44-04:00
Reduce complexity by removing joins with mempty
ldArgs, cArgs and cppArgs are all `mempty`. Thus concatenating them adds
nothing but some complexity while reading the code.
- - - - -
38d65187 by Matthew Pickering at 2025-10-21T13:12:20+01:00
Fix stack decoding when using profiled runtime
There are three fixes in this commit.
* We need to replicate the `InfoTable` and `InfoTableProf`
approach for the other stack constants (see the new Stack.ConstantsProf
file).
* Then we need to appropiately import the profiled or non-profiled
versions.
* Finally, there was an incorrect addition in `stackFrameSize`. We need
to cast after performing addition on words.
Fixes #26507
- - - - -
17231bfb by fendor at 2025-10-21T13:12:20+01:00
Add regression test for #26507
- - - - -
4f5bf93b by Simon Peyton Jones at 2025-10-25T04:05:34-04:00
Postscript to fix for #26255
This MR has comments only
- - - - -
6ef22fa0 by IC Rainbow at 2025-10-26T18:23:01-04:00
Add SIMD primops for bitwise logical operations
This adds 128-bit wide and/or/xor instructions for X86 NCG,
with both SSE and AVX encodings.
```
andFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# -- andps / vandps
andDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# -- andpd / vandpd
andInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# -- pand / vpand
```
The new primops are available on ARM when using LLVM backend.
Tests added:
- simd015 (floats and doubles)
- simd016 (integers)
- simd017 (words)
Fixes #26417
- - - - -
fbdc623a by sheaf at 2025-10-26T18:23:52-04:00
Add hints for unsolved HasField constraints
This commit adds hints and explanations for unsolved 'HasField'
constraints.
GHC will now provide additional explanations for an unsolved constraint
of the form 'HasField fld_name rec_ty fld_ty'; the details are laid out in
Note [Error messages for unsolved HasField constraints], but briefly:
1. Provide similar name suggestions (e.g. mis-spelled field name)
and import suggestions (record field not in scope).
These result in actionable 'GhcHints', which is helpful to provide
code actions in HLS.
2. Explain why GHC did not solve the constraint, e.g.:
- 'fld_name' is not a string literal (e.g. a type variable)
- 'rec_ty' is a TyCon without any fields, e.g. 'Int' or 'Bool'.
- 'fld_ty' contains existentials variables or foralls.
- The record field is a pattern synonym field (GHC does not generate
HasField instances for those).
- 'HasField' is a custom 'TyCon', not actually the built-in
'HasField' typeclass from 'GHC.Records'.
On the way, we slightly refactor the mechanisms for import suggestions
in GHC.Rename.Unbound. This is to account for the fact that, for
'HasField', we don't care whether the field is imported qualified or
unqualified. 'importSuggestions' was refactored, we now have
'sameQualImportSuggestions' and 'anyQualImportSuggestions'.
Fixes #18776 #22382 #26480
- - - - -
99d5707f by sheaf at 2025-10-26T18:23:52-04:00
Rename PatSyn MatchContext to PatSynCtx to avoid punning
- - - - -
5dc2e9ea by Julian Ospald at 2025-10-27T18:17:23-04:00
Skip uniques test if sources are not available
- - - - -
544b9ec9 by Vladislav Zavialov at 2025-10-27T18:18:06-04:00
Re-export GHC.Hs.Basic from GHC.Hs
Clean up some import sections in GHC by re-exporting GHC.Hs.Basic
from GHC.Hs.
- - - - -
643ce801 by Julian Ospald at 2025-10-28T18:18:55-04:00
rts: remove unneccesary cabal flags
We perform those checks via proper autoconf macros
instead that do the right thing and then add those
libs to the rts buildinfo.
- - - - -
d69ea8fe by Vladislav Zavialov at 2025-10-28T18:19:37-04:00
Test case for #17705
Starting with GHC 9.12 (the first release to include 5745dbd3),
all examples in this ticket are handled as expected.
- - - - -
731a4a21 by Duncan Coutts at 2025-10-30T11:07:21+00:00
Use async rather than sync notification for I/O manager events
When we forkProcess or setNumCapabilities the RTS needs to notify the
in-Haskell I/O manager to let it respond.
Previously we did this synchronously, which starts the thread and runs
the schduler until the thread finishes. With forkProcess, no other
threads would be running at the time, but this is not the case for
setNumCapabilities which has to cope with an inherent race condition. It
looks like forkProcess also does not need to be synchronous, it just
needs the I/O manager thread to be started, but no init needs finishing
before user threads start running.
Previously this used rts_evalIO, which requires an in/out capability
parameter. What we do now is start the IO thread and let it run
asynchronously. This only requires the capability as an in param, since
it cannot cause switching capability (as entering the scheduler can).
This makes the I/O manager API simpler and more uniform.
- - - - -
75a716b5 by Duncan Coutts at 2025-11-11T17:15:11+01:00
Move THREADED_RTS-conditional struct members to end of Capability
Accessing members of the Capability struct from CMM code rely on
accessor macros. (The macros are generated by deriveConstants).
These macros have a single definition. This means that the offsets of
all struct members must *not* vary based on THREADED_RTS vs
!THREADED_RTS. This requires that any struct members that are
conditional on THREADED_RTS must occur after the unconditional struct
members. Hence we move all the ones that are conditional on
THREADED_RTS to the end.
Add a deriveConstants entry for the iomgr member of the Capability
struct, which was the motivation for this change.
Add warning messages to help our future selves. Debugging this took me
a couple hours in gdb!
- - - - -
dbd41e53 by Duncan Coutts at 2025-11-12T09:54:15+01:00
Make the IOManager API use CapIOManager rather than Capability
This makes the API somewhat more self-contained and more consistent.
Now the IOManager API and each of the backends takes just the I/O
manager structure. Previously we had a bit of a mixture, depending on
whether the function needed access to the Capability or just the
CapIOManager.
We still need access to the cap, so we introduce a back reference to
reach the capability, via iomgr->cap.
Convert all uses in select and poll backends, but not win32 ones.
Convert callers in the scheduler and elsewhere.
Also convert the three CMM primops that call IOManager APIs. They just
need to use Capability_iomgr(MyCapability()).
- - - - -
e4e1c7f0 by Duncan Coutts at 2025-11-12T09:55:02+01:00
Split posix/MIO.c out of posix/Signals.c
The MIO I/O manager was secretly living inside the Signals file.
Now it gets its own file, like any other self-respecting I/O manager.
- - - - -
1e364cd9 by Duncan Coutts at 2025-11-12T09:55:02+01:00
Rationalise some scheduler run queue utilities
Move them all to the same place in the file.
Make some static that were used only internally.
Also remove a redundant assignment after calling truncateRunQueue that
is already done within truncateRunQueue.
- - - - -
ea086e40 by Duncan Coutts at 2025-11-14T19:00:51+00:00
Rename initIOManager{AfterFork} to {re}startIOManager
These are more accurate names, since these actions happen after
initialisation and are really about starting (or restarting) background
threads.
- - - - -
8386918f by Duncan Coutts at 2025-11-14T19:01:00+00:00
Add a TODO to the MIO I/O manager
The direction of travel is to make I/O managers per-capability and have
all their state live in the struct CapIOManager. The MIO I/O manager
however still has a number of global variables.
It's not obvious how handle these globals however.
- - - - -
de9f5f9b by Duncan Coutts at 2025-11-14T19:01:18+00:00
Free per-cap I/O managers during shutdown and forkProcess
Historically this was not strictly necessary. The select and win32
legacy I/O managers did not maintain any dynamically allocated
resources. The new poll one does (an auxillary table), and so this
should be freed.
After forkProcess, all threads get deleted. This includes threads
waiting on I/O or timers. So as of this patch, resetting the I/O
manager is just about tidying things up. For example, for the poll
I/O manager this will reset the size of the AIOP table (which
otherwise grows but never shrinks).
In future however the re-initialising will become neeecessary for
functionality, since some I/O managers will need to re-initialise
wakeup fds that are set CLOEXEC.
- - - - -
987b2a23 by Duncan Coutts at 2025-11-14T19:02:22+00:00
Add an FdWakup module for posix I/O managers
This will be used to implement wakeupIOManager for in-RTS I/O managers.
It provides a notification/wakeup mechanism using FDs, suitable for
situations when I/O managers are blocked on a set of fds anyway.
- - - - -
14b09793 by Duncan Coutts at 2025-11-14T19:04:40+00:00
Add wakeupIOManager support for select I/O manager
Uses the FdWakup mechanism.
- - - - -
450f2c4f by Duncan Coutts at 2025-11-14T19:05:01+00:00
Add wakeupIOManager support for poll I/O manager
Uses the FdWakup mechanism.
A quirk we have to cope with is that we now need to poll one more fd --
the wakeup_fd_r -- but this fd has no corresponding entry in the
aiop_table. This is awkward since we have set up our aiop_poll_table to
be an auxilliary table with matching indicies.
The solution this patch uses (and described in the comments) is to have
two tables: struct pollfd *aiop_poll_table, *full_poll_table;
and to have the aiop_poll_table alias the tail of the full_poll_table.
The head entry in the full_poll_table is the extra fd. So we poll the
full_poll_table, while the aiop_poll_table still has matching indicies
with the aiop_table.
Hurrah for C aliasing rules.
- - - - -
88ae709e by Duncan Coutts at 2025-11-14T19:05:22+00:00
Add wakeupIOManager support for win32 legacy I/O manager
- - - - -
2b61a986 by Duncan Coutts at 2025-11-14T19:05:42+00:00
wakeupIOManager is now required for all I/O managers
We are going to rely on it. Previously it could be a no-op. Update the
docs in the header file.
Also, temporarily disable awaitCompletedTimeoutsOrIO post-condition
assertion. It will become more complicated due to wakeupIOManager, and
it's not yet clear how to express it.
We will re-introduce a post condition after a few more changes.
- - - - -
49c614bd by Duncan Coutts at 2025-11-14T19:07:23+00:00
Make signal handling be a respondibility of the I/O manager(s)
Previously it was scattered between I/O managers and the scheduler, and
especially the scheduler's deadlock detection.
Previously the scheduler would poll for pending signals each iteration
of the scheduler loop. The scheduler also had some hairy signal
functionality in the deadlock detection: in the non-threaded RTS (only)
if there were still no threads running after deadlock detection then it
would block waiting for signals.
But signals can and (in my opinion) should be thought of as just a funny
kind of I/O, and thus should be a responsibility of the I/O manager.
So now we have the I/O managers poll for signals when they are polling
for I/O completion (and removing the separate poll in the scheduler).
And when I/O managers block waiting for I/O then they now also start
signal handlers if they get interrupted by a signal. Crucially, if there
is no pending I/O or timers, the awaitCompletedTimeoutsOrIO will still
block waiting for signals.
This patch puts us into an intermediate state: it temporarily breaks
deadlock detection in the non-threaded RTS. The waiting on I/O currently
happens before deadlock detection. This means we'll now wait forever on
signals before doing deadlock detection. We need to move waiting after
deadlock detection. We'll do that in a later patch.
- - - - -
5ce78412 by Duncan Coutts at 2025-11-14T19:11:14+00:00
Clean up signal handling internal API
Now that the I/O manager is responsible for signals, we can simplify the
API we present for signal handling.
We now just need startPendingSignalHandlers, which is called from the
I/O managers. We can get rid of awaitUserSignals. We also don't need
RtsSignals.h to re-export the platform-specific posix/Signals.h or
win32/ConsoleHandler.h
We can also hide more of the implementation of signals. Less has to be
exposed in posix/Signals.h or win32/ConsoleHandler.h. Partly this is
because we don't need inline functions (or macros) in the interface.
Also remove signal_handlers from RTS ABI exported symbols list. It does
not appear to have any users in the core libs, and its really an
internal implementation detail. It should not be exposed unless its
really necessary.
- - - - -
58a0a072 by Duncan Coutts at 2025-11-14T19:26:20+00:00
In the scheduler, move I/O blocking after deadlock detection
To make deadlock detection effective in the non-threaded RTS when there
are deadlocked threads and other unrelated threads waiting on I/O, we
need to arrange to do deadlock detection before we block in scheduler
to wait on I/O.
The solution is to:
1. adjust scheduleFindWork, which runs before deadlock detection, to
only poll for I/O and not block; and
2. add a step after deadlock detection to wait on I/O if there are
still no threads to run (and there's any I/O or timeouts outstanding)
The scheduleCheckBlockedThreads is now so simple that it made more sense
to inline it into scheduleFindWork.
- - - - -
c38fc636 by Duncan Coutts at 2025-11-14T19:26:23+00:00
Remove bogus anyPendingTimeoutsOrIO guard from scheduleDetectDeadlock
The deadlock detection was only invoked if both of these conditions
hold:
1. the run queue is empty
2. there is no pending I/O or timeouts
The second condition is unnecessary. The deadlock detection mechanism
can find deadlocks even if there are other threads waiting on I/O or
timers. Having this extra condition means that we fail to detect
blocked threads if there are any threads waiting on I/O or timers.
Part of fixing issue #26408
- - - - -
a27e3707 by Duncan Coutts at 2025-11-14T19:27:13+00:00
Don't consider pending I/O for early context switch optimisation
Context switches are normally initiated by the timer signal. If however
the user specifies "context switch as often as possible", with +RTS -C0
then the scheduler arranges for an early context switch (when it's just
about to run a Haskell thread).
Context switching very often is expensive, so as an optimisation there
cases where we do not arrange an early context switch:
1. if there's no other threads to run
2. if there is no pending I/O or timers
This patch eliminates case 2, leaving only case 1.
The rationale is as follows. The use of this was inconsistent across
platforms and threaded/non-threaded RTS ways. It only worked on the
non-threaded RTS and on Windows only worked for the win32-legacy I/O
manager. On all other combinations anyPendingTimeoutsOrIO would always
return false. The fact that nobody noticed and complained about this
inconsistency suggests that the feature is not relied upon.
If however it turns out that applications do rely on this, then the
proper thing to do is not to restore this check, but to add a new I/O
manager hint function that returns if there is any pending events that
are likely to happen *soon*: for example timeouts expiring within one
timeslice, or I/O waits on things likely to complete soon like disk I/O,
but not for example socket/pipe I/O.
The motivation to avoid this use of anyPendingTimeoutsOrIO is to
allow us to eliminate anyPendingTimeoutsOrIO entirely. All other uses
of this are just guards on {await,poll}CompletedTimeoutsOrIO and
the guards can safely be folded into those functions. This will better
cope with some I/O managers having no proper implementation of
anyPendingTimeoutsOrIO.
Ultimately this will let us simplify the scheduler which currently has
to have special #ifdef mingw32_HOST_OS cases to cope with the lack of a
working anyPendingTimeoutsOrIO for some Windows I/O managers
- - - - -
48029b5a by Duncan Coutts at 2025-11-14T19:29:26+00:00
Remove anyPendingTimeoutsOrIO guarding {poll,await}CompletedTimeoutsOrIO
Previously the API of the I/O manager used a two step process: check
anyPendingTimeoutsOrIO and then call {poll,await}CompletedTimeoutsOrIO.
This was primarily there as a performance thing, to cheaply check if we
need to do anything.
And then because anyPendingTimeoutsOrIO existed, it was used for other
things too. We have now eliminated the other uses, and are just left
with the performance pattern.
But this was problematic because not all I/O managers correctly
implement anyPendingTimeoutsOrIO (specifically the win32 ones), and now
that we also make I/O managers responsible for signals then we need to
poll/await even if there is no pending I/O or timeouts. If there is no
pending I/O or timeouts then poll/await needs to degenerate to just
waiting forever for any signals.
- - - - -
f2154367 by Duncan Coutts at 2025-11-14T19:29:51+00:00
Remove anyPendingTimeoutsOrIO, it is no longer used
And this avoids the problems arising from the win32 I/O managers having
had a bogus implementation.
- - - - -
7a85b57f by Duncan Coutts at 2025-11-14T19:31:08+00:00
Remove second scheduler call to awaitCompletedTimeoutsOrIO
Previously awaitCompletedTimeoutsOrIO was called both before and after
deadlock detection in the scheduler. The reason for that was that the
win32 I/O managers had a bogus implementation of anyPendingTimeoutsOrIO
and this was used to guard the call of awaitCompletedTimeoutsOrIO prior
to deadlock detection. This meant the first call site was never actually
called when using the win32 I/O managers. This was the reason for the
second call: the first one was never used. What a mess.
So now we have a simple design in the scheduler:
1. poll for completed I/O, timers or signals
2. if no runnable threads: do deadlock detection
3. if still no runnable threads: block waiting for I/O, timers or
signals.
- - - - -
9b958fa2 by Duncan Coutts at 2025-11-14T19:31:46+00:00
Lift emptyRunQueue guard out of scheduleDetectDeadlock
this improved the clarity of the logic when reading the scheduler code.
- - - - -
b5dbb627 by Duncan Coutts at 2025-11-14T19:35:58+00:00
Make non-threaded deadlock detection also rely on idle GC
Only do deadlock detection GC when idle GC kicks in. This also relies on
using wakeUpRts, so now do this unconditionally. Previously wakeUpRts
was for the threaded rts only.
- - - - -
82dc4a0d by Duncan Coutts at 2025-11-14T19:36:04+00:00
Enable idle GC by default on non-threaded RTS.
The behaviour is now uniform between threaded and non-threaded. The
deadlock detection now relies on idle GC for both threaded and
non-threaded ways. Previously deadlock detection did not rely on idle
GC for the non-threaded way.
- - - - -
032b9c4c by Duncan Coutts at 2025-11-14T19:46:54+00:00
Add a long Note [Deadlock detection]
It describes the historical and modern designs and their trade-offs.
The point is we've now unified the code for deadlock detection between
the threaded and non-threaded ways, by changing the non-threaded to
follow the same design as the threaded.
- - - - -
fd2d1aae by Duncan Coutts at 2025-11-14T19:49:13+00:00
Add a test for deadlock detection, issue #26408
- - - - -
a85a430a by Duncan Coutts at 2025-11-14T22:17:40+00:00
Update the user guide with the revised idle GC behaviour
i.e. it's now not just for the threaded RTS, but general.
Also document the fact that disabling idle GC also disables deadlock
detection.
- - - - -
787 changed files:
- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- .gitmodules
- compiler/GHC.hs
- compiler/GHC/Builtin/PrimOps.hs
- compiler/GHC/Builtin/Uniques.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Breakpoints.hs
- + compiler/GHC/ByteCode/Serialize.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/Info.hs
- compiler/GHC/Cmm/Info/Build.hs
- compiler/GHC/Cmm/MachOp.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Cmm/Pipeline.hs
- compiler/GHC/Cmm/UniqueRenamer.hs
- compiler/GHC/Cmm/Utils.hs
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/Config.hs
- compiler/GHC/CmmToAsm/LA64/CodeGen.hs
- compiler/GHC/CmmToAsm/LA64/Instr.hs
- compiler/GHC/CmmToAsm/LA64/Ppr.hs
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/Wasm/FromCmm.hs
- compiler/GHC/CmmToAsm/X86/CodeGen.hs
- compiler/GHC/CmmToAsm/X86/Instr.hs
- compiler/GHC/CmmToAsm/X86/Ppr.hs
- compiler/GHC/CmmToC.hs
- compiler/GHC/CmmToLlvm/Base.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/Make.hs
- compiler/GHC/Core/Multiplicity.hs
- compiler/GHC/Core/Opt/ConstantFold.hs
- compiler/GHC/Core/Opt/Monad.hs
- compiler/GHC/Core/Opt/Pipeline.hs
- compiler/GHC/Core/Opt/Pipeline/Types.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Monad.hs
- compiler/GHC/Core/PatSyn.hs
- compiler/GHC/Core/Ppr.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/Rules/Config.hs
- compiler/GHC/Core/TyCo/Compare.hs
- compiler/GHC/Core/TyCo/Ppr.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Unfold.hs
- compiler/GHC/Core/Unify.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Data/FlatBag.hs
- compiler/GHC/Data/SmallArray.hs
- compiler/GHC/Data/Word64Map/Internal.hs
- compiler/GHC/Data/Word64Map/Lazy.hs
- compiler/GHC/Driver/Backend.hs
- compiler/GHC/Driver/Backend/Internal.hs
- compiler/GHC/Driver/Backpack.hs
- + compiler/GHC/Driver/ByteCode.hs
- compiler/GHC/Driver/CodeOutput.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- compiler/GHC/Driver/Config/Core/Rules.hs
- compiler/GHC/Driver/Config/Finder.hs
- compiler/GHC/Driver/Config/Stg/Debug.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Env/Types.hs
- compiler/GHC/Driver/Errors.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Driver/Messager.hs
- compiler/GHC/Driver/Monad.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Plugins.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Breakpoints.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Foreign/C.hs
- compiler/GHC/HsToCore/Foreign/JavaScript.hs
- compiler/GHC/HsToCore/Foreign/Wasm.hs
- compiler/GHC/HsToCore/Monad.hs
- compiler/GHC/HsToCore/Pmc/Ppr.hs
- compiler/GHC/HsToCore/Pmc/Types.hs
- compiler/GHC/HsToCore/Pmc/Utils.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Usage.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/Iface/Binary.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Errors/Ppr.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Ext/Types.hs
- compiler/GHC/Iface/Flags.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Recomp/Flags.hs
- compiler/GHC/Iface/Rename.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Tidy/StaticPtrTable.hs
- compiler/GHC/Iface/Type.hs
- compiler/GHC/JS/JStg/Monad.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Dynamic.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/MacOS.hs
- compiler/GHC/Linker/Static.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Llvm/Ppr.hs
- compiler/GHC/Llvm/Types.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/Lexer/String.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/Types.hs
- compiler/GHC/Platform.hs
- compiler/GHC/Platform/Reg.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Rename/Unbound.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Heap/Inspect.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Runtime/Interpreter/Types.hs
- compiler/GHC/Runtime/Loader.hs
- compiler/GHC/Settings.hs
- compiler/GHC/Settings/IO.hs
- compiler/GHC/Stg/Debug.hs
- + compiler/GHC/Stg/Debug/Types.hs
- compiler/GHC/Stg/EnforceEpt.hs
- compiler/GHC/Stg/Pipeline.hs
- compiler/GHC/Stg/Unarise.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm/DataCon.hs
- compiler/GHC/StgToCmm/ExtCode.hs
- compiler/GHC/StgToCmm/Layout.hs
- compiler/GHC/StgToCmm/Monad.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToJS/CodeGen.hs
- compiler/GHC/StgToJS/Ids.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/StgToJS/Prim.hs
- compiler/GHC/SysTools/BaseDir.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Deriv/Generics.hs
- compiler/GHC/Tc/Deriv/Utils.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/Solver/Solve.hs-boot
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/CtLoc.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Utils/TcType.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Tc/Utils/Unify.hs-boot
- compiler/GHC/Tc/Validity.hs
- compiler/GHC/Tc/Zonk/TcType.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Types/Hint.hs
- compiler/GHC/Types/Hint/Ppr.hs
- compiler/GHC/Types/Name/Cache.hs
- compiler/GHC/Types/RepType.hs
- compiler/GHC/Types/SourceError.hs
- compiler/GHC/Types/SptEntry.hs
- compiler/GHC/Types/Tickish.hs
- compiler/GHC/Types/TyThing/Ppr.hs
- compiler/GHC/Types/Unique.hs
- compiler/GHC/Types/Unique/DFM.hs
- compiler/GHC/Types/Unique/DSM.hs
- compiler/GHC/Types/Unique/FM.hs
- compiler/GHC/Types/Unique/Supply.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Finder/Types.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Unit/Module/Location.hs
- compiler/GHC/Unit/Module/ModSummary.hs
- compiler/GHC/Unit/Module/WholeCoreBindings.hs
- compiler/GHC/Unit/State.hs
- compiler/GHC/Utils/Binary.hs
- compiler/GHC/Utils/Error.hs
- compiler/GHC/Utils/Outputable.hs
- compiler/GHC/Utils/Ppr.hs
- compiler/Language/Haskell/Syntax/Binds.hs
- compiler/Language/Haskell/Syntax/Decls.hs
- compiler/Language/Haskell/Syntax/Expr.hs
- compiler/cbits/keepCAFsForGHCi.c
- compiler/ghc.cabal.in
- configure.ac
- distrib/configure.ac.in
- docs/users_guide/9.16.1-notes.rst
- docs/users_guide/conf.py
- docs/users_guide/debug-info.rst
- docs/users_guide/debugging.rst
- docs/users_guide/extending_ghc.rst
- docs/users_guide/exts/pragmas.rst
- docs/users_guide/exts/scoped_type_variables.rst
- docs/users_guide/ghci.rst
- docs/users_guide/phases.rst
- docs/users_guide/profiling.rst
- docs/users_guide/runtime_control.rst
- docs/users_guide/separate_compilation.rst
- docs/users_guide/using.rst
- ghc/GHCi/UI.hs
- ghc/Main.hs
- hadrian/bindist/Makefile
- hadrian/bindist/config.mk.in
- hadrian/cfg/default.host.target.in
- hadrian/cfg/default.target.in
- hadrian/cfg/system.config.in
- hadrian/src/Base.hs
- hadrian/src/Oracles/Flag.hs
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Packages.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Rules/Gmp.hs
- hadrian/src/Rules/Libffi.hs
- hadrian/src/Settings/Builders/Cabal.hs
- hadrian/src/Settings/Builders/Common.hs
- hadrian/src/Settings/Builders/DeriveConstants.hs
- hadrian/src/Settings/Builders/Hsc2Hs.hs
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Packages.hs
- libraries/base/changelog.md
- libraries/base/src/GHC/Base.hs
- libraries/base/src/GHC/Exts.hs
- libraries/base/src/GHC/RTS/Flags.hs
- libraries/base/tests/unicode002.stdout
- libraries/base/tests/unicode003.stdout
- libraries/ghc-boot/GHC/Settings/Utils.hs
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghc-experimental/CHANGELOG.md
- libraries/ghc-experimental/src/GHC/Stack/Annotation/Experimental.hs
- libraries/ghc-heap/GHC/Exts/Heap.hs
- + libraries/ghc-internal/cbits/RtsIface.c
- libraries/ghc-internal/cbits/Stack_c.c
- libraries/ghc-internal/codepages/MakeTable.hs
- libraries/ghc-internal/codepages/Makefile
- libraries/ghc-internal/ghc-internal.cabal.in
- + libraries/ghc-internal/include/RtsIfaceSymbols.h
- libraries/ghc-internal/src/GHC/Internal/Base.hs
- libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
- libraries/ghc-internal/src/GHC/Internal/ResponseFile.hs
- + libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc
- libraries/ghc-internal/src/GHC/Internal/Stack/Decode.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Quote.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/DerivedCoreProperties.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleLowerCaseMapping.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleTitleCaseMapping.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleUpperCaseMapping.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Version.hs
- + libraries/ghc-internal/tests/backtraces/T26507.hs
- + libraries/ghc-internal/tests/backtraces/T26507.stderr
- libraries/ghc-internal/tests/backtraces/all.T
- libraries/ghc-internal/tests/stack-annotation/all.T
- libraries/ghc-internal/tools/ucd2haskell/ucd.sh
- libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal
- libraries/ghc-internal/tools/ucd2haskell/unicode_version
- libraries/ghc-prim/changelog.md
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/ObjLink.hs
- libraries/ghci/GHCi/Run.hs
- + libraries/template-haskell-lift
- + libraries/template-haskell-quasiquoter
- m4/find_python.m4
- m4/fp_check_pthreads.m4
- m4/fp_cmm_cpp_cmd_with_args.m4
- m4/fp_find_libdw.m4
- − m4/fp_set_cflags_c99.m4
- − m4/fp_settings.m4
- m4/fp_setup_windows_toolchain.m4
- − m4/fp_visibility_hidden.m4
- m4/fptools_alex.m4
- m4/fptools_happy.m4
- m4/fptools_set_c_ld_flags.m4
- m4/ghc_toolchain.m4
- m4/prep_target_file.m4
- + m4/subst_tooldir.m4
- mk/hsc2hs.in
- rts/Apply.cmm
- rts/BeginPrivate.h
- + rts/BuiltinClosures.c
- + rts/BuiltinClosures.h
- rts/Capability.c
- rts/Capability.h
- rts/CloneStack.h
- + rts/ClosureTable.c
- + rts/ClosureTable.h
- rts/Compact.cmm
- rts/ContinuationOps.cmm
- rts/EndPrivate.h
- rts/Exception.cmm
- rts/ExecPage.c
- rts/Hash.c
- rts/IOManager.c
- rts/IOManager.h
- rts/IOManagerInternals.h
- rts/Interpreter.c
- rts/Prelude.h
- rts/PrimOps.cmm
- rts/Printer.c
- rts/ProfHeap.c
- rts/RaiseAsync.c
- rts/RetainerSet.c
- rts/RtsAPI.c
- − rts/RtsDllMain.c
- − rts/RtsDllMain.h
- rts/RtsFlags.c
- rts/RtsSignals.h
- rts/RtsStartup.c
- rts/RtsSymbols.c
- + rts/RtsToHsIface.c
- rts/Schedule.c
- rts/Schedule.h
- rts/StgMiscClosures.cmm
- rts/StgStdThunks.cmm
- rts/Task.c
- rts/Task.h
- rts/ThreadPaused.c
- rts/Threads.c
- + rts/TimeoutQueue.c
- + rts/TimeoutQueue.h
- rts/Timer.c
- rts/configure.ac
- − rts/external-symbols.list.in
- rts/include/Rts.h
- rts/include/RtsAPI.h
- rts/include/Stg.h
- rts/include/rts/Constants.h
- rts/include/rts/Flags.h
- rts/include/rts/NonMoving.h
- rts/include/rts/OSThreads.h
- + rts/include/rts/RtsToHsIface.h
- rts/include/rts/StableName.h
- rts/include/rts/StablePtr.h
- rts/include/rts/Types.h
- rts/include/rts/storage/Block.h
- rts/include/rts/storage/Closures.h
- rts/include/rts/storage/TSO.h
- − rts/include/stg/DLL.h
- rts/include/stg/MiscClosures.h
- rts/include/stg/Prim.h
- rts/js/mem.js
- + rts/posix/FdWakeup.c
- + rts/posix/FdWakeup.h
- + rts/posix/MIO.c
- + rts/posix/MIO.h
- rts/posix/OSMem.c
- rts/posix/OSThreads.c
- + rts/posix/Poll.c
- + rts/posix/Poll.h
- rts/posix/Select.c
- rts/posix/Select.h
- rts/posix/Signals.c
- rts/posix/Signals.h
- + rts/posix/Timeout.c
- + rts/posix/Timeout.h
- libraries/ghc-internal/cbits/atomic.c → rts/prim/atomic.c
- libraries/ghc-internal/cbits/bitrev.c → rts/prim/bitrev.c
- libraries/ghc-internal/cbits/bswap.c → rts/prim/bswap.c
- libraries/ghc-internal/cbits/clz.c → rts/prim/clz.c
- libraries/ghc-internal/cbits/ctz.c → rts/prim/ctz.c
- libraries/ghc-internal/cbits/int64x2minmax.c → rts/prim/int64x2minmax.c
- libraries/ghc-internal/cbits/longlong.c → rts/prim/longlong.c
- libraries/ghc-internal/cbits/mulIntMayOflo.c → rts/prim/mulIntMayOflo.c
- libraries/ghc-internal/cbits/pdep.c → rts/prim/pdep.c
- libraries/ghc-internal/cbits/pext.c → rts/prim/pext.c
- libraries/ghc-internal/cbits/popcnt.c → rts/prim/popcnt.c
- libraries/ghc-internal/cbits/vectorQuotRem.c → rts/prim/vectorQuotRem.c
- libraries/ghc-internal/cbits/word2float.c → rts/prim/word2float.c
- rts/rts.buildinfo.in
- rts/rts.cabal
- rts/sm/BlockAlloc.c
- rts/sm/Evac.c
- rts/sm/Evac.h
- rts/sm/GCTDecl.h
- rts/sm/GCThread.h
- rts/sm/NonMoving.c
- rts/sm/NonMovingMark.c
- rts/sm/Scav.c
- rts/sm/Storage.c
- rts/wasm/JSFFI.c
- rts/wasm/scheduler.cmm
- rts/win32/AwaitEvent.c
- rts/win32/ConsoleHandler.c
- rts/win32/ConsoleHandler.h
- rts/win32/OSThreads.c
- rts/win32/libHSghc-internal.def
- testsuite/driver/cpu_features.py
- testsuite/driver/testglobals.py
- testsuite/driver/testlib.py
- testsuite/tests/arrows/gadt/T17423.stderr
- testsuite/tests/backpack/should_fail/bkpfail11.stderr
- testsuite/tests/backpack/should_fail/bkpfail43.stderr
- testsuite/tests/bytecode/T24634/T24634a.stdout
- testsuite/tests/bytecode/T24634/T24634b.stdout
- + testsuite/tests/bytecode/T26216.hs
- + testsuite/tests/bytecode/T26216.script
- + testsuite/tests/bytecode/T26216.stdout
- + testsuite/tests/bytecode/T26216_aux.hs
- testsuite/tests/bytecode/all.T
- testsuite/tests/codeGen/should_compile/Makefile
- testsuite/tests/codeGen/should_compile/T14999.stdout
- + testsuite/tests/codeGen/should_compile/T20298a.hs
- + testsuite/tests/codeGen/should_compile/T20298a.stderr
- + testsuite/tests/codeGen/should_compile/T20298b.hs
- + testsuite/tests/codeGen/should_compile/T20298b.stderr
- + testsuite/tests/codeGen/should_compile/T20298c.hs
- + testsuite/tests/codeGen/should_compile/T20298c.stderr
- testsuite/tests/codeGen/should_compile/T25166.stdout → testsuite/tests/codeGen/should_compile/T25166.stdout-ws-32
- + testsuite/tests/codeGen/should_compile/T25166.stdout-ws-64
- testsuite/tests/codeGen/should_compile/all.T
- testsuite/tests/codeGen/should_gen_asm/all.T
- + testsuite/tests/codeGen/should_gen_asm/mavx-should-enable-popcnt.asm
- + testsuite/tests/codeGen/should_gen_asm/mavx-should-enable-popcnt.hs
- + testsuite/tests/codeGen/should_gen_asm/msse-option-order.asm
- + testsuite/tests/codeGen/should_gen_asm/msse-option-order.hs
- testsuite/tests/codeGen/should_run/T13825-unit.hs
- testsuite/tests/codeGen/should_run/T23146/all.T
- testsuite/tests/concurrent/prog001/all.T
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- testsuite/tests/cpranal/should_compile/T18174.stderr
- + testsuite/tests/cross/should_run/T26449.hs
- + testsuite/tests/cross/should_run/all.T
- + testsuite/tests/deriving/should_compile/T26396.hs
- testsuite/tests/deriving/should_compile/all.T
- testsuite/tests/deriving/should_fail/T12768.stderr
- testsuite/tests/deriving/should_fail/T1496.stderr
- testsuite/tests/deriving/should_fail/T21302.stderr
- testsuite/tests/deriving/should_fail/T22696b.stderr
- testsuite/tests/deriving/should_fail/T5498.stderr
- testsuite/tests/deriving/should_fail/T7148.stderr
- testsuite/tests/deriving/should_fail/T7148a.stderr
- testsuite/tests/driver/T11429c.stderr
- testsuite/tests/driver/T21682.stderr
- testsuite/tests/driver/T5313.hs
- + testsuite/tests/driver/bytecode-object/A.hs
- + testsuite/tests/driver/bytecode-object/BytecodeForeign.c
- + testsuite/tests/driver/bytecode-object/BytecodeForeign.hs
- + testsuite/tests/driver/bytecode-object/BytecodeMain.hs
- + testsuite/tests/driver/bytecode-object/BytecodeTest.hs
- + testsuite/tests/driver/bytecode-object/Makefile
- + testsuite/tests/driver/bytecode-object/all.T
- + testsuite/tests/driver/bytecode-object/bytecode_object12.stderr
- + testsuite/tests/driver/bytecode-object/bytecode_object13.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object14.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object15.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object16.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object17.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object18.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object19.script
- + testsuite/tests/driver/bytecode-object/bytecode_object19.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object25.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object4.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object5.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object6.stdout
- testsuite/tests/driver/fat-iface/T22405/T22405.stdout
- testsuite/tests/driver/fat-iface/T22405/T22405b.stdout
- testsuite/tests/driver/fat-iface/fat011.stderr
- testsuite/tests/driver/j-space/Makefile
- testsuite/tests/driver/j-space/all.T
- testsuite/tests/driver/j-space/genJspace
- testsuite/tests/driver/multipleHomeUnits/all.T
- testsuite/tests/ghc-api/T10052/T10052.hs
- testsuite/tests/ghc-api/T10942.hs
- testsuite/tests/ghc-api/T20757.hs
- + testsuite/tests/ghc-api/T26264.hs
- + testsuite/tests/ghc-api/T26264.stdout
- testsuite/tests/ghc-api/T8639_api.hs
- testsuite/tests/ghc-api/all.T
- testsuite/tests/ghc-api/annotations-literals/literals.hs
- testsuite/tests/ghc-api/apirecomp001/myghc.hs
- testsuite/tests/ghc-api/settings-escape/T24265.hs
- testsuite/tests/ghc-api/settings-escape/T24265.stderr
- + testsuite/tests/ghc-api/settings-escape/ghc-install-folder/lib with spaces/targets/.gitkeep
- + testsuite/tests/ghci-wasm/Makefile
- + testsuite/tests/ghci-wasm/T26430.hs
- + testsuite/tests/ghci-wasm/T26430A.c
- + testsuite/tests/ghci-wasm/T26430B.c
- + testsuite/tests/ghci-wasm/T26431.hs
- + testsuite/tests/ghci-wasm/T26431.stdout
- + testsuite/tests/ghci-wasm/all.T
- testsuite/tests/ghci.debugger/scripts/break022/all.T
- testsuite/tests/ghci.debugger/scripts/break022/break022.script
- testsuite/tests/ghci.debugger/scripts/break023/all.T
- testsuite/tests/ghci.debugger/scripts/break023/break023.script
- testsuite/tests/ghci/linking/dyn/T3372.hs
- testsuite/tests/ghci/prog001/prog001.T
- testsuite/tests/ghci/prog001/prog001.script
- testsuite/tests/ghci/prog002/prog002.T
- testsuite/tests/ghci/prog002/prog002.script
- testsuite/tests/ghci/prog003/prog003.T
- testsuite/tests/ghci/prog003/prog003.script
- testsuite/tests/ghci/prog005/prog005.T
- testsuite/tests/ghci/prog005/prog005.script
- testsuite/tests/ghci/prog010/all.T
- testsuite/tests/ghci/prog010/ghci.prog010.script
- testsuite/tests/ghci/prog012/all.T
- testsuite/tests/ghci/prog012/prog012.script
- testsuite/tests/ghci/recompTHghci/all.T
- testsuite/tests/ghci/recompTHghci/recompTHghci.script
- testsuite/tests/ghci/scripts/T18330.script
- testsuite/tests/ghci/scripts/T18330.stdout
- testsuite/tests/ghci/scripts/T1914.script
- testsuite/tests/ghci/scripts/T20587.script
- testsuite/tests/ghci/scripts/T6106.script
- testsuite/tests/ghci/scripts/T8353.script
- testsuite/tests/ghci/scripts/all.T
- testsuite/tests/ghci/scripts/ghci038.script
- testsuite/tests/ghci/scripts/ghci058.script
- testsuite/tests/ghci/scripts/ghci063.script
- − testsuite/tests/ghci/shell.hs
- testsuite/tests/ghci/should_run/PackedDataCon/packeddatacon.T
- testsuite/tests/ghci/should_run/UnboxedTuples/unboxedtuples.T
- testsuite/tests/ghci/should_run/UnliftedDataTypeInterp/unlifteddatatypeinterp.T
- testsuite/tests/impredicative/T17332.stderr
- testsuite/tests/indexed-types/should_compile/PushedInAsGivens.stderr
- testsuite/tests/indexed-types/should_fail/T14887.stderr
- testsuite/tests/indexed-types/should_fail/T26176.stderr
- testsuite/tests/indexed-types/should_fail/T2693.stderr
- testsuite/tests/indexed-types/should_fail/T4093b.stderr
- testsuite/tests/indexed-types/should_fail/T8518.stderr
- testsuite/tests/indexed-types/should_fail/T9662.stderr
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
- testsuite/tests/interface-stability/ghc-prim-exports.stdout
- testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32
- testsuite/tests/linear/should_fail/Linear17.stderr
- testsuite/tests/linear/should_fail/LinearLet7.stderr
- testsuite/tests/linear/should_fail/T19361.stderr
- testsuite/tests/linters/all.T
- + testsuite/tests/llvm/should_run/T26065.hs
- + testsuite/tests/llvm/should_run/T26065.stdout
- testsuite/tests/llvm/should_run/all.T
- testsuite/tests/numeric/should_run/foundation.hs
- testsuite/tests/overloadedrecflds/should_compile/BootFldReexport.stderr
- testsuite/tests/overloadedrecflds/should_fail/T16745.stderr
- testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr
- + testsuite/tests/overloadedrecflds/should_fail/T26391.hs
- + testsuite/tests/overloadedrecflds/should_fail/T26391.stderr
- + testsuite/tests/overloadedrecflds/should_fail/T26480.hs
- + testsuite/tests/overloadedrecflds/should_fail/T26480.stderr
- + testsuite/tests/overloadedrecflds/should_fail/T26480_aux1.hs
- + testsuite/tests/overloadedrecflds/should_fail/T26480_aux2.hs
- + testsuite/tests/overloadedrecflds/should_fail/T26480b.hs
- + testsuite/tests/overloadedrecflds/should_fail/T26480b.stderr
- testsuite/tests/overloadedrecflds/should_fail/all.T
- testsuite/tests/overloadedrecflds/should_fail/hasfieldfail01.stderr
- testsuite/tests/overloadedrecflds/should_fail/hasfieldfail02.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail10.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail11.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail13.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail8.hs
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail8.stderr
- testsuite/tests/parser/should_fail/T16270h.stderr
- + testsuite/tests/parser/should_fail/T26418.hs
- + testsuite/tests/parser/should_fail/T26418.stderr
- testsuite/tests/parser/should_fail/all.T
- + testsuite/tests/parser/should_run/T26415.hs
- + testsuite/tests/parser/should_run/T26415.stdout
- testsuite/tests/parser/should_run/all.T
- testsuite/tests/partial-sigs/should_compile/T21719.stderr
- + testsuite/tests/patsyn/should_compile/T26465b.hs
- + testsuite/tests/patsyn/should_compile/T26465c.hs
- + testsuite/tests/patsyn/should_compile/T26465d.hs
- + testsuite/tests/patsyn/should_compile/T26465d.stderr
- testsuite/tests/patsyn/should_compile/all.T
- + testsuite/tests/patsyn/should_fail/T26465.hs
- + testsuite/tests/patsyn/should_fail/T26465.stderr
- testsuite/tests/patsyn/should_fail/all.T
- testsuite/tests/perf/compiler/Makefile
- testsuite/tests/perf/compiler/MultiLayerModulesDefsGhci.script
- + testsuite/tests/perf/compiler/MultiLayerModulesDefsGhciWithBytecodeFiles.script
- testsuite/tests/perf/compiler/all.T
- testsuite/tests/perf/should_run/T3586.hs
- testsuite/tests/perf/should_run/UniqLoop.hs
- testsuite/tests/perf/should_run/all.T
- testsuite/tests/plugins/annotation-plugin/SayAnnNames.hs
- testsuite/tests/plugins/late-plugin/LatePlugin.hs
- testsuite/tests/plugins/simple-plugin/Simple/ReplacePlugin.hs
- + testsuite/tests/pmcheck/should_compile/T26400.hs
- + testsuite/tests/pmcheck/should_compile/T26400.stderr
- + testsuite/tests/pmcheck/should_compile/T26400b.hs
- testsuite/tests/pmcheck/should_compile/all.T
- testsuite/tests/polykinds/T13393.stderr
- − testsuite/tests/process/process010.stdout-i386-unknown-solaris2
- testsuite/tests/quantified-constraints/T19690.stderr
- testsuite/tests/quantified-constraints/T19921.stderr
- testsuite/tests/quantified-constraints/T21006.stderr
- testsuite/tests/regalloc/regalloc_unit_tests.hs
- testsuite/tests/rename/should_fail/T19843h.stderr
- testsuite/tests/rep-poly/T12709.stderr
- testsuite/tests/roles/should_compile/Roles13.stderr
- testsuite/tests/roles/should_fail/RolesIArray.stderr
- + testsuite/tests/rts/ClosureTable.hs
- + testsuite/tests/rts/ClosureTable_c.c
- testsuite/tests/rts/T22859.hs
- + testsuite/tests/rts/T26408.hs
- + testsuite/tests/rts/T26408.stderr
- + testsuite/tests/rts/TimeoutQueue.c
- + testsuite/tests/rts/TimeoutQueue.stdout
- testsuite/tests/rts/all.T
- + testsuite/tests/rts/ipe/distinct-tables/Main.hs
- + testsuite/tests/rts/ipe/distinct-tables/Makefile
- + testsuite/tests/rts/ipe/distinct-tables/X.hs
- + testsuite/tests/rts/ipe/distinct-tables/all.T
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables01.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables02.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables03.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables04.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables05.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables06.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables07.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables08.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables09.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables10.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables11.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables12.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables13.stdout
- − testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-32-mingw32
- − testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr-ws-32-mingw32
- testsuite/tests/rts/linker/T2615.hs
- − testsuite/tests/rts/outofmem.stderr-i386-apple-darwin
- − testsuite/tests/rts/outofmem.stderr-i386-unknown-mingw32
- − testsuite/tests/rts/outofmem.stderr-powerpc-apple-darwin
- testsuite/tests/simd/should_run/all.T
- + testsuite/tests/simd/should_run/simd015.hs
- + testsuite/tests/simd/should_run/simd015.stdout
- + testsuite/tests/simd/should_run/simd016.hs
- + testsuite/tests/simd/should_run/simd016.stdout
- + testsuite/tests/simd/should_run/simd017.hs
- + testsuite/tests/simd/should_run/simd017.stdout
- testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs
- testsuite/tests/simplCore/should_compile/DsSpecPragmas.stderr
- testsuite/tests/simplCore/should_compile/OpaqueNoCastWW.stderr
- testsuite/tests/simplCore/should_compile/T17673.stderr
- testsuite/tests/simplCore/should_compile/T18078.stderr
- testsuite/tests/simplCore/should_compile/T18995.stderr
- testsuite/tests/simplCore/should_compile/T19890.stderr
- testsuite/tests/simplCore/should_compile/T21948.stderr
- testsuite/tests/simplCore/should_compile/T21960.stderr
- testsuite/tests/simplCore/should_compile/T24808.stderr
- − testsuite/tests/simplCore/should_compile/T25713.stderr
- testsuite/tests/simplCore/should_compile/T4201.stdout
- testsuite/tests/simplCore/should_compile/T8331.stderr
- testsuite/tests/simplCore/should_compile/rule2.stderr
- testsuite/tests/simplCore/should_compile/simpl017.stderr
- testsuite/tests/simplStg/should_compile/T22840.stderr
- + testsuite/tests/tcplugins/T26395.hs
- + testsuite/tests/tcplugins/T26395.stderr
- + testsuite/tests/tcplugins/T26395_Plugin.hs
- testsuite/tests/tcplugins/all.T
- testsuite/tests/th/T10945.stderr
- testsuite/tests/th/T8761.stderr
- testsuite/tests/th/TH_StaticPointers02.stderr
- testsuite/tests/typecheck/no_skolem_info/T20232.stderr
- testsuite/tests/typecheck/should_compile/T11339.stderr
- testsuite/tests/typecheck/should_compile/T14434.hs
- + testsuite/tests/typecheck/should_compile/T17705.hs
- + testsuite/tests/typecheck/should_compile/T26376.hs
- + testsuite/tests/typecheck/should_compile/T26457.hs
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_fail/DoExpansion3.stderr
- testsuite/tests/typecheck/should_fail/T11672.stderr
- testsuite/tests/typecheck/should_fail/T12177.stderr
- testsuite/tests/typecheck/should_fail/T12373.stderr
- testsuite/tests/typecheck/should_fail/T15801.stderr
- testsuite/tests/typecheck/should_fail/T15807.stderr
- testsuite/tests/typecheck/should_fail/T16074.stderr
- testsuite/tests/typecheck/should_fail/T18357a.stderr
- testsuite/tests/typecheck/should_fail/T19627.stderr
- testsuite/tests/typecheck/should_fail/T20241b.stderr
- testsuite/tests/typecheck/should_fail/T20666.stderr
- testsuite/tests/typecheck/should_fail/T20666a.stderr
- testsuite/tests/typecheck/should_fail/T20666b.stderr
- testsuite/tests/typecheck/should_fail/T21530a.stderr
- testsuite/tests/typecheck/should_fail/T22707.stderr
- testsuite/tests/typecheck/should_fail/T22912.stderr
- testsuite/tests/typecheck/should_fail/T23427.stderr
- testsuite/tests/typecheck/should_fail/T24064.stderr
- + testsuite/tests/typecheck/should_fail/T26330.hs
- + testsuite/tests/typecheck/should_fail/T26330.stderr
- testsuite/tests/typecheck/should_fail/T8142.stderr
- testsuite/tests/typecheck/should_fail/T8603.stderr
- testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr
- testsuite/tests/typecheck/should_fail/VisFlag1.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/typecheck/should_fail/tcfail128.stderr
- testsuite/tests/typecheck/should_fail/tcfail153.stderr
- testsuite/tests/typecheck/should_fail/tcfail168.stderr
- testsuite/tests/typecheck/should_fail/tcfail177.stderr
- testsuite/tests/typecheck/should_fail/tcfail185.stderr
- testsuite/tests/typecheck/should_run/Typeable1.stderr
- + testsuite/tests/unboxedsums/UbxSumUnpackedSize.hs
- + testsuite/tests/unboxedsums/UbxSumUnpackedSize.stdout
- + testsuite/tests/unboxedsums/UbxSumUnpackedSize.stdout-ws-32
- testsuite/tests/unboxedsums/all.T
- testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Parsers.hs
- utils/check-exact/Preprocess.hs
- utils/deriveConstants/Main.hs
- utils/genprimopcode/Main.hs
- utils/genprimopcode/Syntax.hs
- utils/ghc-pkg/Main.hs
- utils/ghc-pkg/ghc-pkg.cabal.in
- utils/ghc-toolchain/exe/Main.hs
- utils/ghc-toolchain/ghc-toolchain.cabal
- + utils/ghc-toolchain/src/GHC/Toolchain/Library.hs
- utils/ghc-toolchain/src/GHC/Toolchain/PlatformDetails.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Target.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cpp.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cxx.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/MergeObjs.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Utils.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
- utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs
- utils/haddock/hypsrc-test/Main.hs
- utils/haddock/hypsrc-test/ref/src/Bug1091.html
- utils/haddock/hypsrc-test/ref/src/CPP.html
- utils/haddock/hypsrc-test/ref/src/Classes.html
- utils/haddock/hypsrc-test/ref/src/Constructors.html
- utils/haddock/hypsrc-test/ref/src/Identifiers.html
- utils/haddock/hypsrc-test/ref/src/LinkingIdentifiers.html
- utils/haddock/hypsrc-test/ref/src/Literals.html
- utils/haddock/hypsrc-test/ref/src/Operators.html
- utils/haddock/hypsrc-test/ref/src/Polymorphism.html
- utils/haddock/hypsrc-test/ref/src/PositionPragmas.html
- utils/haddock/hypsrc-test/ref/src/Quasiquoter.html
- utils/haddock/hypsrc-test/ref/src/Records.html
- utils/haddock/hypsrc-test/ref/src/TemplateHaskellQuasiquotes.html
- utils/haddock/hypsrc-test/ref/src/TemplateHaskellSplices.html
- utils/haddock/hypsrc-test/ref/src/Types.html
- utils/haddock/hypsrc-test/ref/src/UsingQuasiquotes.html
- utils/jsffi/dyld.mjs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/05ac0a020dad30c7505b0243ccac31…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/05ac0a020dad30c7505b0243ccac31…
You're receiving this email because of your account on gitlab.haskell.org.
1
0