[Git][ghc/ghc][wip/clyring/GHC-ByteOrder-naming] 198 commits: compiler: Exclude units with no exposed modules from unused package check
by Matthew Craven (@clyring) 11 Jan '26
by Matthew Craven (@clyring) 11 Jan '26
11 Jan '26
Matthew Craven pushed to branch wip/clyring/GHC-ByteOrder-naming at Glasgow Haskell Compiler / GHC
Commits:
5cdcfaed by Ben Gamari at 2025-11-06T09:01:36-05:00
compiler: Exclude units with no exposed modules from unused package check
Such packages cannot be "used" in the Haskell sense of the word yet
are nevertheless necessary as they may provide, e.g., C object code or
link flags.
Fixes #24120.
- - - - -
74b8397a by Brandon Chinn at 2025-11-06T09:02:19-05:00
Replace deprecated argparse.FileType
- - - - -
36ddf988 by Ben Gamari at 2025-11-06T09:03:01-05:00
Bump unix submodule to 2.8.8.0
Closes #26474.
- - - - -
c32b3a29 by fendor at 2025-11-06T09:03:43-05:00
Fix assertion in `postStringLen` to account for \0 byte
We fix the assertion to handle trailing \0 bytes in `postStringLen`.
Before this change, the assertion looked like this:
ASSERT(eb->begin + eb->size > eb->pos + len + 1);
Let's assume some values to see why this is actually off by one:
eb->begin = 0
eb->size = 1
eb->pos = 0
len = 1
then the assertion would trigger correctly:
0 + 1 > 0 + 1 + 1 => 1 > 2 => false
as there is not enough space for the \0 byte (which is the trailing +1).
However, if we change `eb->size = 2`, then we do have enough space for a
string of length 1, but the assertion still fails:
0 + 2 > 0 + 1 + 1 => 2 > 2 => false
Which causes the assertion to fail if there is exactly enough space for
the string with a trailing \0 byte.
Clearly, the assertion should be `>=`!
If we switch around the operand, it should become more obvious that `<=`
is the correct comparison:
ASSERT(eb->pos + len + 1 <= eb->begin + eb->size);
This is expresses more naturally that the current position plus the
length of the string (and the null byte) must be smaller or equal to the
overall size of the buffer.
This change also is in line with the implementation in
`hasRoomForEvent` and `hasRoomForVariableEvent`:
```
StgBool hasRoomForEvent(EventsBuf *eb, EventTypeNum eNum)
{
uint32_t size = ...;
if (eb->pos + size > eb->begin + eb->size)
...
```
the check `eb->pos + size > eb->begin + eb->size` is identical to
`eb->pos + size <= eb->begin + eb->size` plus a negation.
- - - - -
3034a6f2 by Ben Gamari at 2025-11-06T09:04:24-05:00
Bump os-string submodule to 2.0.8
- - - - -
39567e85 by Cheng Shao at 2025-11-06T09:05:06-05:00
rts: use computed goto for instruction dispatch in the bytecode interpreter
This patch uses computed goto for instruction dispatch in the bytecode
interpreter. Previously instruction dispatch is done by a classic
switch loop, so executing the next instruction requires two jumps: one
to the start of the switch loop and another to the case block based on
the instruction tag. By using computed goto, we can build a jump table
consisted of code addresses indexed by the instruction tags
themselves, so executing the next instruction requires only one jump,
to the destination directly fetched from the jump table.
Closes #12953.
- - - - -
93fc7265 by sheaf at 2025-11-06T21:33:24-05:00
Correct hasFixedRuntimeRep in matchExpectedFunTys
This commit fixes a bug in the representation-polymormorphism check in
GHC.Tc.Utils.Unify.matchExpectedFunTys. The problem was that we put
the coercion resulting from hasFixedRuntimeRep in the wrong place,
leading to the Core Lint error reported in #26528.
The change is that we have to be careful when using 'mkWpFun': it
expects **both** the expected and actual argument types to have a
syntactically fixed RuntimeRep, as explained in Note [WpFun-FRR-INVARIANT]
in GHC.Tc.Types.Evidence.
On the way, this patch improves some of the commentary relating to
other usages of 'mkWpFun' in the compiler, in particular in the view
pattern case of 'tc_pat'. No functional changes, but some stylistic
changes to make the code more readable, and make it easier to understand
how we are upholding the WpFun-FRR-INVARIANT.
Fixes #26528
- - - - -
c052c724 by Simon Peyton Jones at 2025-11-06T21:34:06-05:00
Fix a horrible shadowing bug in implicit parameters
Fixes #26451. The change is in GHC.Tc.Solver.Monad.updInertDicts
where we now do /not/ delete /Wanted/ implicit-parameeter constraints.
This bug has been in GHC since 9.8! But it's quite hard to provoke;
I contructed a tests in T26451, but it was hard to do so.
- - - - -
b253013e by Georgios Karachalias at 2025-11-07T17:21:57-05:00
Remove the `CoreBindings` constructor from `LinkablePart`
Adjust HscRecompStatus to disallow unhydrated WholeCoreBindings
from being passed as input to getLinkDeps (which would previously
panic in this case).
Fixes #26497
- - - - -
ac7b737e by Sylvain Henry at 2025-11-07T17:22:51-05:00
Testsuite: pass ext-interp test way (#26552)
Note that some tests are still marked as broken with the ext-interp way
(see #26552 and #14335)
- - - - -
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>
- - - - -
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.
- - - - -
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.
- - - - -
0a64a78b by Sven Tennie at 2025-11-15T20:31:10-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.)
- - - - -
15b311be by sheaf at 2025-11-15T20:32:02-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).
- - - - -
b33284c7 by sheaf at 2025-11-15T20:32:02-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
-------------------------
- - - - -
b6faf5d0 by sheaf at 2025-11-15T20:32:02-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.
- - - - -
682bf979 by Mike Pilgrem at 2025-11-16T16:44:14+00:00
Fix #26293 Valid stack.yaml for hadrian
- - - - -
acc70c3a by Simon Peyton Jones at 2025-11-18T16:21:20-05:00
Fix a bug in defaulting
Addresses #26582
Defaulting was doing some unification but then failing to
iterate. Silly.
I discovered that the main solver was unnecessarily iterating even
if there was a unification for an /outer/ unification variable, so
I fixed that too.
- - - - -
c12fa73e by Simon Peyton Jones at 2025-11-19T02:55:01-05:00
Make PmLit be in Ord, and use it in Map
This MR addresses #26514, by changing from
data PmAltConSet = PACS !(UniqDSet ConLike) ![PmLit]
to
data PmAltConSet = PACS !(UniqDSet ConLike) !(Map PmLit PmLit)
This matters when doing pattern-match overlap checking, when there
is a very large set of patterns. For most programs it makes
no difference at all.
For the N=5000 case of the repro case in #26514, compiler
mutator time (with `-fno-code`) goes from 1.9s to 0.43s.
All for the price for an Ord instance for PmLit
- - - - -
41b84f40 by sheaf at 2025-11-19T02:55:52-05:00
Add passing tests for #26311 and #26072
This commit adds two tests cases that now pass since landing the changes
to typechecking of data constructors in b33284c7.
Fixes #26072 #26311
- - - - -
1faa758a by sheaf at 2025-11-19T02:55:52-05:00
mkCast: weaken bad cast warning for multiplicity
This commit weakens the warning message emitted when constructing a bad
cast in mkCast to ignore multiplicity.
Justification: since b33284c7, GHC uses sub-multiplicity coercions to
typecheck data constructors. The coercion optimiser is free to discard
these coercions, both for performance reasons, and because GHC's Core
simplifier does not (yet) preserve linearity.
We thus weaken 'mkCast' to use 'eqTypeIgnoringMultiplicity' instead of
'eqType', to avoid getting many spurious warnings about mismatched
multiplicities.
- - - - -
55eab80d by Sylvain Henry at 2025-11-20T17:33:13-05:00
Build external interpreter program on demand (#24731)
This patch teaches GHC how to build the external interpreter program
when it is missing. As long as we have the `ghci` library, doing this is
trivial so most of this patch is refactoring for doing it sanely.
- - - - -
08bbc028 by Rodrigo Mesquita at 2025-11-20T17:33:54-05:00
Add tests for #23973 and #26565
These were fixed by 4af4f0f070f83f948e49ad5d7835fd91b8d3f0e6 in !10417
- - - - -
6b42232c by sheaf at 2025-11-20T17:34:35-05:00
Mark T26410_ffi as fragile on Windows
As seen in #26595, this test intermittently fails on Windows.
This commit marks it as fragile, until we get around to fixing it.
- - - - -
b7b7c049 by Andrew Lelechenko at 2025-11-21T21:04:01+00:00
Add nubOrd / nubOrdBy to Data.List and Data.List.NonEmpty
As per https://github.com/haskell/core-libraries-committee/issues/336
- - - - -
352d5462 by Marc Scholten at 2025-11-22T10:33:03-05:00
Fix haddock test runner to handle UTF-8 output
xhtml 3000.4.0.0 now produces UTF-8 output instead of escaping non-ASCII characters.
When using --test-accept it previously wrote files in the wrong encoding
because they have not been decoded properly when reading the files.
- - - - -
48a3ed57 by Simon Peyton Jones at 2025-11-25T15:33:54+00:00
Add a fast-path for args=[] to occAnalApp
In the common case of having not arguments, occAnalApp
was doing redundant work.
- - - - -
951e5ed9 by Simon Peyton Jones at 2025-11-25T15:33:54+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
- - - - -
f1959dfc by Simon Peyton Jones at 2025-11-26T11:58:07+00:00
Remove a quadratic-cost assertion check in mkCoreApp
See the new Note [Assertion checking in mkCoreApp]
- - - - -
98fa0d36 by Simon Hengel at 2025-11-27T17:54:57-05:00
Fix typo in docs/users_guide/exts/type_families.rst
- - - - -
5b97e5ce by Simon Hengel at 2025-11-27T17:55:37-05:00
Fix broken RankNTypes example in user's guide
- - - - -
fa2aaa00 by Simon Peyton Jones at 2025-11-27T17:56:18-05:00
Switch off specialisation in ExactPrint
In !15057 (where we re-introduced -fpolymoprhic-specialisation) we found
that ExactPrint's compile time blew up by a factor of 5. It turned out
to be caused by bazillions of specialisations of `markAnnotated`.
Since ExactPrint isn't perf-critical, it does not seem worth taking
the performance hit, so this patch switches off specialisation in
this one module.
- - - - -
1fd25987 by Simon Peyton Jones at 2025-11-27T17:56:18-05:00
Switch -fpolymorphic-specialisation on by default
This patch addresses #23559.
Now that !10479 has landed and #26329 is fixed, we can switch on
polymorphic specialisation by default, addressing a bunch of other
tickets listed in #23559.
Metric changes:
* CoOpt_Singleton: +4% compiler allocations: we just get more
specialisations
* info_table_map_perf: -20% decrease in compiler allocations.
This is caused by using -fno-specialise in ExactPrint.hs
Without that change we get a 4x blow-up in compile time;
see !15058 for details
Metric Decrease:
info_table_map_perf
Metric Increase:
CoOpt_Singletons
- - - - -
b7fe7445 by Matthew Pickering at 2025-11-27T17:56:59-05:00
rts: Fix a deadlock with eventlog flush interval and RTS shutdown
The ghc_ticker thread attempts to flush at the eventlog tick interval, this requires
waiting to take all capabilities.
At the same time, the main thread is shutting down, the schedule is
stopped and then we wait for the ticker thread to finish.
Therefore we are deadlocked.
The solution is to use `newBoundTask/exitMyTask`, so that flushing can
cooperate with the scheduler shutdown.
Fixes #26573
- - - - -
1d4a1229 by sheaf at 2025-11-27T17:58:02-05:00
SimpleOpt: don't subst in pushCoercionIntoLambda
It was noticed in #26589 that the change in 15b311be was incorrect:
the simple optimiser carries two different substitution-like pieces of
information: 'soe_subst' (from InVar to OutExpr) and 'soe_inl'
(from InId to InExpr). It is thus incorrect to have 'pushCoercionIntoLambda'
apply the substitution from 'soe_subst' while discarding 'soe_inl'
entirely, which is what was done in 15b311be.
Instead, we change back pushCoercionIntoLambda to take an InScopeSet,
and optimise the lambda before calling 'pushCoercionIntoLambda' to avoid
mixing InExpr with OutExpr, or mixing two InExpr with different
environments. We can then call 'soeZapSubst' without problems.
Fixes #26588 #26589
- - - - -
84a087d5 by Sylvain Henry at 2025-11-28T17:35:28-05:00
Fix PIC jump tables on Windows (#24016)
Avoid overflows in jump tables by using a base label closer to the jump
targets. See added Note [Jump tables]
- - - - -
82db7042 by Zubin Duggal at 2025-11-28T17:36:10-05:00
rts/linker/PEi386: Copy strings before they are inserted into LoadedDllCache. The original strings are temporary and might be freed at an arbitrary point.
Fixes #26613
- - - - -
ff3f0d09 by Ben Gamari at 2025-11-29T18:34:28-05:00
gitlab-ci: Run ghcup-metadata jobs on OpenCape runners
This significantly reduces our egress traffic
and makes the jobs significantly faster.
- - - - -
ef0dc33b by Matthew Pickering at 2025-11-29T18:35:10-05:00
Use 'OsPath' in getModificationTimeIfExists
This part of the compiler is quite hot during recompilation checking in
particular since the filepaths will be translated to a string. It is
better to use the 'OsPath' native function, which turns out to be easy
to do.
- - - - -
fa3bd0a6 by Georgios Karachalias at 2025-11-29T18:36:05-05:00
Use OsPath in PkgDbRef and UnitDatabase, not FilePath
- - - - -
0d7c05ec by Ben Gamari at 2025-12-01T03:13:46-05:00
hadrian: Place user options after package arguments
This makes it easier for the user to override the default package
arguments with `UserSettings.hs`.
Fixes #25821.
-------------------------
Metric Decrease:
T14697
-------------------------
- - - - -
3b2c4598 by Vladislav Zavialov at 2025-12-01T03:14:29-05:00
Namespace-specified wildcards in import/export lists (#25901)
This change adds support for top-level namespace-specified wildcards
`type ..` and `data ..` to import and export lists.
Examples:
import M (type ..) -- imports all type and class constructors from M
import M (data ..) -- imports all data constructors and terms from M
module M (type .., f) where
-- exports all type and class constructors defined in M,
-- plus the function 'f'
The primary intended usage of this feature is in combination with module
aliases, allowing namespace disambiguation:
import Data.Proxy as T (type ..) -- T.Proxy is unambiguously the type constructor
import Data.Proxy as D (data ..) -- D.Proxy is unambiguously the data constructor
The patch accounts for the interactions of wildcards with:
* Imports with `hiding` clauses
* Import warnings -Wunused-imports, -Wdodgy-imports
* Export warnings -Wduplicate-exports, -Wdodgy-exports
Summary of the changes:
1. Move the NamespaceSpecifier type from GHC.Hs.Binds to GHC.Hs.Basic,
making it possible to use it in more places in the AST.
2. Extend the AST (type: IE) with a representation of `..`, `type ..`,
and `data ..` (constructor: IEWholeNamespace). Per the proposal, the
plain `..` is always rejected with a dedicated error message.
3. Extend the grammar in Parser.y with productions for `..`, `type ..`,
and `data ..` in both import and export lists.
4. Implement wildcard imports by updating the `filterImports` function
in GHC.Rename.Names; the logic for IEWholeNamespace is roughly
modeled after the Nothing (no explicit import list) case.
5. Implement wildcard exports by updating the `exports_from_avail`
function in GHC.Tc.Gen.Export; the logic for IEWholeNamespace is
closely modeled after the IEModuleContents case.
6. Refactor and extend diagnostics to report the new warnings and
errors. See PsErrPlainWildcardImport, DodgyImportsWildcard,
PsErrPlainWildcardExport, DodgyExportsWildcard,
TcRnDupeWildcardExport.
Note that this patch is specifically about top-level import/export
items. Subordinate import/export items are left unchanged.
- - - - -
c71faa76 by Luite Stegeman at 2025-12-01T03:16:05-05:00
rts: Handle overflow of ELF section header string table
If the section header string table is stored in a section greater
than or equal to SHN_LORESERVE (0xff00), the 16-bit field e_shstrndx
in the ELF header does not contain the section number, but rather
an overflow value SHN_XINDEX (0xffff) indicating that we need to look
elsewhere.
This fixes the linker by not using e_shstrndx directly but calling
elf_shstrndx, which correctly handles the SHN_XINDEX value.
Fixes #26603
- - - - -
ab20eb54 by Mike Pilgrem at 2025-12-01T22:46:55+00:00
Re CLC issue 292 Warn GHC.Internal.List.{init,last} are partial
Also corrects the warning for `tail` to refer to `Data.List.uncons` (like the existing warning for `head`).
In module `Settings.Warnings`, applies `-Wno-x-partial` to the `filepath`, and `parsec` packages (outside GHC's repository).
Also bumps submodules.
- - - - -
fc1d7f79 by Jade Lovelace at 2025-12-02T11:04:09-05:00
docs: fix StandaloneKindSignatures in DataKinds docs
These should be `type` as otherwise GHC reports a duplicate definition
error.
- - - - -
beae879b by Rodrigo Mesquita at 2025-12-03T15:42:37+01:00
task: Substitute some datatypes for newtypes
* Substitutes some data type declarations for newtype declarations
* Adds comment to `LlvmConfigCache`, which must decidedly not be a
newtype.
Fixes #23555
- - - - -
3bd7dd44 by mangoiv at 2025-12-04T04:36:45-05:00
Renamer: reinstate the template haskell level check in notFound
Out-of-scope names might be caused by a staging error, as is explained by
Note [Out of scope might be a staging error] in GHC.Tc.Utils.Env.hs.
This logic was assumed to be dead code after 217caad1 and has thus been
removed. This commit reintroduces it and thus fixes issue #26099.
- - - - -
0318010b by Zubin Duggal at 2025-12-04T04:37:27-05:00
testlib: Optionally include the way name in the expected output file
This allows us to have different outputs for different ways.
- - - - -
6d945fdd by Zubin Duggal at 2025-12-04T04:37:27-05:00
testsuite: Accept output of tests failing in ext-interp way due to differing compilation requirements
Fixes #26552
- - - - -
0ffc5243 by Cheng Shao at 2025-12-04T04:38:09-05:00
devx: minor fixes for compile_flags.txt
This patch includes minor fixes for compile_flags.txt to improve
developer experience when using clangd as language server to hack on
RTS C sources:
- Ensure `-fPIC` is passed and `__PIC__` is defined, to be coherent
with `-DDYNAMIC` and ensure the `__PIC__` guarded code paths are
indexed
- Add the missing `-DRtsWay` definition, otherwise a few source files
like `RtsUtils.c` and `Trace.c` would produce clangd errors
- - - - -
e36a5fcb by Matthew Pickering at 2025-12-05T16:25:57-05:00
Add support for building bytecode libraries
A bytecode library is a collection of bytecode files (.gbc) and a
library which combines together additional object files.
A bytecode library is created by invoking GHC with the `-bytecodelib`
flag.
A library can be created from in-memory `ModuleByteCode` linkables or
by passing `.gbc` files as arguments on the command line.
Fixes #26298
- - - - -
8f9ae339 by Matthew Pickering at 2025-12-05T16:25:57-05:00
Load bytecode libraries to satisfy package dependencies
This commit allows you to use a bytecode library to satisfy a package
dependency when using the interpreter.
If a user enables `-fprefer-byte-code`, then if a package provides a
bytecode library, that will be loaded and used to satisfy the
dependency.
The main change is to separate the relevant parts of the `LoaderState`
into external and home package byte code. Bytecode is loaded into either
the home package or external part (similar to HPT/EPS split), HPT
bytecode can be unloaded. External bytecode is never unloaded.
The unload function has also only been called with an empty list of
"stable linkables" for a long time. It has been modified to directly
implement a complete unloading of the home package bytecode linkables.
At the moment, the bytecode libraries are found in the "library-dirs"
field from the package description. In the future when `Cabal`
implements support for "bytecode-library-dirs" field, we can read the
bytecode libraries from there. No changes to the Cabal submodule are
necessary at the moment.
Four new tests are added in testsuite/tests/cabal, which generate fake
package descriptions and test loading the libraries into GHCi.
Fixes #26298
- - - - -
54458ce4 by mangoiv at 2025-12-05T16:26:50-05:00
ExplicitLevelImports: improve documentation of the code
- more explicit names for variable names like `flg` or `topLevel`
- don't pass the same value twice to functions
- some explanations of interesting but undocumented code paths
- adjust comment to not mention non-existent error message
- - - - -
c7061392 by mangoiv at 2025-12-05T16:27:42-05:00
driver: don't expect nodes to exist when checking paths between them
In `mgQueryZero`, previously node lookups were expected to never fail,
i.e. it was expected that when calculating the path between two nodes in
a zero level import graph, both nodes would always exist. This is not
the case, e.g. in some situations involving exact names (see the
test-case). The fix is to first check whether the node is present in the
graph at all, instead of panicking, just to report that there is no
path.
Closes #26568
- - - - -
d6cf8463 by Peng Fan at 2025-12-06T11:06:28-05:00
NCG/LA64: Simplify genCCall into two parts
genCCall is too long, so it's been simplified into two parts:
genPrim and genLibCCall.
Suggested by Andreas Klebinger
- - - - -
9d371d23 by Matthew Pickering at 2025-12-06T11:07:09-05:00
hadrian: Use a response file to invoke GHC for dep gathering.
In some cases we construct an argument list too long for GHC to
handle directly on windows. This happens when we generate
the dependency file because the command line will contain
references to a large number of .hs files.
To avoid this we now invoke GHC using a response file when
generating dependencies to sidestep length limitations.
Note that we only pass the actual file names in the dependency
file. Why? Because this side-steps #26560
- - - - -
0043bfb0 by Marc Scholten at 2025-12-06T11:08:03-05:00
update xhtml to 3000.4.0.0
haddock-api: bump xhtml bounds
haddock-api: use lazy text instead of string to support xhtml 3000.4.0.0
Bumping submodule xhtml to 3000.4.0.0
add xhtml to stage0Packages
remove unused import of writeUtf8File
Remove redundant import
Update haddock golden files for xhtml 3000.4.0.0
Metric Decrease:
haddock.Cabal
haddock.base
- - - - -
fc958fc9 by Julian Ospald at 2025-12-06T11:08:53-05:00
rts: Fix object file format detection in loadArchive
Commit 76d1041dfa4b96108cfdd22b07f2b3feb424dcbe seems to
have introduced this bug, ultimately leading to failure of
test T11788. I can only theorize that this test isn't run
in upstream's CI, because they don't build a static GHC.
The culprit is that we go through the thin archive, trying
to follow the members on the filesystem, but don't
re-identify the new object format of the member. This pins
`object_fmt` to `NotObject` from the thin archive.
Thanks to @angerman for spotting this.
- - - - -
0f297f6e by mangoiv at 2025-12-06T11:09:44-05:00
users' guide: don't use f strings in the python script to ensure compatibility with python 3.5
- - - - -
3bfe7aa2 by Matthew Pickering at 2025-12-07T12:18:57-05:00
ci: Try using multi repl in ghc-in-ghci test
This should be quite a bit faster than the ./hadrian/ghci command as it
doesn't properly build all the dependencies.
- - - - -
2ef1601a by Rodrigo Mesquita at 2025-12-07T12:19:38-05:00
Stack.Decode: Don't error on bitmap size 0
A RET_BCO may have a bitmap with no payload.
In that case, the bitmap = 0.
One can observe this by using -ddump-bcos and interpreting
```
main = pure ()
```
Observe, for instance, that the BCO for this main function has size 0:
```
ProtoBCO Main.main#0:
\u []
break<main:Main,0>() GHC.Internal.Base.pure
GHC.Internal.Base.$fApplicativeIO GHC.Internal.Tuple.()
bitmap: 0 []
BRK_FUN <breakarray> main:Main 0 <cc>
PACK () 0
PUSH_G GHC.Internal.Base.$fApplicativeIO
PUSH_APPLY_PP
PUSH_G GHC.Internal.Base.pure
ENTER
```
Perhaps we never tried to decode a stack in which a BCO like this was
present. However, for the debugger, we want to decode stacks of threads
stopped at breakpoints, and these kind of BCOs do get on a stack under
e.g. `stg_apply_interp_info` frames.
See the accompanying test in the next commit for an example to trigger
the bug this commit fixes.
Fixes #26640
- - - - -
747153d2 by Rodrigo Mesquita at 2025-12-07T12:19:38-05:00
Add test for #26640
- - - - -
d4b1e353 by Simon Hengel at 2025-12-10T00:00:02-05:00
Fix syntax error in gadt_syntax.rst
- - - - -
91cc8be6 by Cheng Shao at 2025-12-10T00:00:43-05:00
ci: fix "ci.sh clean" to address frequent out of space error on windows runners
This patch fixes the `ci.sh clean` logic to address frequent out of
space error on windows runners; previously it didn't clean up the
inplace mingw blobs, which is the largest source of space leak on
windows runners. See added comment for detailed explanation.
- - - - -
fe2b79f4 by Recursion Ninja at 2025-12-10T08:34:18-05:00
Narrow before optimising MUL/DIV/REM into shifts
The MUL/DIV/REM operations can be optimised into shifts when one of the
operands is a constant power of 2. However, as literals in Cmm are
stored as 'Integer', for this to be correct we first need to narrow the
literal to the appropriate width before checking whether the literal is
a power of 2.
Fixes #25664
- - - - -
06c2349c by Recursion Ninja at 2025-12-10T08:34:58-05:00
Decouple 'Language.Haskell.Syntax.Type' from 'GHC.Utils.Panic'
- Remove the *original* defintion of 'hsQTvExplicit' defined within 'Language.Haskell.Syntax.Type'
- Redefine 'hsQTvExplicit' as 'hsq_explicit' specialized to 'GhcPass' exported by 'GHC.Utils.Panic'
- Define 'hsQTvExplicitBinders' as 'hsq_explicit' specialized to 'DocNameI' exported by 'Haddock.GhcUtils'.
- Replace all call sites of the original 'hsQTvExplicit' definition with either:
1. 'hsQTvExplicit' updated definition
2. 'hsQTvExplicitBinders'
All call sites never entered the 'XLHsQTyVars' constructor branch, but a call to 'panic' existed on this code path because the type system was not strong enought to guarantee that the 'XLHsQTyVars' construction was impossible.
These two specialized functions provide the type system with enough information to make that guarantee, and hence the dependancy on 'panic' can be removed.
- - - - -
ac0815d5 by sheaf at 2025-12-10T23:39:57-05:00
Quantify arg before mult in function arrows
As noted in #23764, we expect quantification order to be left-to-right,
so that in a type such as
a %m -> b
the inferred quantification order should be [a, m, b] and not [m, a, b].
This was addressed in commit d31fbf6c, but that commit failed to update
some other functions such as GHC.Core.TyCo.FVs.tyCoFVsOfType.
This affects Haddock, as whether we print an explicit forall or not
depends on whether the inferred quantification order matches the actual
quantification order.
- - - - -
2caf796e by sheaf at 2025-12-10T23:39:57-05:00
Haddock: improvements to ty-var quantification
This commit makes several improvements to how Haddock deals with the
quantification of type variables:
1. In pattern synonyms, Haddock used to jumble up universal and
existential quantification. That is now fixed, fixing #26252.
Tested in the 'PatternSyns2' haddock-html test.
2. The logic for computing whether to use an explicit kind annotation
for a type variable quantified in a forall was not even wrong.
This commit improves the heuristic, but it will always remain an
imperfect heuristic (lest we actually run kind inference again).
In the future (#26271), we hope to avoid reliance on this heuristic.
- - - - -
b14bdd59 by Teo Camarasu at 2025-12-10T23:40:38-05:00
Add explicit export list to GHC.Num
Let's make clear what this module exports to allow us to easily deprecate and remove some of these in the future. Resolves https://gitlab.haskell.org/ghc/ghc/-/issues/26625
- - - - -
d99f8326 by Cheng Shao at 2025-12-11T19:14:18-05:00
compiler: remove unused CPP code in foreign stub
This patch removes unused CPP code in the generated foreign stub:
- `#define IN_STG_CODE 0` is not needed, since `Rts.h` already
includes this definition
- The `if defined(__cplusplus)` code paths are not needed in the `.c`
file, since we don't generate C++ stubs and don't include C++
headers in our stubs. But it still needs to be present in the `.h`
header since it might be later included into C++ source files.
- - - - -
46c9746f by Cheng Shao at 2025-12-11T19:14:57-05:00
configure: bump LlvmMaxVersion to 22
This commit bumps LlvmMaxVersion to 22; 21.x releases have been
available since Aug 26th, 2025 and there's no regressions with 21.x so
far. This bump is also required for updating fedora image to 43.
- - - - -
96fce8d0 by Cheng Shao at 2025-12-12T01:17:51+01:00
hadrian: add support for building with UndefinedBehaviorSanitizer
This patch adds a +ubsan flavour transformer to hadrian to build all
stage1+ C/C++ code with UndefinedBehaviorSanitizer. This is
particularly useful to catch potential undefined behavior in the RTS
codebase.
- - - - -
f7a06d8c by Cheng Shao at 2025-12-12T01:17:51+01:00
ci: update alpine/fedora & add ubsan job
This patch updates alpine image to 3.23, fedora image to 43, and adds
a `x86_64-linux-fedora43-validate+debug_info+ubsan` job that's run in
validate/nightly pipelines to catch undefined behavior in the RTS
codebase.
- - - - -
2ccd11ca by Cheng Shao at 2025-12-12T01:17:51+01:00
rts: fix zero-length VLA undefined behavior in interpretBCO
This commit fixes a zero-length VLA undefined behavior in interpretBCO, caught by UBSan:
```
+rts/Interpreter.c:3133:19: runtime variable length array bound evaluates to non-positive value 0
```
- - - - -
4156ed19 by Cheng Shao at 2025-12-12T01:17:51+01:00
rts: fix unaligned ReadSpB in interpretBCO
This commit fixes unaligned ReadSpB in interpretBCO, caught by UBSan:
```
+rts/Interpreter.c:2174:64: runtime load of misaligned address 0x004202059dd1 for type 'StgWord', which requires 8 byte alignment
```
To perform proper unaligned read, we define StgUnalignedWord as a type
alias of StgWord with aligned(1) attribute, and load StgUnalignedWord
instead of StgWord in ReadSpB, so the C compiler is aware that we're
not loading with natural alignment.
- - - - -
fef89fb9 by Cheng Shao at 2025-12-12T01:17:51+01:00
rts: fix signed integer overflow in subword arithmetic in interpretBCO
This commit fixes signed integer overflow in subword arithmetic in
interpretBCO, see added note for detailed explanation.
- - - - -
3c001377 by Cheng Shao at 2025-12-13T05:03:15-05:00
ci: use treeless fetch for perf notes
This patch improves the ci logic for fetching perf notes by using
treeless fetch
(https://github.blog/open-source/git/get-up-to-speed-with-partial-clone-and-…)
to avoid downloading all blobs of the perf notes repo at once, and
only fetch the actually required blobs on-demand when needed. This
makes the initial `test-metrics.sh pull` operation much faster, and
also more robust, since we are seeing an increasing rate of 504 errors
in CI when fetching all perf notes at once, which is a major source of
CI flakiness at this point.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
123a8d77 by Peter Trommler at 2025-12-13T05:03:57-05:00
Cmm: remove restriction in MachOp folding
- - - - -
0b54b5fd by Andreas Klebinger at 2025-12-13T05:04:38-05:00
Remove explicit Typeable deriviations.
- - - - -
08b13f7b by Cheng Shao at 2025-12-13T05:05:18-05:00
ci: set gc.auto=0 during setup stage
This patch sets `gc.auto=0` during `setup` stage of CI, see added
comment for detailed explanation.
- - - - -
3b5aecb5 by Ben Gamari at 2025-12-13T23:43:10+01:00
Bump exceptions submodule to 0.10.11
- - - - -
c32de3b0 by Johan Förberg at 2025-12-15T02:36:03-05:00
base: Define Semigroup and Monoid instances for lazy ST
CLC proposal:
https://github.com/haskell/core-libraries-committee/issues/374
Fixes #26581
- - - - -
4f8b660c by mangoiv at 2025-12-15T02:37:05-05:00
ci: do not require nightly cabal-reinstall job to succeed
- - - - -
2c2a3ef3 by Cheng Shao at 2025-12-15T11:51:53-05:00
docs: drop obsolete warning about -fexternal-interpreter on windows
This patch drops an obsolete warning about -fexternal-interpreter not
supported on windows; it is supported since a long time ago, including
the profiled way.
- - - - -
68573aa5 by Marc Scholten at 2025-12-15T11:53:00-05:00
haddock: Drop Haddock.Backends.HaddockDB as it's unused
- - - - -
b230d549 by mangoiv at 2025-12-16T15:17:45-05:00
base: generalize delete{Firsts,}By
When we delete{Firsts,}By we should not require the
lists to be the same type. This is an especially useful
generalisation in the case of deleteFirstsBy because we
can skip an invocation of the map function.
This change was discussed on the core-libraries-committee's bug
tracker at https://github.com/haskell/core-libraries-committee/issues/372.
- - - - -
6a2b43e3 by Cheng Shao at 2025-12-16T15:18:30-05:00
compiler: clean up redundant LANGUAGE pragmas
This patch bumps `default-language` of `ghc`/`ghc-bin` from `GHC2021`
to `GHC2024` (which is supported in ghc 9.10, current boot ghc lower
version bound), and also cleans up redundant `LANGUAGE` pragmas (as
well as `default-extensions`/`other-extensions`) that are already
implied by `GHC2024`.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
fca9cd7c by sheaf at 2025-12-18T13:18:18-05:00
X86 CodeGen: fix assign_eax_sse_regs
We must set %al to the number of SSE2 registers that contain arguments
(in case we are dealing with a varargs function). The logic for counting
how many arguments reside in SSE2 registers was incorrect, as it used
'isFloatFormat', which incorrectly ignores vector registers.
We now instead do case analysis on the register class:
is_sse_reg r =
case targetClassOfReg platform r of
RcFloatOrVector -> True
RcInteger -> False
This change is necessary to prevent segfaults in T20030_test1j, because
subsequent commits change the format calculations, resulting in vector
formats more often.
- - - - -
53150617 by sheaf at 2025-12-18T13:18:19-05:00
X86 regUsageOfInstr: fix format for IMUL
When used with 8-bit operands, the IMUL instruction returns the result
in the lower 16 bits of %rax (also known as %ax). This is different
than for the other sizes, where an input at 16, 32 or 64 bits will
result in 16, 32 or 64 bits of output in both %rax and %rdx.
This doesn't affect the behaviour of the compiler, because we don't
allow partial writes at sub-word sizes. The rationale is explained
in Wrinkle [Don't allow scalar partial writes] in Note [Register formats in liveness analysis],
in GHC.CmmToAsm.Reg.Liveness.
- - - - -
c7a56dd1 by sheaf at 2025-12-18T13:18:19-05:00
Liveness analysis: consider register formats
This commit updates the register allocator to be a bit more careful in
situations in which a single register is used at multiple different
formats, e.g. when xmm1 is used both to store a Double# and a DoubleX2#.
This is done by introducing the 'Regs' newtype around 'UniqSet RegWithFormat',
for which the combining operations take the larger of the two formats
instead of overriding the format.
Operations on 'Regs' are defined in 'GHC.CmmToAsm.Reg.Regs'. There is
a modest compile-time cost for the additional overhead for tracking
register formats, which causes the metric increases of this commit.
The subtle aspects of the implementation are outlined in
Note [Register formats in liveness analysis] in GHC.CmmToAsm.Reg.Liveness.
Fixes #26411 #26611
-------------------------
Metric Increase:
T12707
T26425
T3294
-------------------------
- - - - -
c2e83339 by sheaf at 2025-12-18T13:18:19-05:00
Register allocator: reload at same format as spill
This commit ensures that if we spill a register onto the stack at a
given format, we then always reload the register at this same format.
This ensures we don't end up in a situation where we spill F64x2 but end
up only reloading the lower F64. This first reload would make us believe
the whole data is in a register, thus silently losing the upper 64 bits
of the spilled register's contents.
Fixes #26526
- - - - -
55ab583b by sheaf at 2025-12-18T13:18:19-05:00
Register allocation: writes redefine format
As explained in Note [Allocated register formats] in GHC.CmmToAsm.Reg.Linear,
we consider all writes to redefine the format of the register.
This ensures that in a situation such as
movsd .Ln6m(%rip),%v1
shufpd $0,%v1,%v1
we properly consider the broadcast operation to change the format of %v1
from F64 to F64x2.
This completes the fix to #26411 (test in T26411b).
- - - - -
951402ed by Vladislav Zavialov at 2025-12-18T13:19:05-05:00
Parser: improve mkModuleImpExp, remove checkImportSpec
1. The `mkModuleImpExp` helper now knows whether it is processing an import or
export list item, and uses this information to produce a more accurate error
message for `import M (T(..,x))` with PatternSynonyms disabled.
The old message incorrectly referred to this case as an export form.
2. The `checkImportSpec` helper is removed in favor of more comprehensive error
checking in `mkModuleImpExp`.
3. Additionaly, the invariants of `ImpExpList` and `ImpExpAllWith` have been
made more explicit in the comments and assertions (calls to 'panic').
Test case: import-syntax-no-ext
- - - - -
47d83d96 by Vladislav Zavialov at 2025-12-18T13:19:06-05:00
Subordinate namespace-specified wildcards (#25901)
Add support for subordinate namespace-specified wildcards
`X(type ..)` and `X(data ..)` to import and export lists.
Examples:
import M (Cls(type ..)) -- imports Cls and all its associated types
import M (Cls(data ..)) -- imports Cls and all its methods
module M (R(data ..), C(type ..)) where
-- exports R and all its data constructors and record fields;
-- exports C and all its associated types, but not its methods
The scope of this change is limited to the case where the wildcard is the only
subordinate import/export item, whereas the more complex forms `X(type .., f)`
or `X(type .., data ..)` are unsupported and raise the newly introduced
PsErrUnsupportedExplicitNamespace error. This restriction may be lifted later.
Summary of the changes:
1. Refactor IEThingAll to store its extension field XIEThingAll as a record
IEThingAllExt instead of a tuple.
2. Extend the AST by adding a NamespaceSpecifier field to IEThingAllExt,
representing an optional namespace specifier `type` or `data` in front
of a subordinate wildcard `X(..)`.
3. Extend the grammar in Parser.y with productions for `type ..` and `data ..`
in subordinate import/export items.
4. Introduce `filterByNamespaceGREs` to filter [GlobalRdrElt] by a
NamespaceSpecifier; use it in `filterImports` and `exports_from_avail`
to account for the namespace specifier in IEThingAll.
5. Improve diagnostics by storing more information in DodgyImportsEmptyParent
and DodgyExportsEmptyParent.
Test cases:
T25901_sub_e T25901_sub_f T25901_sub_g T25901_sub_a
T25901_sub_b T25901_sub_c T25901_sub_d T25901_sub_w
DodgyImports02 DodgyImports03 DodgyImports04
- - - - -
eac418bb by Recursion Ninja at 2025-12-18T13:19:48-05:00
Removing the 'Data' instance for 'InstEnv'.
The 'Data' instance is blocking work on Trees that Grow, and the
'Data' instance seem to have been added without a clear purpose.
- - - - -
e920e038 by Recursion Ninja at 2025-12-18T13:19:48-05:00
'Decouple Language.Haskell.Syntax.Decls' from 'GHC.Unit.Module.Warnings'
- - - - -
bd38b76c by Cheng Shao at 2025-12-18T13:20:31-05:00
testsuite: improve coverage of foundation test
This patch refactors the `foundation` test a bit to improve coverage:
- Instead of using a hard-coded seed, a random seed is now taken from
the command line, and printed upon test failure. This improves test
coverage over many future CI runs, and shall a failure occur, the
seed is available in the CI log for local reproduction.
- The iterations count is bumped to 1000 instead of 100, similar to
the bump in `test-primops`. Runtime timeout is bumped 2x just to be
safe.
- Improve `newLCGGen` by using non-atomic loads/stores on a
`MutableByteArray#` for storing mutable `Word64`, this test doesn't
use parallelism in the first place
- Fixed a few compiler warnings and removed redundant pragmas and
imports
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
3995187c by Sylvain Henry at 2025-12-18T13:21:45-05:00
Doc: document -pgmi "" (#26634)
- - - - -
5729418c by Cheng Shao at 2025-12-18T13:22:29-05:00
rts: use __builtin_mul_overflow for hs_mulIntMayOflo
This patch uses `__builtin_mul_overflow` to implement
`hs_mulIntMayOflo`. This is a GNU C checked arithmetic builtin
function supported by gcc/clang, is type-generic so works for both
32-bit/64-bit, and makes the code both more efficient and easier to
read/maintain than the previous hand rolled logic.
- - - - -
1ca4b49a by Cheng Shao at 2025-12-18T13:23:11-05:00
compiler/rts: fix ABI mismatch in barf() invocations
This patch fixes a long-standing issue of ABI mismatch in `barf()`
invocations, both in compiler-emitted code and in hand written Cmm
code:
- In RTS, we have `barf()` which reports a fatal internal error
message and exits the program.
- `barf()` is a variadic C function! When used as a callee of a
foreign call with `ccall` calling convention instead of `capi`,
there is an ABI mismatch between the caller and the callee!
- Unfortunately, both the compiler and the Cmm sources contain many
places where we call `barf()` via `ccall` convention!! Like, when
you write `foreign "C" barf("foo object (%p) entered!", R1)`, it
totally doesn't do what you think it'll do at all!! The second
argument `R1` is not properly passed in `va_list`, and the behavior
is completely undefined!!
- Even more unfortunately, this issue has been sitting around long
enough because the ABI mismatch is subtle enough on normie platforms
like x64 and arm64.
- But there are platforms like wasm32 that are stricter about ABI, and
the broken `barf()` invocations already causes trouble for wasm
backend: we had to use ugly hacks like `barf(errmsg, NULL)` to make
`wasm-ld` happy, and even with this band-aid, compiler-generated
`barf()` invocations are still broken, resulting in regressions in
certain debug-related functionality, e.g. `-dtag-inference-checks`
is broken on wasm32 (#22882).
This patch properly fixes the issue:
- We add non-variadic `barf` wrappers in the RTS that can be used as
`ccall` callees
- Both the compiler `emitBarf` logic and the hand-written Cmm are
changed to call these wrappers
- `emitBarf` now also properly annotates the foreign call as
`CmmNeverReturns` to indicate it's a noreturn call to enable more
efficient code generation
`-dtag-inference-checks` now works on wasm. Closes #22882.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
b3dd23b9 by Vilim Lendvaj at 2025-12-18T13:23:57-05:00
Remove outdated comment
The Traversable instance for ZipList is no longer in
GHC.Internal.Data.Traversable. In fact, it is right below this very comment.
- - - - -
9a9c2f03 by Cheng Shao at 2025-12-18T13:24:39-05:00
compiler: remove unused OtherSection logic
This patch removes the OtherSection logic in Cmm, given it's never
actually used by any of our backends.
- - - - -
91edd292 by Wolfgang Jeltsch at 2025-12-19T03:18:19-05:00
Remove unused known-key and name variables for generics
This removes the known-key and corresponding name variables for `K1`,
`M1`, `R`, `D`, `C`, `S`, and `URec` from `GHC.Generics`, as they are
apparently nowhere used in GHC’s source code.
- - - - -
73ee7e38 by Wolfgang Jeltsch at 2025-12-19T03:19:02-05:00
Remove unused known keys and names for generics classes
This removes the known-key and corresponding name variables for
`Datatype`, `Constructor`, and `Selector` from `GHC.Generics`, as they
are apparently nowhere used in GHC’s source code.
- - - - -
f69c5f14 by Cheng Shao at 2025-12-19T03:19:45-05:00
wasm: fix handling of ByteArray#/MutableByteArray# arguments in JSFFI imports
This patch fixes the handling of ByteArray#/MutableByteArray#
arguments in JSFFI imports, see the amended note and manual for
explanation. Also adds a test to witness the fix.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
224446a2 by Cheng Shao at 2025-12-20T07:49:54-05:00
rts: workaround -Werror=maybe-uninitialized false positives
In some cases gcc might report -Werror=maybe-uninitialized that we
know are false positives, but need to workaround it to make validate
builds with -Werror pass.
- - - - -
251ec087 by Cheng Shao at 2025-12-20T07:49:54-05:00
hadrian: use -Og as C/C++ optimization level when debugging
This commit enables -Og as optimization level when compiling the debug
ways of rts. According to gcc documentation
(https://gcc.gnu.org/onlinedocs/gcc/Optimize-Options.html#index-Og)
-Og is a better choice than -O0 for producing debuggable code. It's
also supported by clang as well, so it makes sense to use it as a
default for debugging. Also add missing -g3 flag to C++ compilation
flags in +debug_info flavour transformer.
- - - - -
fb586c67 by Cheng Shao at 2025-12-20T07:50:36-05:00
compiler: replace DList with OrdList
This patch removes `DList` logic from the compiler and replaces it
with `OrdList` which also supports O(1) concatenation and should be
more memory efficient than the church-encoded `DList`.
- - - - -
8149c987 by Cheng Shao at 2025-12-20T17:06:51-05:00
hadrian: add with_profiled_libs flavour transformer
This patch adds a `with_profiled_libs` flavour transformer to hadrian
which is the exact opposite of `no_profiled_libs`. It adds profiling
ways to stage1+ rts/library ways, and doesn't alter other flavour
settings. It is useful when needing to test profiling logic locally
with a quick flavour.
- - - - -
746b18cd by Cheng Shao at 2025-12-20T17:06:51-05:00
hadrian: fix missing profiled dynamic libraries in profiled_ghc
This commit fixes the profiled_ghc flavour transformer to include
profiled dynamic libraries as well, since they're supported by GHC
since !12595.
- - - - -
4dd7e3b9 by Cheng Shao at 2025-12-20T17:07:33-05:00
ci: set http.postBuffer to mitigate perf notes timeout on some runners
This patch sets http.postBuffer to mitigate the timeout when fetching
perf notes on some runners with slow internet connection. Fixes #26684.
- - - - -
bc36268a by Wolfgang Jeltsch at 2025-12-21T16:23:24-05:00
Remove unused known keys and names for type representations
This removes the known-key and corresponding name variables for
`TrName`, `TrNameD`, `TypeRep`, `KindRepTypeLitD`, `TypeLitSort`, and
`mkTrType`, as they are apparently nowhere used in GHC’s source code.
- - - - -
ff5050e9 by Wolfgang Jeltsch at 2025-12-21T16:24:04-05:00
Remove unused known keys and names for natural operations
This removes the known-key and corresponding name variables for
`naturalAndNot`, `naturalLog2`, `naturalLogBaseWord`, `naturalLogBase`,
`naturalPowMod`, `naturalSizeInBase`, `naturalToFloat`, and
`naturalToDouble`, as they are apparently nowhere used in GHC’s source
code.
- - - - -
424388c2 by Wolfgang Jeltsch at 2025-12-21T16:24:45-05:00
Remove the unused known key and name for `Fingerprint`
This removes the variables for the known key and the name of the
`Fingerprint` data constructor, as they are apparently nowhere used in
GHC’s source code.
- - - - -
a1ed86fe by Wolfgang Jeltsch at 2025-12-21T16:25:26-05:00
Remove the unused known key and name for `failIO`
This removes the variables for the known key and the name of the
`failIO` operation, as they are apparently nowhere used in GHC’s source
code.
- - - - -
b8220daf by Wolfgang Jeltsch at 2025-12-21T16:26:07-05:00
Remove the unused known key and name for `liftM`
This removes the variables for the known key and the name of the `liftM`
operation, as they are apparently nowhere used in GHC’s source code.
- - - - -
eb0628b1 by Wolfgang Jeltsch at 2025-12-21T16:26:47-05:00
Fix the documentation of `hIsClosed`
- - - - -
db1ce858 by sheaf at 2025-12-22T17:11:17-05:00
Do deep subsumption when computing valid hole fits
This commit makes a couple of improvements to the code that
computes "valid hole fits":
1. It uses deep subsumption for data constructors.
This matches up the multiplicities, as per
Note [Typechecking data constructors].
This fixes #26338 (test: LinearHoleFits).
2. It now suggests (non-unidirectional) pattern synonyms as valid
hole fits. This fixes #26339 (test: PatSynHoleFit).
3. It uses 'stableNameCmp', to make the hole fit output deterministic.
-------------------------
Metric Increase:
hard_hole_fits
-------------------------
- - - - -
72ee9100 by sheaf at 2025-12-22T17:11:17-05:00
Speed up hole fits with a quick pre-test
This speeds up the machinery for valid hole fits by doing a small
check to rule out obviously wrong hole fits, such as:
1. A hole fit identifier whose type has a different TyCon at the head,
after looking through foralls and (=>) arrows, e.g.:
hole_ty = Int
cand_ty = Maybe a
or
hole_ty = forall a b. a -> b
cand_ty = forall x y. Either x y
2. A hole fit identifier that is not polymorphic when the hole type
is polymorphic, e.g.
hole_ty = forall a. a -> a
cand_ty = Int -> Int
-------------------------
Metric Decrease:
hard_hole_fits
-------------------------
- - - - -
30e513ba by Cheng Shao at 2025-12-22T17:12:00-05:00
configure: remove unused win32-tarballs.md5sum
This patch removes the unused `win32-tarballs.md5sum` file from the
tree. The current mingw tarball download logic in
`mk/get-win32-tarballs.py` fetches and checks against `SHA256SUM` from
the same location where the tarballs are fetched, and this file has
been unused for a few years.
- - - - -
a2d52b3b by Wolfgang Jeltsch at 2025-12-23T04:47:33-05:00
Add an operation `System.IO.hGetNewlineMode`
This commit also contains some small code and documentation changes for
related operations, for the sake of consistency.
- - - - -
b26d134a by Cheng Shao at 2025-12-23T04:48:15-05:00
rts: opportunistically reclaim slop space in shrinkMutableByteArray#
Previously, `shrinkMutableByteArray#` shrinks a `MutableByteArray#`
in-place by assigning the new size to it, and zeroing the extra slop
space. That slop space is not reclaimed and wasted. But it's often the
case that we allocate a `MutableByteArray#` upfront, then shrink it
shortly after, so the `MutableByteArray#` closure sits right at the
end of a nursery block; this patch identifies such chances, and also
shrink `bd->free` if possible, reducing heap space fragmentation.
Co-authored-by: Codex <codex(a)openai.com>
-------------------------
Metric Decrease:
T10678
-------------------------
- - - - -
c72ddabf by Cheng Shao at 2025-12-23T16:13:23-05:00
hadrian: fix bootstrapping with ghc-9.14
This patch fixes bootstrapping GHC with ghc-9.14, tested locally with
ghc-9.14.1 release as bootstrapping GHC.
- - - - -
0fd6d8e4 by Cheng Shao at 2025-12-23T16:14:05-05:00
hadrian: pass -keep-tmp-files to test ghc when --keep-test-files is enabled
This patch makes hadrian pass `-keep-tmp-files` to test ghc when
`--keep-test-files` is enabled, so you can check the ghc intermediate
files when debugging certain test failures. Closes #26688.
- - - - -
81d10134 by Cheng Shao at 2025-12-24T06:11:52-05:00
configure: remove dead code in configure scripts
This patch removes dead code in our configure scripts, including:
- Variables and auto-detected programs that are not used
- autoconf functions that are not used, or export a variable that's
not used
- `AC_CHECK_HEADERS` invocations that don't have actual corresponding
`HAVE_XXX_H` usage
- Other dead code (e.g. stray `AC_DEFUN()`)
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
fb1381c3 by Wolfgang Jeltsch at 2025-12-24T06:12:34-05:00
Remove unused known keys and names for list operations
This removes the known-key and corresponding name variables for
`concat`, `filter`, `zip`, and `(++)`, as they are apparently nowhere
used in GHC’s source code.
- - - - -
7b9c20f4 by Recursion Ninja at 2025-12-24T10:35:36-05:00
Decoupling Language.Haskell.Syntax.Binds from GHC.Types.Basic
by transferring InlinePragma types between the modules.
* Moved InlinePragma data-types to Language.Haskell.Syntax.Binds.InlinePragma
* Partitioned of Arity type synonyms to GHC.Types.Arity
* InlinePragma is now extensible via Trees That Grow
* Activation is now extensible via Trees That Grow
* Maybe Arity change to more descriptive InlineSaturation data-type
* InlineSaturation information removed from InlinePragma during GHS parsing pass
* Cleaned up the exposed module interfaces of the new modules
- - - - -
a3afae0c by Simon Peyton Jones at 2025-12-25T15:26:36-05:00
Check for rubbish literals in Lint
Addresses #26607.
See new Note [Checking for rubbish literals] in GHC.Core.Lint
- - - - -
8a317b6f by Aaron Allen at 2026-01-01T03:05:15-05:00
[#26183] Associated Type Iface Fix
When determining "extras" for class decl interface entries, axioms for
the associated types need to included so that dependent modules will be
recompiled if those axioms change.
resolves #26183
- - - - -
ae1aeaab by Cheng Shao at 2026-01-01T03:06:32-05:00
testsuite: run numeric tests with optasm when available
This patch adds the `optasm` extra way to nueric tests when NCG is
available. Some numeric bugs only surface with optimization, omitting
this can hide these bugs and even make them slip into release! (e.g. #26711)
- - - - -
6213bb57 by maralorn at 2026-01-02T16:30:32+01:00
GHC.Internal.Exception.Context: Fix comment
on addExceptionAnnotation
- - - - -
b820ff50 by Janis Voigtlaender at 2026-01-05T02:43:18-05:00
GHC.Internal.Control.Monad.replicateM: Fix comment
- - - - -
a8a94aad by Cheng Shao at 2026-01-05T16:24:04-05:00
hadrian: drops unused PE linker script for windows
This patch drops unused PE linker script for windows in the
`MergeObjects` builder of hadrian. The linker script is used for
merging object files into a single `HS*.o` object file and undoing the
effect of split sections, when building the "ghci library" object
file. However, we don't build the ghci library on windows, and this
code path is actually unreachable.
- - - - -
53038ea9 by Cheng Shao at 2026-01-05T16:24:04-05:00
hadrian: drop unused logic for building ghci libraries
This patch drops the unused logic for building ghci libraries in
hadrian:
- The term "ghci library" refers to an optional object file per
library `HS*.o`, which is merged from multiple object files in that
library using the `MergeObjects` builder in hadrian.
- The original rationale of having a ghci library object, in addition
to normal archives, was to speedup ghci loading, since the combined
object is linked with a linker script to undo the effects of
`-fsplit-sections` to reduce section count and make it easier for
the RTS linker to handle.
- However, most GHC builds enable `dynamicGhcPrograms` by default, in
such cases the ghci library would already not be built.
- `dynamicGhcPrograms` is disabled on Windows, but still we don't
build the ghci library due to lack of functioning merge objects
command.
- The only case that we actually build ghci library objects, are
alpine fully static bindists. However, for other reasons, split
sections is already disabled for fully static builds anyway!
- There will not be any regression if the ghci library objects are
absent from a GHC global libdir when `dynamicGhcPrograms` is
disabled. The RTS linker can already load the archives without any
issue.
Hence the removal. We now forcibly disable ghci libraries for all
Cabal components, and rip out all logic related to `MergeObjects` and
ghci libraries in hadrian. This also nicely cleans up some old todos
and fixmes that are no longer relevant.
Note that MergeObjects in hadrian is not the same thing as merge
objects in the GHC driver. The latter is not affected by this patch.
-------------------------
Metric Decrease:
libdir
-------------------------
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
8f209336 by Simon Jakobi at 2026-01-05T16:24:48-05:00
User's guide: Fix link to language extensions
Instead of linking to haddocks, it seemed more useful to link
to the extension overview in the user's guide.
Closes #26614.
- - - - -
0b7df6db by Simon Peyton Jones at 2026-01-06T09:32:23-05:00
Improved fundeps for closed type families
The big payload of this commit is to execute the plan suggested
in #23162, by improving the way that we generate functional
dependencies for closed type families.
It is all described in Note [Exploiting closed type families]
Most of the changes are in GHC.Tc.Solver.FunDeps
Other small changes
* GHC.Tc.Solver.bumpReductionDepth. This function brings together the code that
* Bumps the depth
* Checks for overflow
Previously the two were separated, sometimes quite widely.
* GHC.Core.Unify.niFixSubst: minor improvement, removing an unnecessary
itraetion in the base case.
* GHC.Core.Unify: no need to pass an InScopeSet to
tcUnifyTysForInjectivity. It can calculate one for itself; and it is
never inspected anyway so it's free to do so.
* GHC.Tc.Errors.Ppr: slight impovement to the error message for
reduction-stack overflow, when a constraint (rather than a type) is
involved.
* GHC.Tc.Solver.Monad.wrapUnifier: small change to the API
- - - - -
fde8bd88 by Simon Peyton Jones at 2026-01-06T09:32:23-05:00
Add missing (KK4) to kick-out criteria
There was a missing case in kick-out that meant we could fail
to solve an eminently-solvable constraint.
See the new notes about (KK4)
- - - - -
00082844 by Simon Peyton Jones at 2026-01-06T09:32:23-05:00
Some small refactorings of error reporting in the typechecker
This is just a tidy-up commit.
* Add ei_insoluble to ErrorItem, to cache insolubility.
Small tidy-up.
* Remove `is_ip` and `mkIPErr` from GHC.Tc.Errors; instead enhance mkDictErr
to handle implicit parameters. Small refactor.
- - - - -
fe4cb252 by Simon Peyton Jones at 2026-01-06T09:32:24-05:00
Improve recording of insolubility for fundeps
This commit addresses #22652, by recording when the fundeps for
a constraint are definitely insoluble. That in turn improves the
perspicacity of the pattern-match overlap checker.
See Note [Insoluble fundeps]
- - - - -
df0ffaa5 by Simon Peyton Jones at 2026-01-06T09:32:24-05:00
Fix a buglet in niFixSubst
The MR of which this is part failed an assertion check extendTvSubst
because we extended the TvSubst with a CoVar. Boo.
This tiny patch fixes it, and adds the regression test from #13882
that showed it up.
- - - - -
3d6aba77 by konsumlamm at 2026-01-06T09:33:16-05:00
Fix changelog formatting
- - - - -
69e0ab59 by Cheng Shao at 2026-01-06T19:37:56-05:00
compiler: add targetHasRTSWays function
This commit adds a `targetHasRTSWays` util function in
`GHC.Driver.Session` to query if the target RTS has a given Ways (e.g.
WayThreaded).
- - - - -
25a0ab94 by Cheng Shao at 2026-01-06T19:37:56-05:00
compiler: link on-demand external interpreter with threaded RTS
This commit makes the compiler link the on-demand external interpreter
program with threaded RTS if it is available in the target RTS ways.
This is a better default than the previous single-threaded RTS, and it
enables the external interpreter to benefit from parallelism when
deserializing CreateBCOs messages.
- - - - -
92404a2b by Cheng Shao at 2026-01-06T19:37:56-05:00
hadrian: link iserv with threaded RTS
This commit makes hadrian link iserv with threaded RTS if it's
available in the RTS ways. Also cleans up the iserv main C program
which can be replaced by the `-fkeep-cafs` link-time option.
- - - - -
a20542d2 by Cheng Shao at 2026-01-06T19:38:38-05:00
ghc-internal: remove unused GMP macros
This patch removes unused GMP related macros from `ghc-internal`. The
in-tree GMP version was hard coded and outdated, but it was not used
anywhere anyway.
- - - - -
4079dcd6 by Cheng Shao at 2026-01-06T19:38:38-05:00
hadrian: fix in-tree gmp configure error on newer c compilers
Building in-tree gmp on newer c compilers that default to c23 fails at
configure stage, this patch fixes it, see added comment for
explanation.
- - - - -
414d1fe1 by Cheng Shao at 2026-01-06T19:39:20-05:00
compiler: fix LLVM backend pdep/pext handling for i386 target
This patch fixes LLVM backend's pdep/pext handling for i386 target,
and also removes non-existent 128/256/512 bit hs_pdep/hs_pext callees.
See amended note for more explanation. Fixes #26450.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
c7f6fba3 by Cheng Shao at 2026-01-06T19:39:20-05:00
ci: remove allow_failure flag for i386 alpine job
The LLVM codegen issue for i386 has been fixed, and the i386 alpine
job should pass now. This commit removes the allow_failure flag so
that other i386 regressions in the future are signaled more timely.
- - - - -
52d00c05 by Simon Peyton Jones at 2026-01-07T10:24:21-05:00
Add missing InVar->OutVar lookup in SetLevels
As #26681 showed, the SetLevels pass was failing to map an InVar to
an OutVar. Very silly! I'm amazed it hasn't broken before now.
I have improved the type singatures (to mention InVar and OutVar)
so it's more obvious what needs to happen.
- - - - -
ab0a5594 by Cheng Shao at 2026-01-07T10:25:04-05:00
hadrian: drop deprecated pkgHashSplitObjs code path
This patch drops deprecated `pkgHashSplitObjs` code path from hadrian,
since GHC itself has removed split objs support many versions ago and
this code path is unused.
- - - - -
bb3a2ba1 by Cheng Shao at 2026-01-07T10:25:44-05:00
hadrian: remove linting/assertion in quick-validate flavour
The `quick-validate` flavour is meant for testing ghc and passing the
testsuite locally with similar settings to `validate` but faster. This
patch removes the linting/assertion overhead in `quick-validate` to
improve developer experience. I also took the chance to simplify
redundant logic of rts/library way definition in `validate` flavour.
- - - - -
7971f5dd by Cheng Shao at 2026-01-07T10:26:26-05:00
deriveConstants: clean up unused constants
This patch cleans up unused constants from `deriveConstants`, they are
not used by C/Cmm code in the RTS, nor compiler-generated code.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
4df96993 by Cheng Shao at 2026-01-07T10:27:08-05:00
hadrian: pass -fno-omit-frame-pointer with +debug_info
This patch adds `-fno-omit-frame-pointer` as C/C++ compilation flag
when compiling with `+debug_info` flavour transformer. It's a sane
default when you care about debugging and reliable backtraces, and
makes debugging/profiling with bpf easier.
- - - - -
8a3900a3 by Aaron Allen at 2026-01-07T10:27:57-05:00
[26705] Include TyCl instances in data fam iface entry
Ensures dependent modules are recompiled when the class instances for a
data family instance change.
resolves #26705
- - - - -
a0b980af by Cheng Shao at 2026-01-07T10:28:38-05:00
hadrian: remove unused Hp2Ps/Hpc builders
This patch removes the Hp2Ps/Hpc builders from hadrian, they are
unused in the build system. Note that the hp2ps/hpc programs are still
built and not affected.
- - - - -
50a58757 by Cheng Shao at 2026-01-07T10:29:20-05:00
hadrian: only install js files to libdir for wasm/js targets
There are certain js files required for wasm/js targets to work, and
previously hadrian would install those js files to libdir
unconditionally on other targets as well. This could be a minor
annoyance for packagers especially when the unused js files contain
shebangs that interfere with the packaging process. This patch makes
hadrian only selectively install the right js files for the right
targets.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
da40e553 by Simon Peyton Jones at 2026-01-07T10:30:00-05:00
Add flavour transformer assertions_stage1
This allows us to enable -DDEBUG assertions in the stage1 compiler
- - - - -
ec3cf767 by Cheng Shao at 2026-01-08T06:24:31-05:00
make: remove unused Makefiles from legacy make build system
This patch removes unused Makefiles from legacy make build system; now
they are never used by hadrian in any way, and they already include
common boilerplate mk files that are long gone in the make build
system removal, hence the housecleaning.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
04ea3f83 by Cheng Shao at 2026-01-08T06:25:13-05:00
compiler: use -O3 as LLVM optimization level for ghc -O2
The GHC driver clamps LLVM optimization level to `-O2` due to LLVM
crashes, but those were historical issues many years ago that are no
longer relevant for LLVM versions we support today. This patch changes
the driver to use `-O3` as LLVM optimization level when compiling with
`-O2`, which is a better default when we're willing to trade
compilation time for faster generated code.
- - - - -
472df471 by Peter Trommler at 2026-01-08T13:28:54-05:00
Use half-word literals in info tables
With this commit info tables are mapped to the same assembler code
on big-endian and little-endian platforms.
Fixes #26579.
- - - - -
393f9c51 by Simon Peyton Jones at 2026-01-08T13:29:35-05:00
Refactor srutOkForBinderSwap
This MR does a small refactor:
* Moves `scrutOkForBinderSwap` and `BinderSwapDecision`
to GHC.Core.Utils
* Inverts the sense of the coercion it returns, which makes
more sense
No effect on behaviour
- - - - -
ad76fb0f by Simon Peyton Jones at 2026-01-08T13:29:36-05:00
Improve case merging
This small MR makes case merging happen a bit more often than
it otherwise could, by getting join points out of the way.
See #26709 and GHC.Core.Utils
Note [Floating join points out of DEFAULT alternatives]
- - - - -
4c9395f5 by Cheng Shao at 2026-01-08T13:30:16-05:00
hadrian: remove broken hsc2hs flag when cross compiling to windows
This patch removes the `--via-asm` hsc2hs flag when cross compiling to
windows. With recent llvm-mingw toolchain, it would fail with:
```
x86_64-w64-mingw32-hsc2hs: Cannot combine instructions: [Quad 8,Long 4,Long 241,Ref ".Ltmp1-.Ltmp0"]
```
The hsc2hs default `--cross-compile` logic is slower but works.
- - - - -
71fdef55 by Simon Peyton Jones at 2026-01-08T13:30:57-05:00
Try harder to keep the substitution empty
Avoid unnecessary cloning of variables in the Simplifier.
Addresses #26724,
See Note [Keeping the substitution empty]
We get some big wins in compile time
Metrics: compile_time/bytes allocated
-------------------------------------
Baseline
Test Metric value New value Change
----------------------------------------------------------------------------
CoOpt_Singletons(normal) ghc/alloc 721,544,088 692,174,216 -4.1% GOOD
LargeRecord(normal) ghc/alloc 1,268,031,157 1,265,168,448 -0.2%
T14766(normal) ghc/alloc 918,218,533 688,432,296 -25.0% GOOD
T15703(normal) ghc/alloc 318,103,629 306,638,016 -3.6% GOOD
T17836(normal) ghc/alloc 419,174,584 418,400,824 -0.2%
T18478(normal) ghc/alloc 471,042,976 470,261,376 -0.2%
T20261(normal) ghc/alloc 573,387,162 563,663,336 -1.7%
T24984(normal) ghc/alloc 87,832,666 87,636,168 -0.2%
T25196(optasm) ghc/alloc 1,103,284,040 1,101,376,992 -0.2%
hard_hole_fits(normal) ghc/alloc 224,981,413 224,608,208 -0.2%
geo. mean -0.3%
minimum -25.0%
maximum +0.1%
Metric Decrease:
CoOpt_Singletons
T14766
T15703
- - - - -
30341168 by Simon Peyton Jones at 2026-01-08T13:31:38-05:00
Add regression test for #24867
- - - - -
1ac1a541 by Julian Ospald at 2026-01-09T02:48:53-05:00
Support statically linking executables properly
Fixes #26434
In detail, this does a number of things:
* Makes GHC aware of 'extra-libraries-static' (this changes the package
database format).
* Adds a switch '-static-external' that will honour 'extra-libraries-static'
to link external system dependencies statically.
* Adds a new field to settings/targets: "ld supports verbatim namespace".
This field is used by '-static-external' to conditionally use '-l:foo.a'
syntax during linking, which is more robust than trying to find the
absolute path to an archive on our own.
* Adds a switch '-fully-static' that is meant as a high-level interface
for e.g. cabal. This also honours 'extra-libraries-static'.
This also attempts to clean up the confusion around library search directories.
At the moment, we have 3 types of directories in the package database
format:
* library-dirs
* library-dirs-static
* dynamic-library-dirs
However, we only have two types of linking: dynamic or static. Given the
existing logic in 'mungeDynLibFields', this patch assumes that
'library-dirs' is really just nothing but a fallback and always
prefers the more specific variants if they exist and are non-empty.
Conceptually, we should be ok with even just one search dirs variant.
Haskell libraries are named differently depending on whether they're
static or dynamic, so GHC can conveniently pick the right one depending
on the linking needs. That means we don't really need to play tricks
with search paths to convince the compiler to do linking as we want it.
For system C libraries, the convention has been anyway to place static and
dynamic libs next to each other, so we need to deal with that issue
anyway and it is outside of our control. But this is out of the scope
of this patch.
This patch is backwards compatible with cabal. Cabal should however
be patched to use the new '-fully-static' switch.
- - - - -
ad3c808d by Julian Ospald at 2026-01-09T02:48:53-05:00
Warn when "-dynamic" is mixed with "-staticlib"
- - - - -
322dd672 by Matthew Pickering at 2026-01-09T02:49:35-05:00
rts: Use INFO_TABLE_CONSTR for stg_dummy_ret_closure
Since the closure type is CONSTR_NOCAF, we need to use INFO_TABLE_CONSTR
to populate the constructor description field (this crashes ghc-debug
when decoding AP_STACK frames sometimes)
Fixes #26745
- - - - -
039bac4c by Ben Gamari at 2026-01-09T20:22:16-05:00
ghc-internal: Move STM utilities out of GHC.Internal.Conc.Sync
This is necessary to avoid an import cycle on Windows when importing
`GHC.Internal.Exception.Context` in `GHC.Internal.Conc.Sync`.
On the road to address #25365.
- - - - -
8c389e8c by Ben Gamari at 2026-01-09T20:22:16-05:00
base: Capture backtrace from throwSTM
Implements core-libraries-committee#297.
Fixes #25365.
- - - - -
e1ce1fc3 by Ben Gamari at 2026-01-09T20:22:16-05:00
base: Annotate rethrown exceptions in catchSTM with WhileHandling
Implements core-libraries-committee#298
- - - - -
c4ebdbdf by Cheng Shao at 2026-01-09T20:23:06-05:00
compiler: make getPrim eagerly evaluate its result
This commit makes `GHC.Utils.Binary.getPrim` eagerly evaluate its
result, to avoid accidental laziness when future patches build other
binary parsers using `getPrim`.
- - - - -
66a0c4f7 by Cheng Shao at 2026-01-09T20:23:06-05:00
compiler: implement fast get/put for Word16/Word32/Word64
Previously, `GHC.Utils.Binary` contains `get`/`put` functions for
`Word16`/`Word32`/`Word64` which always loads and stores them as
big-endian words at a potentially unaligned address. The previous
implementation is based on loads/stores of individual bytes and
concatenating bytes with bitwise operations, which currently cannot be
fused to a single load/store operation by GHC.
This patch implements fast `get`/`put` functions for
`Word16`/`Word32`/`Word64` based on a single memory load/store, with
an additional `byteSwap` operation on little-endian hosts. It is based
on unaligned load/store primops added since GHC 9.10, and we already
require booting with at least 9.10, so it's about time to switch to
this faster path.
- - - - -
641ec3f0 by Simon Peyton Jones at 2026-01-09T20:23:55-05:00
Fix scoping errors in specialisation
Using -fspecialise-aggressively in #26682 showed up a couple of
subtle errors in the type-class specialiser.
* dumpBindUDs failed to call `deleteCallsMentioning`, resulting in a
call that mentioned a dictionary that was not in scope. This call
has been missing since 2009!
commit c43c981705ec33da92a9ce91eb90f2ecf00be9fe
Author: Simon Peyton Jones <simonpj(a)microsoft.com>
Date: Fri Oct 23 16:15:51 2009 +0000
Fixed by re-combining `dumpBindUDs` and `dumpUDs`.
* I think there was another bug involving the quantified type
variables in polymorphic specialisation. In any case I refactored
`specHeader` and `spec_call` so that the former looks for the
extra quantified type variables rather than the latter. This
is quite a worthwhile simplification: less code, easier to grok.
Test case in simplCore/should_compile/T26682,
brilliantly minimised by @sheaf.
- - - - -
2433e91d by Cheng Shao at 2026-01-09T20:24:43-05:00
compiler: change sectionProtection to take SectionType argument
This commit changes `sectionProtection` to only take `SectionType`
argument instead of whole `Section`, since it doesn't need the Cmm
section content anyway, and it can then be called in parts of NCG
where we only have a `SectionType` in scope.
- - - - -
e5926fbe by Cheng Shao at 2026-01-09T20:24:43-05:00
compiler: change isInitOrFiniSection to take SectionType argument
This commit changes `isInitOrFiniSection` to only take `SectionType`
argument instead of whole `Section`, since it doesn't need the Cmm
section content anyway, and it can then be called in parts of NCG
where we only have a `SectionType` in scope. Also marks it as
exported.
- - - - -
244d57d7 by Cheng Shao at 2026-01-09T20:24:43-05:00
compiler: fix split sections on windows
This patch fixes split sections on windows by emitting the right
COMDAT section header in NCG, see added comment for more explanation.
Fix #26696 #26494.
-------------------------
Metric Decrease:
LargeRecord
T9675
size_hello_artifact
size_hello_artifact_gzip
size_hello_unicode
size_hello_unicode_gzip
Metric Increase:
T13035
-------------------------
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
182f3d0f by Cheng Shao at 2026-01-09T20:25:28-05:00
iserv: add comment about -fkeep-cafs
- - - - -
49675b69 by Matthew Craven at 2026-01-09T20:26:14-05:00
Account for "stupid theta" in demand sig for DataCon wrappers
Fixes #26748.
- - - - -
8d147b42 by Matthew Craven at 2026-01-10T18:00:04-05:00
Break the import cycle involving GHC.Internal.ByteOrder
This moves the 'Read ByteOrder' and 'Generic ByteOrder'
instances so that 'GHC.Internal.Unicode.Bits' doesn't have
to {-# SOURCE #-} import to get its hands on what really should
be a compile-time constant! (This situation was probably hurting
optimization of 'isUpperCase' and 'isLowerCase'.)
- - - - -
92307d50 by Matthew Craven at 2026-01-10T18:44:24-05:00
base: Provide `hostByteOrder` to replace `targetByteOrder`
The latter is an egregious misnomer; the concept of target system
does not even apply in the context of the `base` library as it is
not a compiler or code generation tool. It is expected that
`targetByteOrder` will be deprecated and then removed once
`hostByteOrder` has existed for a few releases.
The new `hostByteOrder` is also re-exported from a new home in
`System.Info` along with the `ByteOrder` type and its constructors.
- - - - -
1162 changed files:
- .gitattributes
- .gitlab-ci.yml
- .gitlab/ci.sh
- .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
- .gitlab/rel_eng/upload_ghc_libs.py
- .gitlab/test-metrics.sh
- compile_flags.txt
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/PrimOps.hs
- compiler/GHC/Builtin/PrimOps/Ids.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Literals.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Builtin/Utils.hs
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/Breakpoints.hs
- compiler/GHC/ByteCode/InfoTable.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/ByteCode/Serialize.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Cmm.hs
- compiler/GHC/Cmm/BlockId.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/CommonBlockElim.hs
- compiler/GHC/Cmm/Config.hs
- compiler/GHC/Cmm/ContFlowOpt.hs
- compiler/GHC/Cmm/Dataflow.hs
- compiler/GHC/Cmm/Dataflow/Block.hs
- compiler/GHC/Cmm/Dataflow/Graph.hs
- compiler/GHC/Cmm/Dataflow/Label.hs
- compiler/GHC/Cmm/DebugBlock.hs
- compiler/GHC/Cmm/Dominators.hs
- compiler/GHC/Cmm/Expr.hs
- compiler/GHC/Cmm/Graph.hs
- compiler/GHC/Cmm/Info.hs
- compiler/GHC/Cmm/Info/Build.hs
- compiler/GHC/Cmm/InitFini.hs
- compiler/GHC/Cmm/LRegSet.hs
- compiler/GHC/Cmm/LayoutStack.hs
- compiler/GHC/Cmm/Lint.hs
- compiler/GHC/Cmm/Liveness.hs
- compiler/GHC/Cmm/MachOp.hs
- compiler/GHC/Cmm/Node.hs
- compiler/GHC/Cmm/Opt.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Cmm/ProcPoint.hs
- compiler/GHC/Cmm/Reducibility.hs
- compiler/GHC/Cmm/Reg.hs
- compiler/GHC/Cmm/Sink.hs
- compiler/GHC/Cmm/Switch.hs
- compiler/GHC/Cmm/Switch/Implement.hs
- compiler/GHC/Cmm/ThreadSanitizer.hs
- compiler/GHC/Cmm/UniqueRenamer.hs
- compiler/GHC/Cmm/Utils.hs
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/CmmToAsm/AArch64/RegInfo.hs
- compiler/GHC/CmmToAsm/BlockLayout.hs
- compiler/GHC/CmmToAsm/CFG.hs
- compiler/GHC/CmmToAsm/CPrim.hs
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Format.hs
- compiler/GHC/CmmToAsm/LA64/CodeGen.hs
- compiler/GHC/CmmToAsm/LA64/Ppr.hs
- compiler/GHC/CmmToAsm/Monad.hs
- compiler/GHC/CmmToAsm/PPC/CodeGen.hs
- compiler/GHC/CmmToAsm/PPC/Ppr.hs
- compiler/GHC/CmmToAsm/PPC/RegInfo.hs
- compiler/GHC/CmmToAsm/Ppr.hs
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToAsm/Reg/Graph.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Coalesce.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs
- compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs
- compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs
- compiler/GHC/CmmToAsm/Reg/Linear.hs
- compiler/GHC/CmmToAsm/Reg/Linear/Base.hs
- compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs
- compiler/GHC/CmmToAsm/Reg/Linear/State.hs
- compiler/GHC/CmmToAsm/Reg/Linear/X86.hs
- compiler/GHC/CmmToAsm/Reg/Linear/X86_64.hs
- compiler/GHC/CmmToAsm/Reg/Liveness.hs
- + compiler/GHC/CmmToAsm/Reg/Regs.hs
- compiler/GHC/CmmToAsm/Reg/Target.hs
- compiler/GHC/CmmToAsm/Wasm.hs
- compiler/GHC/CmmToAsm/Wasm/Asm.hs
- compiler/GHC/CmmToAsm/Wasm/FromCmm.hs
- compiler/GHC/CmmToAsm/Wasm/Types.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/CmmToLlvm/Data.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion.hs-boot
- compiler/GHC/Core/Coercion/Axiom.hs
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/FamInstEnv.hs
- compiler/GHC/Core/InstEnv.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/LateCC/TopLevelBinds.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Lint/Interactive.hs
- compiler/GHC/Core/Make.hs
- compiler/GHC/Core/Map/Expr.hs
- compiler/GHC/Core/Map/Type.hs
- compiler/GHC/Core/Multiplicity.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CSE.hs
- compiler/GHC/Core/Opt/CallerCC.hs
- compiler/GHC/Core/Opt/ConstantFold.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Monad.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/Pipeline.hs
- compiler/GHC/Core/Opt/Pipeline/Types.hs
- compiler/GHC/Core/Opt/SetLevels.hs
- compiler/GHC/Core/Opt/Simplify.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Opt/WorkWrap.hs
- compiler/GHC/Core/Ppr.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/RoughMap.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/TyCo/Compare.hs
- compiler/GHC/Core/TyCo/FVs.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/TyCo/Subst.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/TyCon/Env.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Type.hs-boot
- compiler/GHC/Core/Unfold/Make.hs
- compiler/GHC/Core/Unify.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/CoreToStg.hs
- compiler/GHC/Data/Bag.hs
- compiler/GHC/Data/FastString.hs
- compiler/GHC/Data/Graph/Collapse.hs
- compiler/GHC/Data/Graph/Color.hs
- compiler/GHC/Data/Graph/Directed.hs
- compiler/GHC/Data/List/Infinite.hs
- compiler/GHC/Data/List/NonEmpty.hs
- compiler/GHC/Data/Maybe.hs
- compiler/GHC/Data/OsPath.hs
- compiler/GHC/Data/Pair.hs
- compiler/GHC/Data/Stream.hs
- compiler/GHC/Data/Strict.hs
- compiler/GHC/Data/StringBuffer.hs
- compiler/GHC/Data/TrieMap.hs
- compiler/GHC/Data/Word64Map.hs
- compiler/GHC/Driver/Backend.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/CmdLine.hs
- compiler/GHC/Driver/CodeOutput.hs
- compiler/GHC/Driver/Config/Core/Lint.hs
- compiler/GHC/Driver/Config/Core/Lint/Interactive.hs
- compiler/GHC/Driver/Config/Core/Opt/Simplify.hs
- + compiler/GHC/Driver/Config/Interpreter.hs
- compiler/GHC/Driver/Config/Linker.hs
- compiler/GHC/Driver/Config/StgToCmm.hs
- compiler/GHC/Driver/Config/Tidy.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Env.hs
- compiler/GHC/Driver/Env/KnotVars.hs
- compiler/GHC/Driver/Errors.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/GenerateCgIPEStub.hs
- compiler/GHC/Driver/Hooks.hs
- compiler/GHC/Driver/LlvmConfigCache.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Driver/MakeSem.hs
- compiler/GHC/Driver/Phases.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Pipeline/LogQueue.hs
- compiler/GHC/Driver/Pipeline/Monad.hs
- compiler/GHC/Driver/Pipeline/Phases.hs
- compiler/GHC/Driver/Plugins.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Driver/Session/Inspect.hs
- compiler/GHC/Driver/Session/Units.hs
- compiler/GHC/Hs.hs
- compiler/GHC/Hs/Basic.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Doc.hs
- compiler/GHC/Hs/Doc.hs-boot
- compiler/GHC/Hs/DocString.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Expr.hs-boot
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Lit.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Pat.hs-boot
- compiler/GHC/Hs/Stats.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/HsToCore/Arrows.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Foreign/C.hs
- compiler/GHC/HsToCore/Foreign/Decl.hs
- compiler/GHC/HsToCore/Foreign/JavaScript.hs
- compiler/GHC/HsToCore/Foreign/Wasm.hs
- compiler/GHC/HsToCore/ListComp.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Match/Literal.hs
- compiler/GHC/HsToCore/Monad.hs
- compiler/GHC/HsToCore/Pmc.hs
- compiler/GHC/HsToCore/Pmc/Check.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Pmc/Solver.hs
- compiler/GHC/HsToCore/Pmc/Solver/Types.hs
- compiler/GHC/HsToCore/Pmc/Types.hs
- compiler/GHC/HsToCore/Pmc/Utils.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/Iface/Binary.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Env.hs
- compiler/GHC/Iface/Errors.hs
- compiler/GHC/Iface/Errors/Ppr.hs
- compiler/GHC/Iface/Errors/Types.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Ext/Debug.hs
- compiler/GHC/Iface/Ext/Types.hs
- compiler/GHC/Iface/Ext/Utils.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Iface/Rename.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Tidy.hs
- compiler/GHC/Iface/Type.hs
- compiler/GHC/Iface/Warnings.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/JS/Ident.hs
- compiler/GHC/JS/JStg/Monad.hs
- compiler/GHC/JS/JStg/Syntax.hs
- compiler/GHC/JS/Make.hs
- compiler/GHC/JS/Optimizer.hs
- compiler/GHC/JS/Ppr.hs
- compiler/GHC/JS/Syntax.hs
- compiler/GHC/JS/Transform.hs
- + compiler/GHC/Linker/ByteCode.hs
- compiler/GHC/Linker/Config.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Dynamic.hs
- + compiler/GHC/Linker/Executable.hs
- − compiler/GHC/Linker/ExtraObj.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/MacOS.hs
- compiler/GHC/Linker/Static.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Linker/Unit.hs
- compiler/GHC/Linker/Windows.hs
- compiler/GHC/Llvm/MetaData.hs
- compiler/GHC/Llvm/Ppr.hs
- compiler/GHC/Llvm/Types.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Errors/Basic.hs
- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Parser/String.hs
- compiler/GHC/Parser/Types.hs
- compiler/GHC/Platform.hs
- compiler/GHC/Platform/Reg/Class.hs
- compiler/GHC/Platform/Reg/Class/NoVectors.hs
- compiler/GHC/Platform/Reg/Class/Separate.hs
- compiler/GHC/Platform/Reg/Class/Unified.hs
- compiler/GHC/Prelude/Basic.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Expr.hs-boot
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Rename/Unbound.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Runtime/Debugger.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Heap/Layout.hs
- compiler/GHC/Runtime/Interpreter.hs
- + compiler/GHC/Runtime/Interpreter/C.hs
- + compiler/GHC/Runtime/Interpreter/Init.hs
- compiler/GHC/Runtime/Interpreter/JS.hs
- compiler/GHC/Runtime/Interpreter/Process.hs
- compiler/GHC/Runtime/Interpreter/Types.hs
- compiler/GHC/Runtime/Interpreter/Types/SymbolCache.hs
- compiler/GHC/Settings.hs
- compiler/GHC/Settings/IO.hs
- compiler/GHC/Stg/Debug.hs
- compiler/GHC/Stg/EnforceEpt.hs
- compiler/GHC/Stg/EnforceEpt/Rewrite.hs
- compiler/GHC/Stg/EnforceEpt/TagSig.hs
- compiler/GHC/Stg/EnforceEpt/Types.hs
- compiler/GHC/Stg/FVs.hs
- compiler/GHC/Stg/Lift/Analysis.hs
- compiler/GHC/Stg/Lift/Monad.hs
- compiler/GHC/Stg/Lift/Types.hs
- compiler/GHC/Stg/Lint.hs
- compiler/GHC/Stg/Pipeline.hs
- compiler/GHC/Stg/Syntax.hs
- compiler/GHC/Stg/Unarise.hs
- compiler/GHC/Stg/Utils.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm.hs
- compiler/GHC/StgToCmm/ArgRep.hs
- compiler/GHC/StgToCmm/Bind.hs
- compiler/GHC/StgToCmm/CgUtils.hs
- compiler/GHC/StgToCmm/Closure.hs
- compiler/GHC/StgToCmm/ExtCode.hs
- compiler/GHC/StgToCmm/InfoTableProv.hs
- compiler/GHC/StgToCmm/Lit.hs
- compiler/GHC/StgToCmm/Monad.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToCmm/Utils.hs
- compiler/GHC/StgToJS/Apply.hs
- compiler/GHC/StgToJS/Arg.hs
- compiler/GHC/StgToJS/CodeGen.hs
- compiler/GHC/StgToJS/DataCon.hs
- compiler/GHC/StgToJS/Deps.hs
- compiler/GHC/StgToJS/Expr.hs
- compiler/GHC/StgToJS/ExprCtx.hs
- compiler/GHC/StgToJS/FFI.hs
- compiler/GHC/StgToJS/Heap.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/StgToJS/Linker/Opt.hs
- compiler/GHC/StgToJS/Linker/Types.hs
- compiler/GHC/StgToJS/Linker/Utils.hs
- compiler/GHC/StgToJS/Literal.hs
- compiler/GHC/StgToJS/Monad.hs
- compiler/GHC/StgToJS/Object.hs
- compiler/GHC/StgToJS/Regs.hs
- compiler/GHC/StgToJS/Rts/Rts.hs
- compiler/GHC/StgToJS/Rts/Types.hs
- compiler/GHC/StgToJS/Sinker/Collect.hs
- compiler/GHC/StgToJS/Sinker/Sinker.hs
- compiler/GHC/StgToJS/Sinker/StringsUnfloat.hs
- compiler/GHC/StgToJS/Types.hs
- compiler/GHC/StgToJS/Utils.hs
- compiler/GHC/SysTools.hs
- compiler/GHC/SysTools/Ar.hs
- compiler/GHC/SysTools/BaseDir.hs
- compiler/GHC/SysTools/Cpp.hs
- compiler/GHC/SysTools/Tasks.hs
- compiler/GHC/SysTools/Terminal.hs
- compiler/GHC/Tc/Deriv.hs
- compiler/GHC/Tc/Deriv/Functor.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/Hole.hs
- compiler/GHC/Tc/Errors/Hole/FitTypes.hs
- compiler/GHC/Tc/Errors/Hole/Plugin.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Errors/Types/PromotionErr.hs
- compiler/GHC/Tc/Gen/Annotation.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Default.hs
- compiler/GHC/Tc/Gen/Do.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Expr.hs-boot
- compiler/GHC/Tc/Gen/Foreign.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Gen/Match.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/Instance/Family.hs
- compiler/GHC/Tc/Instance/FunDeps.hs
- compiler/GHC/Tc/Instance/Typeable.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/FunDeps.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Irred.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Rewrite.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/Solver/Types.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Build.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/ErrCtxt.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Backpack.hs
- compiler/GHC/Tc/Utils/Concrete.hs
- compiler/GHC/Tc/Utils/Env.hs
- compiler/GHC/Tc/Utils/Instantiate.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/Validity.hs
- compiler/GHC/Tc/Zonk/Monad.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Types/Annotations.hs
- + compiler/GHC/Types/Arity.hs
- compiler/GHC/Types/Avail.hs
- compiler/GHC/Types/Basic.hs
- compiler/GHC/Types/CompleteMatch.hs
- compiler/GHC/Types/CostCentre.hs
- compiler/GHC/Types/CostCentre/State.hs
- compiler/GHC/Types/DefaultEnv.hs
- compiler/GHC/Types/Demand.hs
- compiler/GHC/Types/Error.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/FieldLabel.hs
- compiler/GHC/Types/Fixity.hs
- compiler/GHC/Types/ForeignCall.hs
- compiler/GHC/Types/ForeignStubs.hs
- compiler/GHC/Types/GREInfo.hs
- compiler/GHC/Types/Hint.hs
- compiler/GHC/Types/Hint/Ppr.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Info.hs
- compiler/GHC/Types/Id/Make.hs
- + compiler/GHC/Types/InlinePragma.hs
- compiler/GHC/Types/Literal.hs
- compiler/GHC/Types/Name.hs
- compiler/GHC/Types/Name/Cache.hs
- compiler/GHC/Types/Name/Occurrence.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Types/Name/Set.hs
- compiler/GHC/Types/PkgQual.hs
- compiler/GHC/Types/RepType.hs
- compiler/GHC/Types/SaneDouble.hs
- compiler/GHC/Types/SourceText.hs
- compiler/GHC/Types/SrcLoc.hs
- compiler/GHC/Types/Tickish.hs
- compiler/GHC/Types/TyThing.hs
- compiler/GHC/Types/Unique/DFM.hs
- compiler/GHC/Types/Unique/DSet.hs
- compiler/GHC/Types/Unique/FM.hs
- compiler/GHC/Types/Unique/Map.hs
- compiler/GHC/Types/Unique/SDFM.hs
- compiler/GHC/Types/Unique/Set.hs
- compiler/GHC/Types/Var.hs
- compiler/GHC/Types/Var/Env.hs
- compiler/GHC/Unit.hs
- compiler/GHC/Unit/Env.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Home/ModInfo.hs
- compiler/GHC/Unit/Home/PackageTable.hs
- compiler/GHC/Unit/Info.hs
- compiler/GHC/Unit/Module.hs
- compiler/GHC/Unit/Module/Deps.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Unit/Module/ModIface.hs
- compiler/GHC/Unit/Module/ModSummary.hs
- compiler/GHC/Unit/Module/Status.hs
- compiler/GHC/Unit/Module/Warnings.hs
- compiler/GHC/Unit/Module/WholeCoreBindings.hs
- compiler/GHC/Unit/State.hs
- compiler/GHC/Unit/Types.hs
- compiler/GHC/Unit/Types.hs-boot
- compiler/GHC/Utils/Binary.hs
- compiler/GHC/Utils/Binary/Typeable.hs
- compiler/GHC/Utils/Exception.hs
- compiler/GHC/Utils/Json.hs
- compiler/GHC/Utils/Logger.hs
- compiler/GHC/Utils/Misc.hs
- compiler/GHC/Utils/Monad/Codensity.hs
- compiler/GHC/Utils/Outputable.hs
- compiler/GHC/Utils/Panic.hs
- compiler/GHC/Utils/Panic/Plain.hs
- compiler/GHC/Wasm/ControlFlow.hs
- compiler/GHC/Wasm/ControlFlow/FromCmm.hs
- compiler/Language/Haskell/Syntax.hs
- compiler/Language/Haskell/Syntax/Basic.hs
- compiler/Language/Haskell/Syntax/Binds.hs
- + compiler/Language/Haskell/Syntax/Binds/InlinePragma.hs
- compiler/Language/Haskell/Syntax/Decls.hs
- compiler/Language/Haskell/Syntax/Expr.hs
- compiler/Language/Haskell/Syntax/Expr.hs-boot
- compiler/Language/Haskell/Syntax/Extension.hs
- compiler/Language/Haskell/Syntax/ImpExp.hs
- compiler/Language/Haskell/Syntax/Lit.hs
- compiler/Language/Haskell/Syntax/Pat.hs
- compiler/Language/Haskell/Syntax/Pat.hs-boot
- compiler/Language/Haskell/Syntax/Type.hs
- compiler/ghc.cabal.in
- configure.ac
- distrib/configure.ac.in
- − docs/Makefile
- − docs/storage-mgt/Makefile
- docs/users_guide/9.16.1-notes.rst
- − docs/users_guide/Makefile
- docs/users_guide/bugs.rst
- docs/users_guide/compare-flags.py
- 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/arrows.rst
- docs/users_guide/exts/data_kinds.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/explicit_namespaces.rst
- docs/users_guide/exts/gadt.rst
- docs/users_guide/exts/gadt_syntax.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/pragmas.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/table.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/exts/type_families.rst
- docs/users_guide/ghci.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-optimisation.rst
- docs/users_guide/using.rst
- docs/users_guide/wasm.rst
- docs/users_guide/win32-dlls.rst
- − driver/Makefile
- − driver/ghc/Makefile
- − driver/ghci/Makefile
- − driver/haddock/Makefile
- − driver/utils/merge_sections.ld
- − driver/utils/merge_sections_pe.ld
- ghc/GHC/Driver/Session/Lint.hs
- ghc/GHC/Driver/Session/Mode.hs
- ghc/GHCi/Leak.hs
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Exception.hs
- ghc/GHCi/UI/Info.hs
- ghc/GHCi/UI/Monad.hs
- ghc/Main.hs
- − ghc/Makefile
- ghc/ghc-bin.cabal.in
- hadrian/cabal.project
- hadrian/cfg/default.host.target.in
- hadrian/cfg/default.target.in
- hadrian/doc/flavours.md
- hadrian/hadrian.cabal
- hadrian/src/Base.hs
- hadrian/src/Builder.hs
- hadrian/src/Context.hs
- hadrian/src/Flavour.hs
- hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
- hadrian/src/Hadrian/Haskell/Cabal/Type.hs
- hadrian/src/Hadrian/Haskell/Hash.hs
- hadrian/src/Hadrian/Oracles/ArgsHash.hs
- hadrian/src/Hadrian/Oracles/Cabal/Type.hs
- hadrian/src/Hadrian/Oracles/DirectoryContents.hs
- hadrian/src/Hadrian/Oracles/Path.hs
- hadrian/src/Hadrian/Oracles/TextFile.hs
- hadrian/src/Hadrian/Utilities.hs
- hadrian/src/Oracles/Flag.hs
- hadrian/src/Oracles/Flavour.hs
- hadrian/src/Oracles/ModuleFiles.hs
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Packages.hs
- hadrian/src/Rules.hs
- hadrian/src/Rules/Gmp.hs
- hadrian/src/Rules/Library.hs
- hadrian/src/Rules/Register.hs
- hadrian/src/Rules/ToolArgs.hs
- hadrian/src/Settings.hs
- hadrian/src/Settings/Builders/Cabal.hs
- hadrian/src/Settings/Builders/Ghc.hs
- hadrian/src/Settings/Builders/Hsc2Hs.hs
- − hadrian/src/Settings/Builders/MergeObjects.hs
- hadrian/src/Settings/Builders/RunTest.hs
- hadrian/src/Settings/Builders/SplitSections.hs
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Flavours/Validate.hs
- hadrian/src/Settings/Packages.hs
- hadrian/src/Settings/Warnings.hs
- hadrian/stack.yaml
- hadrian/stack.yaml.lock
- − libraries/Makefile
- libraries/base/base.cabal.in
- libraries/base/changelog.md
- libraries/base/src/Data/List.hs
- libraries/base/src/Data/List/NonEmpty.hs
- + libraries/base/src/Data/List/NubOrdSet.hs
- libraries/base/src/GHC/ByteOrder.hs
- libraries/base/src/GHC/Conc.hs
- libraries/base/src/GHC/Conc/Sync.hs
- libraries/base/src/GHC/Num.hs
- libraries/base/src/System/IO.hs
- libraries/base/src/System/Info.hs
- libraries/base/tests/all.T
- − libraries/doc/Makefile
- libraries/exceptions
- libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs
- libraries/ghc-boot/GHC/Unit/Database.hs
- libraries/ghc-internal/configure.ac
- libraries/ghc-internal/ghc-internal.buildinfo.in
- libraries/ghc-internal/ghc-internal.cabal.in
- libraries/ghc-internal/include/HsIntegerGmp.h.in
- libraries/ghc-internal/src/GHC/Internal/ByteOrder.hs
- − libraries/ghc-internal/src/GHC/Internal/ByteOrder.hs-boot
- libraries/ghc-internal/src/GHC/Internal/Conc/IO.hs
- libraries/ghc-internal/src/GHC/Internal/Conc/POSIX.hs
- libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs
- libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs-boot
- libraries/ghc-internal/src/GHC/Internal/Conc/Windows.hs
- libraries/ghc-internal/src/GHC/Internal/Control/Monad.hs
- libraries/ghc-internal/src/GHC/Internal/Control/Monad/ST/Lazy/Imp.hs
- libraries/ghc-internal/src/GHC/Internal/Data/OldList.hs
- libraries/ghc-internal/src/GHC/Internal/Event/Thread.hs
- libraries/ghc-internal/src/GHC/Internal/Event/Windows/Thread.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs
- libraries/ghc-internal/src/GHC/Internal/Float.hs
- libraries/ghc-internal/src/GHC/Internal/Functor/ZipList.hs
- libraries/ghc-internal/src/GHC/Internal/Generics.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Handle.hs
- libraries/ghc-internal/src/GHC/Internal/List.hs
- libraries/ghc-internal/src/GHC/Internal/Read.hs
- + libraries/ghc-internal/src/GHC/Internal/STM.hs
- libraries/ghc-internal/src/GHC/Internal/Stack/Decode.hs
- libraries/ghc-internal/src/GHC/Internal/System/IO.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Monad.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Bits.hs
- libraries/os-string
- libraries/template-haskell/vendored-filepath/System/FilePath/Posix.hs
- libraries/template-haskell/vendored-filepath/System/FilePath/Windows.hs
- libraries/unix
- libraries/xhtml
- linters/lint-codes/LintCodes/Static.hs
- − linters/lint-codes/Makefile
- − linters/lint-notes/Makefile
- llvm-passes
- − m4/find_ghc_bootstrap_prog.m4
- − m4/fp_copy_shellvar.m4
- + m4/fp_linker_supports_verbatim.m4
- − m4/fp_prog_ld_flag.m4
- − m4/fp_prog_sort.m4
- m4/prep_target_file.m4
- mk/system-cxx-std-lib-1.0.conf.in
- − mk/win32-tarballs.md5sum
- + rts/.ubsan-suppressions
- rts/Apply.cmm
- rts/Compact.cmm
- rts/ContinuationOps.cmm
- rts/Exception.cmm
- rts/Interpreter.c
- rts/Jumps.h
- − rts/Makefile
- rts/PrimOps.cmm
- rts/RtsMessages.c
- rts/StgMiscClosures.cmm
- rts/StgStartup.cmm
- rts/configure.ac
- rts/eventlog/EventLog.c
- rts/gen_event_types.py
- − rts/include/Makefile
- rts/include/Stg.h
- rts/include/rts/Bytecodes.h
- rts/include/rts/Messages.h
- rts/include/stg/Types.h
- rts/linker/Elf.c
- rts/linker/InitFini.c
- rts/linker/LoadArchive.c
- rts/linker/PEi386.c
- rts/prim/mulIntMayOflo.c
- rts/rts.buildinfo.in
- rts/rts.cabal
- rts/sm/Sanity.c
- testsuite/config/ghc
- + testsuite/driver/_elffile.py
- testsuite/driver/runtests.py
- testsuite/driver/testglobals.py
- testsuite/driver/testlib.py
- testsuite/ghc-config/ghc-config.hs
- testsuite/mk/boilerplate.mk
- testsuite/tests/backpack/should_fail/T19244a.stderr
- + testsuite/tests/bytecode/T23973.hs
- + testsuite/tests/bytecode/T23973.script
- + testsuite/tests/bytecode/T23973.stdout
- + testsuite/tests/bytecode/T26565.hs
- + testsuite/tests/bytecode/T26565.script
- + testsuite/tests/bytecode/T26565.stdout
- + testsuite/tests/bytecode/T26640.hs
- + testsuite/tests/bytecode/T26640.script
- + testsuite/tests/bytecode/T26640.stdout
- testsuite/tests/bytecode/all.T
- + testsuite/tests/cabal/Bytecode.hs
- + testsuite/tests/cabal/BytecodeForeign.c
- + testsuite/tests/cabal/BytecodeForeign.hs
- testsuite/tests/cabal/Makefile
- testsuite/tests/cabal/all.T
- + testsuite/tests/cabal/bytecode.pkg
- + testsuite/tests/cabal/bytecode.script
- + testsuite/tests/cabal/bytecode_foreign.pkg
- + testsuite/tests/cabal/bytecode_foreign.script
- testsuite/tests/cabal/ghcpkg03.stderr
- testsuite/tests/cabal/ghcpkg03.stderr-mingw32
- testsuite/tests/cabal/ghcpkg05.stderr
- testsuite/tests/cabal/ghcpkg05.stderr-mingw32
- + testsuite/tests/cabal/pkg_bytecode.stderr
- + testsuite/tests/cabal/pkg_bytecode.stdout
- + testsuite/tests/cabal/pkg_bytecode_foreign.stderr
- + testsuite/tests/cabal/pkg_bytecode_foreign.stdout
- + testsuite/tests/cabal/pkg_bytecode_with_gbc.stderr
- + testsuite/tests/cabal/pkg_bytecode_with_gbc.stdout
- + testsuite/tests/cabal/pkg_bytecode_with_o.stderr
- + testsuite/tests/cabal/pkg_bytecode_with_o.stdout
- + testsuite/tests/cmm/opt/T25664.hs
- + testsuite/tests/cmm/opt/T25664.stdout
- testsuite/tests/cmm/opt/all.T
- + testsuite/tests/codeGen/should_run/T24016.hs
- + testsuite/tests/codeGen/should_run/T24016.stdout
- + testsuite/tests/codeGen/should_run/T26537.hs
- + testsuite/tests/codeGen/should_run/T26537.stdout
- testsuite/tests/codeGen/should_run/all.T
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- testsuite/tests/dependent/should_fail/T11334b.stderr
- testsuite/tests/diagnostic-codes/codes.stdout
- + testsuite/tests/dmdanal/should_run/T26748.hs
- + testsuite/tests/dmdanal/should_run/T26748.stdout
- testsuite/tests/dmdanal/should_run/all.T
- testsuite/tests/driver/Makefile
- + testsuite/tests/driver/T20696/T20696.stderr-ext-interp
- + testsuite/tests/driver/T24120.hs
- + testsuite/tests/driver/T24731.hs
- + testsuite/tests/driver/T26551.hs
- + testsuite/tests/driver/T26551.stderr
- testsuite/tests/driver/all.T
- testsuite/tests/driver/bytecode-object/Makefile
- testsuite/tests/driver/bytecode-object/all.T
- testsuite/tests/driver/bytecode-object/bytecode_object19.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object20.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object21.stderr
- + testsuite/tests/driver/bytecode-object/bytecode_object21.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object23.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object24.stdout
- + testsuite/tests/driver/fat-iface/fat012.stderr-ext-interp
- + testsuite/tests/driver/fat-iface/fat015.stderr-ext-interp
- + testsuite/tests/driver/fully-static/Hello.hs
- + testsuite/tests/driver/fully-static/Makefile
- + testsuite/tests/driver/fully-static/all.T
- + testsuite/tests/driver/fully-static/fully-static.stdout
- + testsuite/tests/driver/fully-static/test/Test.hs
- + testsuite/tests/driver/fully-static/test/test.pkg
- testsuite/tests/driver/j-space/jspace.hs
- + testsuite/tests/driver/mostly-static/Hello.hs
- + testsuite/tests/driver/mostly-static/Makefile
- + testsuite/tests/driver/mostly-static/all.T
- + testsuite/tests/driver/mostly-static/mostly-static.stdout
- + testsuite/tests/driver/mostly-static/test/test.c
- + testsuite/tests/driver/mostly-static/test/test.h
- + testsuite/tests/driver/mostly-static/test/test.pkg
- + testsuite/tests/driver/recomp26183/M.hs
- + testsuite/tests/driver/recomp26183/M2A.hs
- + testsuite/tests/driver/recomp26183/M2B.hs
- + testsuite/tests/driver/recomp26183/Makefile
- + testsuite/tests/driver/recomp26183/all.T
- + testsuite/tests/driver/recomp26183/recomp26183.stderr
- + testsuite/tests/driver/recomp26705/M.hs
- + testsuite/tests/driver/recomp26705/M2A.hs
- + testsuite/tests/driver/recomp26705/M2B.hs
- + testsuite/tests/driver/recomp26705/Makefile
- + testsuite/tests/driver/recomp26705/all.T
- + testsuite/tests/driver/recomp26705/recomp26705.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/T8353.stderr
- testsuite/tests/ghci/scripts/T8959b.stderr
- testsuite/tests/ghci/scripts/ghci051.stderr
- 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/indexed-types/should_compile/CEqCanOccursCheck.hs
- testsuite/tests/indexed-types/should_compile/T12538.stderr
- testsuite/tests/indexed-types/should_fail/T12522a.hs
- testsuite/tests/indexed-types/should_fail/T21092.hs
- − testsuite/tests/indexed-types/should_fail/T21092.stderr
- testsuite/tests/indexed-types/should_fail/T26176.stderr
- testsuite/tests/indexed-types/should_fail/all.T
- 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/jsffi/all.T
- + testsuite/tests/jsffi/bytearrayarg.hs
- + testsuite/tests/jsffi/bytearrayarg.mjs
- + testsuite/tests/jsffi/bytearrayarg.stdout
- + 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/linear/should_run/T26311.hs
- + testsuite/tests/linear/should_run/T26311.stdout
- testsuite/tests/linear/should_run/all.T
- + testsuite/tests/module/T25901_exp_plain_wc.hs
- + testsuite/tests/module/T25901_exp_plain_wc.stderr
- + testsuite/tests/module/T25901_imp_plain_wc.hs
- + testsuite/tests/module/T25901_imp_plain_wc.stderr
- testsuite/tests/module/all.T
- testsuite/tests/numeric/should_compile/T16402.stderr-ws-64
- testsuite/tests/numeric/should_run/all.T
- testsuite/tests/numeric/should_run/foundation.hs
- testsuite/tests/numeric/should_run/foundation.stdout
- testsuite/tests/overloadedrecflds/should_fail/DRFHoleFits.stderr
- testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail10.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail13.stderr
- testsuite/tests/parser/should_fail/T20654a.stderr
- testsuite/tests/patsyn/should_fail/all.T
- + testsuite/tests/patsyn/should_fail/import-syntax-no-ext.hs
- + testsuite/tests/patsyn/should_fail/import-syntax-no-ext.stderr
- testsuite/tests/perf/compiler/all.T
- testsuite/tests/perf/compiler/hard_hole_fits.stderr
- testsuite/tests/perf/should_run/all.T
- testsuite/tests/plugins/test-hole-plugin.stderr
- testsuite/tests/pmcheck/should_compile/T15753c.hs
- + testsuite/tests/pmcheck/should_compile/T15753c.stderr
- testsuite/tests/pmcheck/should_compile/T15753d.hs
- + testsuite/tests/pmcheck/should_compile/T15753d.stderr
- + testsuite/tests/pmcheck/should_compile/T22652.hs
- + testsuite/tests/pmcheck/should_compile/T22652a.hs
- + testsuite/tests/pmcheck/should_compile/T24867.hs
- + testsuite/tests/pmcheck/should_compile/T24867.stderr
- testsuite/tests/pmcheck/should_compile/all.T
- testsuite/tests/pmcheck/should_compile/pmcOrPats.stderr
- + testsuite/tests/polykinds/T13882.hs
- testsuite/tests/polykinds/all.T
- testsuite/tests/quantified-constraints/T15316A.stderr
- testsuite/tests/quantified-constraints/T17267.stderr
- testsuite/tests/quantified-constraints/T17267a.stderr
- testsuite/tests/quantified-constraints/T17267b.stderr
- testsuite/tests/quantified-constraints/T17267c.stderr
- testsuite/tests/quantified-constraints/T17267e.stderr
- testsuite/tests/quantified-constraints/T17458.stderr
- + testsuite/tests/rename/should_compile/T25901_exp_1.hs
- + testsuite/tests/rename/should_compile/T25901_exp_1_helper.hs
- + testsuite/tests/rename/should_compile/T25901_exp_2.hs
- + testsuite/tests/rename/should_compile/T25901_exp_2_helper.hs
- + testsuite/tests/rename/should_compile/T25901_imp_hq.hs
- + testsuite/tests/rename/should_compile/T25901_imp_hu.hs
- + testsuite/tests/rename/should_compile/T25901_imp_sq.hs
- + testsuite/tests/rename/should_compile/T25901_imp_su.hs
- + testsuite/tests/rename/should_compile/T25901_sub_e.hs
- + testsuite/tests/rename/should_compile/T25901_sub_f.hs
- + testsuite/tests/rename/should_compile/T25901_sub_f.stderr
- + testsuite/tests/rename/should_compile/T25901_sub_g.hs
- + testsuite/tests/rename/should_compile/T25901_sub_g.stderr
- + testsuite/tests/rename/should_compile/T25901_sub_g_helper.hs
- testsuite/tests/rename/should_compile/all.T
- testsuite/tests/rename/should_fail/T23570b.stderr
- + testsuite/tests/rename/should_fail/T25901_exp_fail_1.hs
- + testsuite/tests/rename/should_fail/T25901_exp_fail_1.stderr
- + testsuite/tests/rename/should_fail/T25901_exp_fail_1_helper.hs
- + testsuite/tests/rename/should_fail/T25901_exp_fail_2.hs
- + testsuite/tests/rename/should_fail/T25901_exp_fail_2.stderr
- + testsuite/tests/rename/should_fail/T25901_exp_fail_2_helper.hs
- + testsuite/tests/rename/should_fail/T25901_imp_hq_fail_5.hs
- + testsuite/tests/rename/should_fail/T25901_imp_hq_fail_5.stderr
- + testsuite/tests/rename/should_fail/T25901_imp_hq_fail_6.hs
- + testsuite/tests/rename/should_fail/T25901_imp_hq_fail_6.stderr
- + testsuite/tests/rename/should_fail/T25901_imp_hu_fail_4.hs
- + testsuite/tests/rename/should_fail/T25901_imp_hu_fail_4.stderr
- + testsuite/tests/rename/should_fail/T25901_imp_sq_fail_2.hs
- + testsuite/tests/rename/should_fail/T25901_imp_sq_fail_2.stderr
- + testsuite/tests/rename/should_fail/T25901_imp_sq_fail_3.hs
- + testsuite/tests/rename/should_fail/T25901_imp_sq_fail_3.stderr
- + testsuite/tests/rename/should_fail/T25901_imp_su_fail_1.hs
- + testsuite/tests/rename/should_fail/T25901_imp_su_fail_1.stderr
- + testsuite/tests/rename/should_fail/T25901_sub_a.hs
- + testsuite/tests/rename/should_fail/T25901_sub_a.stderr
- + testsuite/tests/rename/should_fail/T25901_sub_b.hs
- + testsuite/tests/rename/should_fail/T25901_sub_b.stderr
- + testsuite/tests/rename/should_fail/T25901_sub_c.hs
- + testsuite/tests/rename/should_fail/T25901_sub_c.stderr
- + testsuite/tests/rename/should_fail/T25901_sub_c_helper.hs
- + testsuite/tests/rename/should_fail/T25901_sub_d.hs
- + testsuite/tests/rename/should_fail/T25901_sub_d.stderr
- + testsuite/tests/rename/should_fail/T25901_sub_d_helper.hs
- + testsuite/tests/rename/should_fail/T25901_sub_w.hs
- + testsuite/tests/rename/should_fail/T25901_sub_w.stderr
- testsuite/tests/rename/should_fail/all.T
- testsuite/tests/rename/should_fail/rnfail055.stderr
- 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/T26072b.hs
- + testsuite/tests/rep-poly/T26528.hs
- testsuite/tests/rep-poly/UnliftedNewtypesLevityBinder.stderr
- testsuite/tests/rep-poly/all.T
- testsuite/tests/rts/KeepCafsBase.hs
- testsuite/tests/rts/all.T
- 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/T26411.hs
- + testsuite/tests/simd/should_run/T26411.stdout
- + testsuite/tests/simd/should_run/T26411b.hs
- + testsuite/tests/simd/should_run/T26411b.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/simplCore/should_compile/T26588.hs
- + testsuite/tests/simplCore/should_compile/T26589.hs
- + testsuite/tests/simplCore/should_compile/T26681.hs
- + testsuite/tests/simplCore/should_compile/T26682.hs
- + testsuite/tests/simplCore/should_compile/T26682a.hs
- + testsuite/tests/simplCore/should_compile/T26709.hs
- + testsuite/tests/simplCore/should_compile/T26709.stderr
- testsuite/tests/simplCore/should_compile/T8331.stderr
- testsuite/tests/simplCore/should_compile/all.T
- testsuite/tests/simplStg/should_compile/all.T
- + testsuite/tests/splice-imports/SI07.stderr-ext-interp
- testsuite/tests/th/T15321.stderr
- + testsuite/tests/th/T26099.hs
- + testsuite/tests/th/T26099.stderr
- + testsuite/tests/th/T26568.hs
- + testsuite/tests/th/T26568.stderr
- testsuite/tests/th/all.T
- testsuite/tests/typecheck/T16127/T16127.stderr
- testsuite/tests/typecheck/should_compile/T13050.stderr
- testsuite/tests/typecheck/should_compile/T14273.stderr
- testsuite/tests/typecheck/should_compile/T14590.stderr
- testsuite/tests/typecheck/should_compile/T16188.hs
- testsuite/tests/typecheck/should_compile/T22560d.stdout
- testsuite/tests/typecheck/should_compile/T25180.stderr
- + testsuite/tests/typecheck/should_compile/T26451.hs
- + testsuite/tests/typecheck/should_compile/T26582.hs
- testsuite/tests/typecheck/should_compile/abstract_refinement_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_compile/constraint_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/free_monad_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/hole_constraints.stderr
- testsuite/tests/typecheck/should_compile/holes.stderr
- testsuite/tests/typecheck/should_compile/holes2.stderr
- testsuite/tests/typecheck/should_compile/holes3.stderr
- testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/subsumption_sort_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/type_in_type_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/valid_hole_fits_interactions.stderr
- testsuite/tests/typecheck/should_fail/ContextStack1.stderr
- testsuite/tests/typecheck/should_fail/FD3.stderr
- testsuite/tests/typecheck/should_fail/FDsFromGivens2.stderr
- testsuite/tests/typecheck/should_fail/FunDepOrigin1b.stderr
- testsuite/tests/typecheck/should_fail/T13506.stderr
- testsuite/tests/typecheck/should_fail/T14884.stderr
- testsuite/tests/typecheck/should_fail/T15629.stderr
- testsuite/tests/typecheck/should_fail/T15767.stderr
- testsuite/tests/typecheck/should_fail/T15883e.stderr
- testsuite/tests/typecheck/should_fail/T19415.stderr
- testsuite/tests/typecheck/should_fail/T19415b.stderr
- testsuite/tests/typecheck/should_fail/T22924b.stderr
- + testsuite/tests/typecheck/should_fail/T23162b.hs
- + testsuite/tests/typecheck/should_fail/T23162b.stderr
- + testsuite/tests/typecheck/should_fail/T23162c.hs
- + testsuite/tests/typecheck/should_fail/T23162d.hs
- testsuite/tests/typecheck/should_fail/T2414.stderr
- testsuite/tests/typecheck/should_fail/T24279.hs
- − testsuite/tests/typecheck/should_fail/T24279.stderr
- testsuite/tests/typecheck/should_fail/T25325.stderr
- testsuite/tests/typecheck/should_fail/T2534.stderr
- testsuite/tests/typecheck/should_fail/T5236.stderr
- testsuite/tests/typecheck/should_fail/T5246.stderr
- testsuite/tests/typecheck/should_fail/T5978.stderr
- testsuite/tests/typecheck/should_fail/T7264.stderr
- testsuite/tests/typecheck/should_fail/T9612.stderr
- testsuite/tests/typecheck/should_fail/TcCoercibleFail.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/typecheck/should_fail/tcfail143.stderr
- testsuite/tests/unboxedsums/UbxSumUnpackedSize.hs
- testsuite/tests/warnings/should_compile/DodgyExports03.stderr
- testsuite/tests/warnings/should_compile/DodgyImports.stderr
- + testsuite/tests/warnings/should_compile/DodgyImports02.hs
- + testsuite/tests/warnings/should_compile/DodgyImports02.stderr
- + testsuite/tests/warnings/should_compile/DodgyImports03.hs
- + testsuite/tests/warnings/should_compile/DodgyImports03.stderr
- + testsuite/tests/warnings/should_compile/DodgyImports03_helper.hs
- + testsuite/tests/warnings/should_compile/DodgyImports04.hs
- + testsuite/tests/warnings/should_compile/DodgyImports04.stderr
- testsuite/tests/warnings/should_compile/DodgyImports_hiding.stderr
- + testsuite/tests/warnings/should_compile/T25901_exp_dodgy.hs
- + testsuite/tests/warnings/should_compile/T25901_exp_dodgy.stderr
- + testsuite/tests/warnings/should_compile/T25901_exp_dup_wc_1.hs
- + testsuite/tests/warnings/should_compile/T25901_exp_dup_wc_1.stderr
- + testsuite/tests/warnings/should_compile/T25901_exp_dup_wc_2.hs
- + testsuite/tests/warnings/should_compile/T25901_exp_dup_wc_2.stderr
- + testsuite/tests/warnings/should_compile/T25901_exp_dup_wc_3.hs
- + testsuite/tests/warnings/should_compile/T25901_exp_dup_wc_3.stderr
- + testsuite/tests/warnings/should_compile/T25901_exp_dup_wc_4.hs
- + testsuite/tests/warnings/should_compile/T25901_exp_dup_wc_4.stderr
- + testsuite/tests/warnings/should_compile/T25901_helper_1.hs
- + testsuite/tests/warnings/should_compile/T25901_helper_2.hs
- + testsuite/tests/warnings/should_compile/T25901_helper_3.hs
- + testsuite/tests/warnings/should_compile/T25901_imp_dodgy_1.hs
- + testsuite/tests/warnings/should_compile/T25901_imp_dodgy_1.stderr
- + testsuite/tests/warnings/should_compile/T25901_imp_dodgy_2.hs
- + testsuite/tests/warnings/should_compile/T25901_imp_dodgy_2.stderr
- + testsuite/tests/warnings/should_compile/T25901_imp_unused_1.hs
- + testsuite/tests/warnings/should_compile/T25901_imp_unused_1.stderr
- + testsuite/tests/warnings/should_compile/T25901_imp_unused_2.hs
- + testsuite/tests/warnings/should_compile/T25901_imp_unused_2.stderr
- + testsuite/tests/warnings/should_compile/T25901_imp_unused_3.hs
- + testsuite/tests/warnings/should_compile/T25901_imp_unused_3.stderr
- + testsuite/tests/warnings/should_compile/T25901_imp_unused_4.hs
- + testsuite/tests/warnings/should_compile/T25901_imp_unused_4.stderr
- testsuite/tests/warnings/should_compile/all.T
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Main.hs
- utils/check-exact/Transform.hs
- utils/check-exact/Utils.hs
- utils/deriveConstants/Main.hs
- utils/genapply/Main.hs
- utils/ghc-pkg/Main.hs
- utils/ghc-toolchain/exe/Main.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Utils.hs
- utils/haddock/cabal.project
- utils/haddock/haddock-api/haddock-api.cabal
- − utils/haddock/haddock-api/src/Haddock/Backends/HaddockDB.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.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/LaTeX.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Names.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Themes.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Utils.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/Doc.hs
- utils/haddock/haddock-api/src/Haddock/GhcUtils.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Create.hs
- utils/haddock/haddock-api/src/Haddock/Utils.hs
- utils/haddock/haddock-library/src/Documentation/Haddock/Parser.hs
- utils/haddock/haddock-test/src/Test/Haddock.hs
- utils/haddock/html-test/ref/Bug1004.html
- utils/haddock/html-test/ref/Bug1050.html
- utils/haddock/html-test/ref/Bug26.html
- + utils/haddock/html-test/ref/Bug26246.html
- utils/haddock/html-test/ref/Bug298.html
- utils/haddock/html-test/ref/Bug458.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/Nesting.html
- utils/haddock/html-test/ref/PatternSyns.html
- + utils/haddock/html-test/ref/PatternSyns2.html
- utils/haddock/html-test/ref/PromotedTypes.html
- utils/haddock/html-test/ref/TitledPicture.html
- utils/haddock/html-test/ref/TypeOperators.html
- utils/haddock/html-test/ref/Unicode.html
- utils/haddock/html-test/ref/Unicode2.html
- + utils/haddock/html-test/src/Bug26246.hs
- + utils/haddock/html-test/src/PatternSyns2.hs
- utils/haddock/hypsrc-test/ref/src/Classes.html
- utils/haddock/hypsrc-test/ref/src/Quasiquoter.html
- utils/haddock/latex-test/ref/LinearTypes/LinearTypes.tex
- utils/hpc
- utils/hsc2hs
- − utils/iserv/cbits/iservmain.c
- utils/iserv/iserv.cabal.in
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c61b6d0ae4d30b74624bff6b65831a…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c61b6d0ae4d30b74624bff6b65831a…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
11 Jan '26
Bodigrim pushed new branch wip/since-for-data.bifoldable1 at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/since-for-data.bifoldable1
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T26343] base: don't expose GHC.Num.{BigNat, Integer, Natural}
by Teo Camarasu (@teo) 11 Jan '26
by Teo Camarasu (@teo) 11 Jan '26
11 Jan '26
Teo Camarasu pushed to branch wip/T26343 at Glasgow Haskell Compiler / GHC
Commits:
68515163 by Teo Camarasu at 2026-01-10T22:32:29+00:00
base: don't expose GHC.Num.{BigNat, Integer, Natural}
We no longer expose GHC.Num.{BigNat, Integer, Natural} from base instead users should get these modules from ghc-bignum.
We make this change to insulate end users from changes to GHC's implementation of big numbers.
Implements CLC proposal 359: https://github.com/haskell/core-libraries-committee/issues/359
- - - - -
13 changed files:
- libraries/base/base.cabal.in
- libraries/base/changelog.md
- libraries/base/src/Data/Array/Byte.hs
- − libraries/base/src/GHC/Num/BigNat.hs
- − libraries/base/src/GHC/Num/Integer.hs
- − libraries/base/src/GHC/Num/Natural.hs
- libraries/base/src/System/CPUTime/Utils.hs
- libraries/ghc-bignum/ghc-bignum.cabal
- libraries/ghc-experimental/src/GHC/TypeNats/Experimental.hs
- 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
Changes:
=====================================
libraries/base/base.cabal.in
=====================================
@@ -219,9 +219,6 @@ Library
, GHC.MVar
, GHC.Natural
, GHC.Num
- , GHC.Num.Integer
- , GHC.Num.Natural
- , GHC.Num.BigNat
, GHC.OldList
, GHC.OverloadedLabels
, GHC.Profiling
=====================================
libraries/base/changelog.md
=====================================
@@ -11,6 +11,7 @@
* Modify the implementation of `Data.List.sortOn` to use `(>)` instead of `compare`. ([CLC proposal #332](https://github.com/haskell/core-libraries-committee/issues/332))
* Add `thenA` and `thenM`. ([CLC proposal #351](https://github.com/haskell/core-libraries-committee/issues/351))
* Fix bug where `naturalAndNot` was incorrectly truncating results ([CLC proposal #350](github.com/haskell/core-libraries-committee/issues/350))
+ * GHC.Num.{BigNat, Integer, Natural} are no longer exposed. Users should import them from `ghc-bignum` instead. ([CLC proposal #359](github.com/haskell/core-libraries-committee/issues/359))
* Remove extra laziness from `Data.Bifunctor.Bifunctor` instances for all tuples to have the same laziness as their `Data.Functor.Functor` counterparts (i.e. they became more strict than before) ([CLC proposal #339](https://github.com/haskell/core-libraries-committee/issues/339))
* Adjust the strictness of `Data.List.iterate'` to be more reasonable: every element of the output list is forced to WHNF when the `(:)` containing it is forced. ([CLC proposal #335)](https://github.com/haskell/core-libraries-committee/issues/335)
* Add `nubOrd` / `nubOrdBy` to `Data.List` and `Data.List.NonEmpty`. ([CLC proposal #336](https://github.com/haskell/core-libraries-committee/issues/336))
=====================================
libraries/base/src/Data/Array/Byte.hs
=====================================
@@ -27,7 +27,7 @@ import qualified GHC.Internal.Data.Foldable as F
import GHC.Internal.Data.Maybe (fromMaybe)
import Data.Semigroup
import GHC.Internal.Exts
-import GHC.Num.Integer (Integer(..))
+import GHC.Internal.Bignum.Integer (Integer(..))
import GHC.Internal.Show (intToDigit)
import GHC.Internal.ST (ST(..), runST)
import GHC.Internal.Word (Word8(..))
=====================================
libraries/base/src/GHC/Num/BigNat.hs deleted
=====================================
@@ -1,6 +0,0 @@
-module GHC.Num.BigNat
- ( module GHC.Internal.Bignum.BigNat
- )
-where
-
-import GHC.Internal.Bignum.BigNat
=====================================
libraries/base/src/GHC/Num/Integer.hs deleted
=====================================
@@ -1,6 +0,0 @@
-module GHC.Num.Integer
- ( module GHC.Internal.Bignum.Integer
- )
-where
-
-import GHC.Internal.Bignum.Integer
=====================================
libraries/base/src/GHC/Num/Natural.hs deleted
=====================================
@@ -1,6 +0,0 @@
-module GHC.Num.Natural
- ( module GHC.Internal.Bignum.Natural
- )
-where
-
-import GHC.Internal.Bignum.Natural
=====================================
libraries/base/src/System/CPUTime/Utils.hs
=====================================
@@ -8,7 +8,7 @@ module System.CPUTime.Utils
) where
import GHC.Internal.Foreign.C.Types
-import GHC.Num.Integer (Integer)
+import GHC.Internal.Bignum.Integer (Integer)
import GHC.Internal.Real (fromIntegral)
cClockToInteger :: CClock -> Integer
=====================================
libraries/ghc-bignum/ghc-bignum.cabal
=====================================
@@ -10,10 +10,8 @@ bug-reports: https://gitlab.haskell.org/ghc/ghc/issues/new
category: Numeric, Algebra, GHC
build-type: Simple
description:
- This package used to provide the low-level implementation of the standard
+ This package provides the low-level implementation of the standard
'BigNat', 'Natural' and 'Integer' types.
- Use `base:GHC.Num.{Integer,Natural,BigNat}` instead or other modules from
- `ghc-internal`.
extra-source-files:
changelog.md
@@ -40,13 +38,6 @@ library
, GHC.Internal.Bignum.Backend as GHC.Num.Backend
, GHC.Internal.Bignum.Backend.Selected as GHC.Num.Backend.Selected
, GHC.Internal.Bignum.Backend.Native as GHC.Num.Backend.Native
- -- reexport from base
- -- We can't reexport these modules from ghc-internal otherwise we get
- -- ambiguity between:
- -- ghc-bignum:GHC.Num.X
- -- base:GHC.Num.X
- -- we should probably just deprecate ghc-bignum and encourage users to use
- -- exports from base instead.
- , GHC.Num.BigNat
- , GHC.Num.Natural
- , GHC.Num.Integer
+ , GHC.Internal.Bignum.BigNat as GHC.Num.BigNat
+ , GHC.Internal.Bignum.Natural as GHC.Num.Natural
+ , GHC.Internal.Bignum.Integer as GHC.Num.Integer
=====================================
libraries/ghc-experimental/src/GHC/TypeNats/Experimental.hs
=====================================
@@ -12,7 +12,7 @@ module GHC.TypeNats.Experimental (
) where
import GHC.Internal.TypeNats
-import GHC.Num.Natural (naturalLog2)
+import GHC.Internal.Bignum.Natural (naturalLog2)
plusSNat :: SNat n -> SNat m -> SNat (n + m)
plusSNat (UnsafeSNat n) (UnsafeSNat m) = UnsafeSNat (n + m)
=====================================
testsuite/tests/interface-stability/base-exports.stdout
=====================================
@@ -8550,340 +8550,6 @@ module GHC.Num where
quotRemInteger :: Integer -> Integer -> (# Integer, Integer #)
subtract :: forall a. Num a => a -> a -> a
-module GHC.Num.BigNat where
- -- Safety: None
- type BigNat :: *
- data BigNat = BN# {unBigNat :: BigNat#}
- type BigNat# :: GHC.Internal.Types.UnliftedType
- type BigNat# = GHC.Internal.Bignum.WordArray.WordArray#
- bigNatAdd :: BigNat# -> BigNat# -> BigNat#
- bigNatAddWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatAddWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatAnd :: BigNat# -> BigNat# -> BigNat#
- bigNatAndInt# :: BigNat# -> GHC.Internal.Prim.Int# -> BigNat#
- bigNatAndNot :: BigNat# -> BigNat# -> BigNat#
- bigNatAndNotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatAndWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatBit :: GHC.Internal.Types.Word -> BigNat#
- bigNatBit# :: GHC.Internal.Prim.Word# -> BigNat#
- bigNatCheck :: BigNat# -> GHC.Internal.Types.Bool
- bigNatCheck# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatClearBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatCompare :: BigNat# -> BigNat# -> GHC.Internal.Types.Ordering
- bigNatCompareWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Ordering
- bigNatCompareWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Types.Ordering
- bigNatComplementBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatCtz :: BigNat# -> GHC.Internal.Types.Word
- bigNatCtz# :: BigNat# -> GHC.Internal.Prim.Word#
- bigNatCtzWord :: BigNat# -> GHC.Internal.Types.Word
- bigNatCtzWord# :: BigNat# -> GHC.Internal.Prim.Word#
- bigNatEncodeDouble# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
- bigNatEq :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatEq# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatEqWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatFromAbsInt# :: GHC.Internal.Prim.Int# -> BigNat#
- bigNatFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromAddrBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromAddrLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromByteArrayBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromByteArrayLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromWord :: GHC.Internal.Types.Word -> BigNat#
- bigNatFromWord# :: GHC.Internal.Prim.Word# -> BigNat#
- bigNatFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatFromWord64# :: GHC.Internal.Prim.Word64# -> BigNat#
- bigNatFromWordArray :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat
- bigNatFromWordArray# :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatFromWordList :: [GHC.Internal.Types.Word] -> BigNat#
- bigNatFromWordList# :: [GHC.Internal.Types.Word] -> GHC.Internal.Bignum.WordArray.WordArray#
- bigNatFromWordListUnsafe :: [GHC.Internal.Types.Word] -> BigNat#
- bigNatGcd :: BigNat# -> BigNat# -> BigNat#
- bigNatGcdWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
- bigNatGe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatGe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatGt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatGt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatGtWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
- bigNatGtWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatIndex :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Types.Word
- bigNatIndex# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word#
- bigNatIsOne :: BigNat# -> GHC.Internal.Types.Bool
- bigNatIsOne# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatIsPowerOf2# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #)
- bigNatIsTwo :: BigNat# -> GHC.Internal.Types.Bool
- bigNatIsTwo# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatIsZero :: BigNat# -> GHC.Internal.Types.Bool
- bigNatIsZero# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatLcm :: BigNat# -> BigNat# -> BigNat#
- bigNatLcmWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatLcmWordWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatLe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatLe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatLeWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
- bigNatLeWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatLog2 :: BigNat# -> GHC.Internal.Types.Word
- bigNatLog2# :: BigNat# -> GHC.Internal.Prim.Word#
- bigNatLogBase :: BigNat# -> BigNat# -> GHC.Internal.Types.Word
- bigNatLogBase# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word#
- bigNatLogBaseWord :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word
- bigNatLogBaseWord# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word#
- bigNatLt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatLt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatMul :: BigNat# -> BigNat# -> BigNat#
- bigNatMulWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatMulWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatNe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatNe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatOne :: BigNat
- bigNatOne# :: (# #) -> BigNat#
- bigNatOr :: BigNat# -> BigNat# -> BigNat#
- bigNatOrWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatPopCount :: BigNat# -> GHC.Internal.Types.Word
- bigNatPopCount# :: BigNat# -> GHC.Internal.Prim.Word#
- bigNatPowMod :: BigNat# -> BigNat# -> BigNat# -> BigNat#
- bigNatPowModWord# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
- bigNatQuot :: BigNat# -> BigNat# -> BigNat#
- bigNatQuotRem# :: BigNat# -> BigNat# -> (# BigNat#, BigNat# #)
- bigNatQuotRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# BigNat#, GHC.Internal.Prim.Word# #)
- bigNatQuotWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatQuotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatRem :: BigNat# -> BigNat# -> BigNat#
- bigNatRemWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word
- bigNatRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
- bigNatSetBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatShiftL :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatShiftL# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatShiftR :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatShiftR# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatShiftRNeg# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatSize :: BigNat# -> GHC.Internal.Types.Word
- bigNatSize# :: BigNat# -> GHC.Internal.Prim.Int#
- bigNatSizeInBase :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word
- bigNatSizeInBase# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word#
- bigNatSqr :: BigNat# -> BigNat#
- bigNatSub :: BigNat# -> BigNat# -> (# (# #) | BigNat# #)
- bigNatSubUnsafe :: BigNat# -> BigNat# -> BigNat#
- bigNatSubWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# (# #) | BigNat# #)
- bigNatSubWordUnsafe :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatSubWordUnsafe# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatTestBit :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
- bigNatTestBit# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatToAddr :: BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
- bigNatToAddr# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToAddrBE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToAddrLE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToInt :: BigNat# -> GHC.Internal.Types.Int
- bigNatToInt# :: BigNat# -> GHC.Internal.Prim.Int#
- bigNatToMutableByteArray# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToMutableByteArrayBE# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToMutableByteArrayLE# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToWord :: BigNat# -> GHC.Internal.Types.Word
- bigNatToWord# :: BigNat# -> GHC.Internal.Prim.Word#
- bigNatToWord64# :: BigNat# -> GHC.Internal.Prim.Word64#
- bigNatToWordList :: BigNat# -> [GHC.Internal.Types.Word]
- bigNatToWordMaybe# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #)
- bigNatXor :: BigNat# -> BigNat# -> BigNat#
- bigNatXorWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatZero :: BigNat
- bigNatZero# :: (# #) -> BigNat#
- gcdInt :: GHC.Internal.Types.Int -> GHC.Internal.Types.Int -> GHC.Internal.Types.Int
- gcdInt# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int#
- gcdWord :: GHC.Internal.Types.Word -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word
- gcdWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
- powModWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
- raiseDivZero_BigNat :: (# #) -> BigNat#
-
-module GHC.Num.Integer where
- -- Safety: None
- type Integer :: *
- data Integer = IS GHC.Internal.Prim.Int# | IP GHC.Internal.Prim.ByteArray# | IN GHC.Internal.Prim.ByteArray#
- integerAbs :: Integer -> Integer
- integerAdd :: Integer -> Integer -> Integer
- integerAnd :: Integer -> Integer -> Integer
- integerBit :: GHC.Internal.Types.Word -> Integer
- integerBit# :: GHC.Internal.Prim.Word# -> Integer
- integerCheck :: Integer -> GHC.Internal.Types.Bool
- integerCheck# :: Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerCompare :: Integer -> Integer -> GHC.Internal.Types.Ordering
- integerComplement :: Integer -> Integer
- integerDecodeDouble# :: GHC.Internal.Prim.Double# -> (# Integer, GHC.Internal.Prim.Int# #)
- integerDiv :: Integer -> Integer -> Integer
- integerDivMod :: Integer -> Integer -> (Integer, Integer)
- integerDivMod# :: Integer -> Integer -> (# Integer, Integer #)
- integerEncodeDouble :: Integer -> GHC.Internal.Types.Int -> GHC.Internal.Types.Double
- integerEncodeDouble# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
- integerEncodeFloat# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float#
- integerEq :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerEq# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Integer
- integerFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Integer #)
- integerFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer
- integerFromBigNatNeg# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer
- integerFromBigNatSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Bignum.BigNat.BigNat# -> Integer
- integerFromByteArray :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> Integer
- integerFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Integer #)
- integerFromInt :: GHC.Internal.Types.Int -> Integer
- integerFromInt# :: GHC.Internal.Prim.Int# -> Integer
- integerFromInt64# :: GHC.Internal.Prim.Int64# -> Integer
- integerFromNatural :: GHC.Internal.Bignum.Natural.Natural -> Integer
- integerFromWord :: GHC.Internal.Types.Word -> Integer
- integerFromWord# :: GHC.Internal.Prim.Word# -> Integer
- integerFromWord64# :: GHC.Internal.Prim.Word64# -> Integer
- integerFromWordList :: GHC.Internal.Types.Bool -> [GHC.Internal.Types.Word] -> Integer
- integerFromWordNeg# :: GHC.Internal.Prim.Word# -> Integer
- integerFromWordSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# -> Integer
- integerGcd :: Integer -> Integer -> Integer
- integerGcde :: Integer -> Integer -> (Integer, Integer, Integer)
- integerGcde# :: Integer -> Integer -> (# Integer, Integer, Integer #)
- integerGe :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerGe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerGt :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerGt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerIsNegative :: Integer -> GHC.Internal.Types.Bool
- integerIsNegative# :: Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerIsOne :: Integer -> GHC.Internal.Types.Bool
- integerIsPowerOf2# :: Integer -> (# (# #) | GHC.Internal.Prim.Word# #)
- integerIsZero :: Integer -> GHC.Internal.Types.Bool
- integerLcm :: Integer -> Integer -> Integer
- integerLe :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerLe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerLog2 :: Integer -> GHC.Internal.Types.Word
- integerLog2# :: Integer -> GHC.Internal.Prim.Word#
- integerLogBase :: Integer -> Integer -> GHC.Internal.Types.Word
- integerLogBase# :: Integer -> Integer -> GHC.Internal.Prim.Word#
- integerLogBaseWord :: GHC.Internal.Types.Word -> Integer -> GHC.Internal.Types.Word
- integerLogBaseWord# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word#
- integerLt :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerLt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerMod :: Integer -> Integer -> Integer
- integerMul :: Integer -> Integer -> Integer
- integerNe :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerNe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerNegate :: Integer -> Integer
- integerOne :: Integer
- integerOr :: Integer -> Integer -> Integer
- integerPopCount# :: Integer -> GHC.Internal.Prim.Int#
- integerPowMod# :: Integer -> Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #)
- integerQuot :: Integer -> Integer -> Integer
- integerQuotRem :: Integer -> Integer -> (Integer, Integer)
- integerQuotRem# :: Integer -> Integer -> (# Integer, Integer #)
- integerRecipMod# :: Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #)
- integerRem :: Integer -> Integer -> Integer
- integerShiftL :: Integer -> GHC.Internal.Types.Word -> Integer
- integerShiftL# :: Integer -> GHC.Internal.Prim.Word# -> Integer
- integerShiftR :: Integer -> GHC.Internal.Types.Word -> Integer
- integerShiftR# :: Integer -> GHC.Internal.Prim.Word# -> Integer
- integerSignum :: Integer -> Integer
- integerSignum# :: Integer -> GHC.Internal.Prim.Int#
- integerSizeInBase# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word#
- integerSqr :: Integer -> Integer
- integerSub :: Integer -> Integer -> Integer
- integerTestBit :: Integer -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
- integerTestBit# :: Integer -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- integerToAddr :: Integer -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
- integerToAddr# :: forall s. Integer -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- integerToBigNatClamp# :: Integer -> GHC.Internal.Bignum.BigNat.BigNat#
- integerToBigNatSign# :: Integer -> (# GHC.Internal.Prim.Int#, GHC.Internal.Bignum.BigNat.BigNat# #)
- integerToInt :: Integer -> GHC.Internal.Types.Int
- integerToInt# :: Integer -> GHC.Internal.Prim.Int#
- integerToInt64# :: Integer -> GHC.Internal.Prim.Int64#
- integerToMutableByteArray :: Integer -> GHC.Internal.Prim.MutableByteArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
- integerToMutableByteArray# :: forall s. Integer -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- integerToNatural :: Integer -> GHC.Internal.Bignum.Natural.Natural
- integerToNaturalClamp :: Integer -> GHC.Internal.Bignum.Natural.Natural
- integerToNaturalThrow :: Integer -> GHC.Internal.Bignum.Natural.Natural
- integerToWord :: Integer -> GHC.Internal.Types.Word
- integerToWord# :: Integer -> GHC.Internal.Prim.Word#
- integerToWord64# :: Integer -> GHC.Internal.Prim.Word64#
- integerXor :: Integer -> Integer -> Integer
- integerZero :: Integer
-
-module GHC.Num.Natural where
- -- Safety: None
- type Natural :: *
- data Natural = NS GHC.Internal.Prim.Word# | NB GHC.Internal.Prim.ByteArray#
- naturalAdd :: Natural -> Natural -> Natural
- naturalAnd :: Natural -> Natural -> Natural
- naturalAndNot :: Natural -> Natural -> Natural
- naturalBit :: GHC.Internal.Types.Word -> Natural
- naturalBit# :: GHC.Internal.Prim.Word# -> Natural
- naturalCheck :: Natural -> GHC.Internal.Types.Bool
- naturalCheck# :: Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalClearBit :: Natural -> GHC.Internal.Types.Word -> Natural
- naturalClearBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
- naturalCompare :: Natural -> Natural -> GHC.Internal.Types.Ordering
- naturalComplementBit :: Natural -> GHC.Internal.Types.Word -> Natural
- naturalComplementBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
- naturalEncodeDouble# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
- naturalEncodeFloat# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float#
- naturalEq :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalEq# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Natural
- naturalFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Natural #)
- naturalFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Natural
- naturalFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Natural #)
- naturalFromWord :: GHC.Internal.Types.Word -> Natural
- naturalFromWord# :: GHC.Internal.Prim.Word# -> Natural
- naturalFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> Natural
- naturalFromWordList :: [GHC.Internal.Types.Word] -> Natural
- naturalGcd :: Natural -> Natural -> Natural
- naturalGe :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalGe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalGt :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalGt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalIsOne :: Natural -> GHC.Internal.Types.Bool
- naturalIsPowerOf2# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #)
- naturalIsZero :: Natural -> GHC.Internal.Types.Bool
- naturalLcm :: Natural -> Natural -> Natural
- naturalLe :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalLe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalLog2 :: Natural -> GHC.Internal.Types.Word
- naturalLog2# :: Natural -> GHC.Internal.Prim.Word#
- naturalLogBase :: Natural -> Natural -> GHC.Internal.Types.Word
- naturalLogBase# :: Natural -> Natural -> GHC.Internal.Prim.Word#
- naturalLogBaseWord :: GHC.Internal.Types.Word -> Natural -> GHC.Internal.Types.Word
- naturalLogBaseWord# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word#
- naturalLt :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalLt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalMul :: Natural -> Natural -> Natural
- naturalNe :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalNe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalNegate :: Natural -> Natural
- naturalOne :: Natural
- naturalOr :: Natural -> Natural -> Natural
- naturalPopCount :: Natural -> GHC.Internal.Types.Word
- naturalPopCount# :: Natural -> GHC.Internal.Prim.Word#
- naturalPowMod :: Natural -> Natural -> Natural -> Natural
- naturalQuot :: Natural -> Natural -> Natural
- naturalQuotRem :: Natural -> Natural -> (Natural, Natural)
- naturalQuotRem# :: Natural -> Natural -> (# Natural, Natural #)
- naturalRem :: Natural -> Natural -> Natural
- naturalSetBit :: Natural -> GHC.Internal.Types.Word -> Natural
- naturalSetBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
- naturalShiftL :: Natural -> GHC.Internal.Types.Word -> Natural
- naturalShiftL# :: Natural -> GHC.Internal.Prim.Word# -> Natural
- naturalShiftR :: Natural -> GHC.Internal.Types.Word -> Natural
- naturalShiftR# :: Natural -> GHC.Internal.Prim.Word# -> Natural
- naturalSignum :: Natural -> Natural
- naturalSizeInBase# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word#
- naturalSqr :: Natural -> Natural
- naturalSub :: Natural -> Natural -> (# (# #) | Natural #)
- naturalSubThrow :: Natural -> Natural -> Natural
- naturalSubUnsafe :: Natural -> Natural -> Natural
- naturalTestBit :: Natural -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
- naturalTestBit# :: Natural -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- naturalToAddr :: Natural -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
- naturalToAddr# :: forall s. Natural -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- naturalToBigNat# :: Natural -> GHC.Internal.Bignum.BigNat.BigNat#
- naturalToMutableByteArray# :: forall s. Natural -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- naturalToWord :: Natural -> GHC.Internal.Types.Word
- naturalToWord# :: Natural -> GHC.Internal.Prim.Word#
- naturalToWordClamp :: Natural -> GHC.Internal.Types.Word
- naturalToWordClamp# :: Natural -> GHC.Internal.Prim.Word#
- naturalToWordMaybe# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #)
- naturalXor :: Natural -> Natural -> Natural
- naturalZero :: Natural
-
module GHC.OldList where
-- Safety: Safe
(!!) :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> GHC.Internal.Types.Int -> a
=====================================
testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
=====================================
@@ -11596,340 +11596,6 @@ module GHC.Num where
quotRemInteger :: Integer -> Integer -> (# Integer, Integer #)
subtract :: forall a. Num a => a -> a -> a
-module GHC.Num.BigNat where
- -- Safety: None
- type BigNat :: *
- data BigNat = BN# {unBigNat :: BigNat#}
- type BigNat# :: GHC.Internal.Types.UnliftedType
- type BigNat# = GHC.Internal.Bignum.WordArray.WordArray#
- bigNatAdd :: BigNat# -> BigNat# -> BigNat#
- bigNatAddWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatAddWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatAnd :: BigNat# -> BigNat# -> BigNat#
- bigNatAndInt# :: BigNat# -> GHC.Internal.Prim.Int# -> BigNat#
- bigNatAndNot :: BigNat# -> BigNat# -> BigNat#
- bigNatAndNotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatAndWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatBit :: GHC.Internal.Types.Word -> BigNat#
- bigNatBit# :: GHC.Internal.Prim.Word# -> BigNat#
- bigNatCheck :: BigNat# -> GHC.Internal.Types.Bool
- bigNatCheck# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatClearBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatCompare :: BigNat# -> BigNat# -> GHC.Internal.Types.Ordering
- bigNatCompareWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Ordering
- bigNatCompareWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Types.Ordering
- bigNatComplementBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatCtz :: BigNat# -> GHC.Internal.Types.Word
- bigNatCtz# :: BigNat# -> GHC.Internal.Prim.Word#
- bigNatCtzWord :: BigNat# -> GHC.Internal.Types.Word
- bigNatCtzWord# :: BigNat# -> GHC.Internal.Prim.Word#
- bigNatEncodeDouble# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
- bigNatEq :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatEq# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatEqWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatFromAbsInt# :: GHC.Internal.Prim.Int# -> BigNat#
- bigNatFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromAddrBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromAddrLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromByteArrayBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromByteArrayLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromWord :: GHC.Internal.Types.Word -> BigNat#
- bigNatFromWord# :: GHC.Internal.Prim.Word# -> BigNat#
- bigNatFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatFromWord64# :: GHC.Internal.Prim.Word64# -> BigNat#
- bigNatFromWordArray :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat
- bigNatFromWordArray# :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatFromWordList :: [GHC.Internal.Types.Word] -> BigNat#
- bigNatFromWordList# :: [GHC.Internal.Types.Word] -> GHC.Internal.Bignum.WordArray.WordArray#
- bigNatFromWordListUnsafe :: [GHC.Internal.Types.Word] -> BigNat#
- bigNatGcd :: BigNat# -> BigNat# -> BigNat#
- bigNatGcdWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
- bigNatGe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatGe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatGt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatGt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatGtWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
- bigNatGtWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatIndex :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Types.Word
- bigNatIndex# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word#
- bigNatIsOne :: BigNat# -> GHC.Internal.Types.Bool
- bigNatIsOne# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatIsPowerOf2# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #)
- bigNatIsTwo :: BigNat# -> GHC.Internal.Types.Bool
- bigNatIsTwo# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatIsZero :: BigNat# -> GHC.Internal.Types.Bool
- bigNatIsZero# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatLcm :: BigNat# -> BigNat# -> BigNat#
- bigNatLcmWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatLcmWordWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatLe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatLe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatLeWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
- bigNatLeWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatLog2 :: BigNat# -> GHC.Internal.Types.Word
- bigNatLog2# :: BigNat# -> GHC.Internal.Prim.Word#
- bigNatLogBase :: BigNat# -> BigNat# -> GHC.Internal.Types.Word
- bigNatLogBase# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word#
- bigNatLogBaseWord :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word
- bigNatLogBaseWord# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word#
- bigNatLt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatLt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatMul :: BigNat# -> BigNat# -> BigNat#
- bigNatMulWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatMulWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatNe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatNe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatOne :: BigNat
- bigNatOne# :: (# #) -> BigNat#
- bigNatOr :: BigNat# -> BigNat# -> BigNat#
- bigNatOrWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatPopCount :: BigNat# -> GHC.Internal.Types.Word
- bigNatPopCount# :: BigNat# -> GHC.Internal.Prim.Word#
- bigNatPowMod :: BigNat# -> BigNat# -> BigNat# -> BigNat#
- bigNatPowModWord# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
- bigNatQuot :: BigNat# -> BigNat# -> BigNat#
- bigNatQuotRem# :: BigNat# -> BigNat# -> (# BigNat#, BigNat# #)
- bigNatQuotRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# BigNat#, GHC.Internal.Prim.Word# #)
- bigNatQuotWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatQuotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatRem :: BigNat# -> BigNat# -> BigNat#
- bigNatRemWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word
- bigNatRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
- bigNatSetBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatShiftL :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatShiftL# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatShiftR :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatShiftR# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatShiftRNeg# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatSize :: BigNat# -> GHC.Internal.Types.Word
- bigNatSize# :: BigNat# -> GHC.Internal.Prim.Int#
- bigNatSizeInBase :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word
- bigNatSizeInBase# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word#
- bigNatSqr :: BigNat# -> BigNat#
- bigNatSub :: BigNat# -> BigNat# -> (# (# #) | BigNat# #)
- bigNatSubUnsafe :: BigNat# -> BigNat# -> BigNat#
- bigNatSubWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# (# #) | BigNat# #)
- bigNatSubWordUnsafe :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatSubWordUnsafe# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatTestBit :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
- bigNatTestBit# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatToAddr :: BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
- bigNatToAddr# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToAddrBE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToAddrLE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToInt :: BigNat# -> GHC.Internal.Types.Int
- bigNatToInt# :: BigNat# -> GHC.Internal.Prim.Int#
- bigNatToMutableByteArray# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToMutableByteArrayBE# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToMutableByteArrayLE# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToWord :: BigNat# -> GHC.Internal.Types.Word
- bigNatToWord# :: BigNat# -> GHC.Internal.Prim.Word#
- bigNatToWord64# :: BigNat# -> GHC.Internal.Prim.Word64#
- bigNatToWordList :: BigNat# -> [GHC.Internal.Types.Word]
- bigNatToWordMaybe# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #)
- bigNatXor :: BigNat# -> BigNat# -> BigNat#
- bigNatXorWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatZero :: BigNat
- bigNatZero# :: (# #) -> BigNat#
- gcdInt :: GHC.Internal.Types.Int -> GHC.Internal.Types.Int -> GHC.Internal.Types.Int
- gcdInt# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int#
- gcdWord :: GHC.Internal.Types.Word -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word
- gcdWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
- powModWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
- raiseDivZero_BigNat :: (# #) -> BigNat#
-
-module GHC.Num.Integer where
- -- Safety: None
- type Integer :: *
- data Integer = IS GHC.Internal.Prim.Int# | IP GHC.Internal.Prim.ByteArray# | IN GHC.Internal.Prim.ByteArray#
- integerAbs :: Integer -> Integer
- integerAdd :: Integer -> Integer -> Integer
- integerAnd :: Integer -> Integer -> Integer
- integerBit :: GHC.Internal.Types.Word -> Integer
- integerBit# :: GHC.Internal.Prim.Word# -> Integer
- integerCheck :: Integer -> GHC.Internal.Types.Bool
- integerCheck# :: Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerCompare :: Integer -> Integer -> GHC.Internal.Types.Ordering
- integerComplement :: Integer -> Integer
- integerDecodeDouble# :: GHC.Internal.Prim.Double# -> (# Integer, GHC.Internal.Prim.Int# #)
- integerDiv :: Integer -> Integer -> Integer
- integerDivMod :: Integer -> Integer -> (Integer, Integer)
- integerDivMod# :: Integer -> Integer -> (# Integer, Integer #)
- integerEncodeDouble :: Integer -> GHC.Internal.Types.Int -> GHC.Internal.Types.Double
- integerEncodeDouble# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
- integerEncodeFloat# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float#
- integerEq :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerEq# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Integer
- integerFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Integer #)
- integerFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer
- integerFromBigNatNeg# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer
- integerFromBigNatSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Bignum.BigNat.BigNat# -> Integer
- integerFromByteArray :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> Integer
- integerFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Integer #)
- integerFromInt :: GHC.Internal.Types.Int -> Integer
- integerFromInt# :: GHC.Internal.Prim.Int# -> Integer
- integerFromInt64# :: GHC.Internal.Prim.Int64# -> Integer
- integerFromNatural :: GHC.Internal.Bignum.Natural.Natural -> Integer
- integerFromWord :: GHC.Internal.Types.Word -> Integer
- integerFromWord# :: GHC.Internal.Prim.Word# -> Integer
- integerFromWord64# :: GHC.Internal.Prim.Word64# -> Integer
- integerFromWordList :: GHC.Internal.Types.Bool -> [GHC.Internal.Types.Word] -> Integer
- integerFromWordNeg# :: GHC.Internal.Prim.Word# -> Integer
- integerFromWordSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# -> Integer
- integerGcd :: Integer -> Integer -> Integer
- integerGcde :: Integer -> Integer -> (Integer, Integer, Integer)
- integerGcde# :: Integer -> Integer -> (# Integer, Integer, Integer #)
- integerGe :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerGe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerGt :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerGt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerIsNegative :: Integer -> GHC.Internal.Types.Bool
- integerIsNegative# :: Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerIsOne :: Integer -> GHC.Internal.Types.Bool
- integerIsPowerOf2# :: Integer -> (# (# #) | GHC.Internal.Prim.Word# #)
- integerIsZero :: Integer -> GHC.Internal.Types.Bool
- integerLcm :: Integer -> Integer -> Integer
- integerLe :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerLe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerLog2 :: Integer -> GHC.Internal.Types.Word
- integerLog2# :: Integer -> GHC.Internal.Prim.Word#
- integerLogBase :: Integer -> Integer -> GHC.Internal.Types.Word
- integerLogBase# :: Integer -> Integer -> GHC.Internal.Prim.Word#
- integerLogBaseWord :: GHC.Internal.Types.Word -> Integer -> GHC.Internal.Types.Word
- integerLogBaseWord# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word#
- integerLt :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerLt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerMod :: Integer -> Integer -> Integer
- integerMul :: Integer -> Integer -> Integer
- integerNe :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerNe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerNegate :: Integer -> Integer
- integerOne :: Integer
- integerOr :: Integer -> Integer -> Integer
- integerPopCount# :: Integer -> GHC.Internal.Prim.Int#
- integerPowMod# :: Integer -> Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #)
- integerQuot :: Integer -> Integer -> Integer
- integerQuotRem :: Integer -> Integer -> (Integer, Integer)
- integerQuotRem# :: Integer -> Integer -> (# Integer, Integer #)
- integerRecipMod# :: Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #)
- integerRem :: Integer -> Integer -> Integer
- integerShiftL :: Integer -> GHC.Internal.Types.Word -> Integer
- integerShiftL# :: Integer -> GHC.Internal.Prim.Word# -> Integer
- integerShiftR :: Integer -> GHC.Internal.Types.Word -> Integer
- integerShiftR# :: Integer -> GHC.Internal.Prim.Word# -> Integer
- integerSignum :: Integer -> Integer
- integerSignum# :: Integer -> GHC.Internal.Prim.Int#
- integerSizeInBase# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word#
- integerSqr :: Integer -> Integer
- integerSub :: Integer -> Integer -> Integer
- integerTestBit :: Integer -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
- integerTestBit# :: Integer -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- integerToAddr :: Integer -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
- integerToAddr# :: forall s. Integer -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- integerToBigNatClamp# :: Integer -> GHC.Internal.Bignum.BigNat.BigNat#
- integerToBigNatSign# :: Integer -> (# GHC.Internal.Prim.Int#, GHC.Internal.Bignum.BigNat.BigNat# #)
- integerToInt :: Integer -> GHC.Internal.Types.Int
- integerToInt# :: Integer -> GHC.Internal.Prim.Int#
- integerToInt64# :: Integer -> GHC.Internal.Prim.Int64#
- integerToMutableByteArray :: Integer -> GHC.Internal.Prim.MutableByteArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
- integerToMutableByteArray# :: forall s. Integer -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- integerToNatural :: Integer -> GHC.Internal.Bignum.Natural.Natural
- integerToNaturalClamp :: Integer -> GHC.Internal.Bignum.Natural.Natural
- integerToNaturalThrow :: Integer -> GHC.Internal.Bignum.Natural.Natural
- integerToWord :: Integer -> GHC.Internal.Types.Word
- integerToWord# :: Integer -> GHC.Internal.Prim.Word#
- integerToWord64# :: Integer -> GHC.Internal.Prim.Word64#
- integerXor :: Integer -> Integer -> Integer
- integerZero :: Integer
-
-module GHC.Num.Natural where
- -- Safety: None
- type Natural :: *
- data Natural = NS GHC.Internal.Prim.Word# | NB GHC.Internal.Prim.ByteArray#
- naturalAdd :: Natural -> Natural -> Natural
- naturalAnd :: Natural -> Natural -> Natural
- naturalAndNot :: Natural -> Natural -> Natural
- naturalBit :: GHC.Internal.Types.Word -> Natural
- naturalBit# :: GHC.Internal.Prim.Word# -> Natural
- naturalCheck :: Natural -> GHC.Internal.Types.Bool
- naturalCheck# :: Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalClearBit :: Natural -> GHC.Internal.Types.Word -> Natural
- naturalClearBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
- naturalCompare :: Natural -> Natural -> GHC.Internal.Types.Ordering
- naturalComplementBit :: Natural -> GHC.Internal.Types.Word -> Natural
- naturalComplementBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
- naturalEncodeDouble# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
- naturalEncodeFloat# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float#
- naturalEq :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalEq# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Natural
- naturalFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Natural #)
- naturalFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Natural
- naturalFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Natural #)
- naturalFromWord :: GHC.Internal.Types.Word -> Natural
- naturalFromWord# :: GHC.Internal.Prim.Word# -> Natural
- naturalFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> Natural
- naturalFromWordList :: [GHC.Internal.Types.Word] -> Natural
- naturalGcd :: Natural -> Natural -> Natural
- naturalGe :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalGe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalGt :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalGt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalIsOne :: Natural -> GHC.Internal.Types.Bool
- naturalIsPowerOf2# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #)
- naturalIsZero :: Natural -> GHC.Internal.Types.Bool
- naturalLcm :: Natural -> Natural -> Natural
- naturalLe :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalLe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalLog2 :: Natural -> GHC.Internal.Types.Word
- naturalLog2# :: Natural -> GHC.Internal.Prim.Word#
- naturalLogBase :: Natural -> Natural -> GHC.Internal.Types.Word
- naturalLogBase# :: Natural -> Natural -> GHC.Internal.Prim.Word#
- naturalLogBaseWord :: GHC.Internal.Types.Word -> Natural -> GHC.Internal.Types.Word
- naturalLogBaseWord# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word#
- naturalLt :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalLt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalMul :: Natural -> Natural -> Natural
- naturalNe :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalNe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalNegate :: Natural -> Natural
- naturalOne :: Natural
- naturalOr :: Natural -> Natural -> Natural
- naturalPopCount :: Natural -> GHC.Internal.Types.Word
- naturalPopCount# :: Natural -> GHC.Internal.Prim.Word#
- naturalPowMod :: Natural -> Natural -> Natural -> Natural
- naturalQuot :: Natural -> Natural -> Natural
- naturalQuotRem :: Natural -> Natural -> (Natural, Natural)
- naturalQuotRem# :: Natural -> Natural -> (# Natural, Natural #)
- naturalRem :: Natural -> Natural -> Natural
- naturalSetBit :: Natural -> GHC.Internal.Types.Word -> Natural
- naturalSetBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
- naturalShiftL :: Natural -> GHC.Internal.Types.Word -> Natural
- naturalShiftL# :: Natural -> GHC.Internal.Prim.Word# -> Natural
- naturalShiftR :: Natural -> GHC.Internal.Types.Word -> Natural
- naturalShiftR# :: Natural -> GHC.Internal.Prim.Word# -> Natural
- naturalSignum :: Natural -> Natural
- naturalSizeInBase# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word#
- naturalSqr :: Natural -> Natural
- naturalSub :: Natural -> Natural -> (# (# #) | Natural #)
- naturalSubThrow :: Natural -> Natural -> Natural
- naturalSubUnsafe :: Natural -> Natural -> Natural
- naturalTestBit :: Natural -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
- naturalTestBit# :: Natural -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- naturalToAddr :: Natural -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
- naturalToAddr# :: forall s. Natural -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- naturalToBigNat# :: Natural -> GHC.Internal.Bignum.BigNat.BigNat#
- naturalToMutableByteArray# :: forall s. Natural -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- naturalToWord :: Natural -> GHC.Internal.Types.Word
- naturalToWord# :: Natural -> GHC.Internal.Prim.Word#
- naturalToWordClamp :: Natural -> GHC.Internal.Types.Word
- naturalToWordClamp# :: Natural -> GHC.Internal.Prim.Word#
- naturalToWordMaybe# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #)
- naturalXor :: Natural -> Natural -> Natural
- naturalZero :: Natural
-
module GHC.OldList where
-- Safety: Safe
(!!) :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> GHC.Internal.Types.Int -> a
=====================================
testsuite/tests/interface-stability/base-exports.stdout-mingw32
=====================================
@@ -8768,340 +8768,6 @@ module GHC.Num where
quotRemInteger :: Integer -> Integer -> (# Integer, Integer #)
subtract :: forall a. Num a => a -> a -> a
-module GHC.Num.BigNat where
- -- Safety: None
- type BigNat :: *
- data BigNat = BN# {unBigNat :: BigNat#}
- type BigNat# :: GHC.Internal.Types.UnliftedType
- type BigNat# = GHC.Internal.Bignum.WordArray.WordArray#
- bigNatAdd :: BigNat# -> BigNat# -> BigNat#
- bigNatAddWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatAddWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatAnd :: BigNat# -> BigNat# -> BigNat#
- bigNatAndInt# :: BigNat# -> GHC.Internal.Prim.Int# -> BigNat#
- bigNatAndNot :: BigNat# -> BigNat# -> BigNat#
- bigNatAndNotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatAndWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatBit :: GHC.Internal.Types.Word -> BigNat#
- bigNatBit# :: GHC.Internal.Prim.Word# -> BigNat#
- bigNatCheck :: BigNat# -> GHC.Internal.Types.Bool
- bigNatCheck# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatClearBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatCompare :: BigNat# -> BigNat# -> GHC.Internal.Types.Ordering
- bigNatCompareWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Ordering
- bigNatCompareWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Types.Ordering
- bigNatComplementBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatCtz :: BigNat# -> GHC.Internal.Types.Word
- bigNatCtz# :: BigNat# -> GHC.Internal.Prim.Word#
- bigNatCtzWord :: BigNat# -> GHC.Internal.Types.Word
- bigNatCtzWord# :: BigNat# -> GHC.Internal.Prim.Word#
- bigNatEncodeDouble# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
- bigNatEq :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatEq# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatEqWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatFromAbsInt# :: GHC.Internal.Prim.Int# -> BigNat#
- bigNatFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromAddrBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromAddrLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromByteArrayBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromByteArrayLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromWord :: GHC.Internal.Types.Word -> BigNat#
- bigNatFromWord# :: GHC.Internal.Prim.Word# -> BigNat#
- bigNatFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatFromWord64# :: GHC.Internal.Prim.Word64# -> BigNat#
- bigNatFromWordArray :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat
- bigNatFromWordArray# :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatFromWordList :: [GHC.Internal.Types.Word] -> BigNat#
- bigNatFromWordList# :: [GHC.Internal.Types.Word] -> GHC.Internal.Bignum.WordArray.WordArray#
- bigNatFromWordListUnsafe :: [GHC.Internal.Types.Word] -> BigNat#
- bigNatGcd :: BigNat# -> BigNat# -> BigNat#
- bigNatGcdWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
- bigNatGe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatGe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatGt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatGt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatGtWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
- bigNatGtWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatIndex :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Types.Word
- bigNatIndex# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word#
- bigNatIsOne :: BigNat# -> GHC.Internal.Types.Bool
- bigNatIsOne# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatIsPowerOf2# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #)
- bigNatIsTwo :: BigNat# -> GHC.Internal.Types.Bool
- bigNatIsTwo# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatIsZero :: BigNat# -> GHC.Internal.Types.Bool
- bigNatIsZero# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatLcm :: BigNat# -> BigNat# -> BigNat#
- bigNatLcmWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatLcmWordWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatLe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatLe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatLeWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
- bigNatLeWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatLog2 :: BigNat# -> GHC.Internal.Types.Word
- bigNatLog2# :: BigNat# -> GHC.Internal.Prim.Word#
- bigNatLogBase :: BigNat# -> BigNat# -> GHC.Internal.Types.Word
- bigNatLogBase# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word#
- bigNatLogBaseWord :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word
- bigNatLogBaseWord# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word#
- bigNatLt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatLt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatMul :: BigNat# -> BigNat# -> BigNat#
- bigNatMulWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatMulWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatNe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatNe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatOne :: BigNat
- bigNatOne# :: (# #) -> BigNat#
- bigNatOr :: BigNat# -> BigNat# -> BigNat#
- bigNatOrWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatPopCount :: BigNat# -> GHC.Internal.Types.Word
- bigNatPopCount# :: BigNat# -> GHC.Internal.Prim.Word#
- bigNatPowMod :: BigNat# -> BigNat# -> BigNat# -> BigNat#
- bigNatPowModWord# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
- bigNatQuot :: BigNat# -> BigNat# -> BigNat#
- bigNatQuotRem# :: BigNat# -> BigNat# -> (# BigNat#, BigNat# #)
- bigNatQuotRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# BigNat#, GHC.Internal.Prim.Word# #)
- bigNatQuotWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatQuotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatRem :: BigNat# -> BigNat# -> BigNat#
- bigNatRemWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word
- bigNatRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
- bigNatSetBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatShiftL :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatShiftL# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatShiftR :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatShiftR# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatShiftRNeg# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatSize :: BigNat# -> GHC.Internal.Types.Word
- bigNatSize# :: BigNat# -> GHC.Internal.Prim.Int#
- bigNatSizeInBase :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word
- bigNatSizeInBase# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word#
- bigNatSqr :: BigNat# -> BigNat#
- bigNatSub :: BigNat# -> BigNat# -> (# (# #) | BigNat# #)
- bigNatSubUnsafe :: BigNat# -> BigNat# -> BigNat#
- bigNatSubWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# (# #) | BigNat# #)
- bigNatSubWordUnsafe :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatSubWordUnsafe# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatTestBit :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
- bigNatTestBit# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatToAddr :: BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
- bigNatToAddr# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToAddrBE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToAddrLE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToInt :: BigNat# -> GHC.Internal.Types.Int
- bigNatToInt# :: BigNat# -> GHC.Internal.Prim.Int#
- bigNatToMutableByteArray# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToMutableByteArrayBE# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToMutableByteArrayLE# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToWord :: BigNat# -> GHC.Internal.Types.Word
- bigNatToWord# :: BigNat# -> GHC.Internal.Prim.Word#
- bigNatToWord64# :: BigNat# -> GHC.Internal.Prim.Word64#
- bigNatToWordList :: BigNat# -> [GHC.Internal.Types.Word]
- bigNatToWordMaybe# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #)
- bigNatXor :: BigNat# -> BigNat# -> BigNat#
- bigNatXorWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatZero :: BigNat
- bigNatZero# :: (# #) -> BigNat#
- gcdInt :: GHC.Internal.Types.Int -> GHC.Internal.Types.Int -> GHC.Internal.Types.Int
- gcdInt# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int#
- gcdWord :: GHC.Internal.Types.Word -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word
- gcdWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
- powModWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
- raiseDivZero_BigNat :: (# #) -> BigNat#
-
-module GHC.Num.Integer where
- -- Safety: None
- type Integer :: *
- data Integer = IS GHC.Internal.Prim.Int# | IP GHC.Internal.Prim.ByteArray# | IN GHC.Internal.Prim.ByteArray#
- integerAbs :: Integer -> Integer
- integerAdd :: Integer -> Integer -> Integer
- integerAnd :: Integer -> Integer -> Integer
- integerBit :: GHC.Internal.Types.Word -> Integer
- integerBit# :: GHC.Internal.Prim.Word# -> Integer
- integerCheck :: Integer -> GHC.Internal.Types.Bool
- integerCheck# :: Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerCompare :: Integer -> Integer -> GHC.Internal.Types.Ordering
- integerComplement :: Integer -> Integer
- integerDecodeDouble# :: GHC.Internal.Prim.Double# -> (# Integer, GHC.Internal.Prim.Int# #)
- integerDiv :: Integer -> Integer -> Integer
- integerDivMod :: Integer -> Integer -> (Integer, Integer)
- integerDivMod# :: Integer -> Integer -> (# Integer, Integer #)
- integerEncodeDouble :: Integer -> GHC.Internal.Types.Int -> GHC.Internal.Types.Double
- integerEncodeDouble# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
- integerEncodeFloat# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float#
- integerEq :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerEq# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Integer
- integerFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Integer #)
- integerFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer
- integerFromBigNatNeg# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer
- integerFromBigNatSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Bignum.BigNat.BigNat# -> Integer
- integerFromByteArray :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> Integer
- integerFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Integer #)
- integerFromInt :: GHC.Internal.Types.Int -> Integer
- integerFromInt# :: GHC.Internal.Prim.Int# -> Integer
- integerFromInt64# :: GHC.Internal.Prim.Int64# -> Integer
- integerFromNatural :: GHC.Internal.Bignum.Natural.Natural -> Integer
- integerFromWord :: GHC.Internal.Types.Word -> Integer
- integerFromWord# :: GHC.Internal.Prim.Word# -> Integer
- integerFromWord64# :: GHC.Internal.Prim.Word64# -> Integer
- integerFromWordList :: GHC.Internal.Types.Bool -> [GHC.Internal.Types.Word] -> Integer
- integerFromWordNeg# :: GHC.Internal.Prim.Word# -> Integer
- integerFromWordSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# -> Integer
- integerGcd :: Integer -> Integer -> Integer
- integerGcde :: Integer -> Integer -> (Integer, Integer, Integer)
- integerGcde# :: Integer -> Integer -> (# Integer, Integer, Integer #)
- integerGe :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerGe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerGt :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerGt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerIsNegative :: Integer -> GHC.Internal.Types.Bool
- integerIsNegative# :: Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerIsOne :: Integer -> GHC.Internal.Types.Bool
- integerIsPowerOf2# :: Integer -> (# (# #) | GHC.Internal.Prim.Word# #)
- integerIsZero :: Integer -> GHC.Internal.Types.Bool
- integerLcm :: Integer -> Integer -> Integer
- integerLe :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerLe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerLog2 :: Integer -> GHC.Internal.Types.Word
- integerLog2# :: Integer -> GHC.Internal.Prim.Word#
- integerLogBase :: Integer -> Integer -> GHC.Internal.Types.Word
- integerLogBase# :: Integer -> Integer -> GHC.Internal.Prim.Word#
- integerLogBaseWord :: GHC.Internal.Types.Word -> Integer -> GHC.Internal.Types.Word
- integerLogBaseWord# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word#
- integerLt :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerLt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerMod :: Integer -> Integer -> Integer
- integerMul :: Integer -> Integer -> Integer
- integerNe :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerNe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerNegate :: Integer -> Integer
- integerOne :: Integer
- integerOr :: Integer -> Integer -> Integer
- integerPopCount# :: Integer -> GHC.Internal.Prim.Int#
- integerPowMod# :: Integer -> Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #)
- integerQuot :: Integer -> Integer -> Integer
- integerQuotRem :: Integer -> Integer -> (Integer, Integer)
- integerQuotRem# :: Integer -> Integer -> (# Integer, Integer #)
- integerRecipMod# :: Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #)
- integerRem :: Integer -> Integer -> Integer
- integerShiftL :: Integer -> GHC.Internal.Types.Word -> Integer
- integerShiftL# :: Integer -> GHC.Internal.Prim.Word# -> Integer
- integerShiftR :: Integer -> GHC.Internal.Types.Word -> Integer
- integerShiftR# :: Integer -> GHC.Internal.Prim.Word# -> Integer
- integerSignum :: Integer -> Integer
- integerSignum# :: Integer -> GHC.Internal.Prim.Int#
- integerSizeInBase# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word#
- integerSqr :: Integer -> Integer
- integerSub :: Integer -> Integer -> Integer
- integerTestBit :: Integer -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
- integerTestBit# :: Integer -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- integerToAddr :: Integer -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
- integerToAddr# :: forall s. Integer -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- integerToBigNatClamp# :: Integer -> GHC.Internal.Bignum.BigNat.BigNat#
- integerToBigNatSign# :: Integer -> (# GHC.Internal.Prim.Int#, GHC.Internal.Bignum.BigNat.BigNat# #)
- integerToInt :: Integer -> GHC.Internal.Types.Int
- integerToInt# :: Integer -> GHC.Internal.Prim.Int#
- integerToInt64# :: Integer -> GHC.Internal.Prim.Int64#
- integerToMutableByteArray :: Integer -> GHC.Internal.Prim.MutableByteArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
- integerToMutableByteArray# :: forall s. Integer -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- integerToNatural :: Integer -> GHC.Internal.Bignum.Natural.Natural
- integerToNaturalClamp :: Integer -> GHC.Internal.Bignum.Natural.Natural
- integerToNaturalThrow :: Integer -> GHC.Internal.Bignum.Natural.Natural
- integerToWord :: Integer -> GHC.Internal.Types.Word
- integerToWord# :: Integer -> GHC.Internal.Prim.Word#
- integerToWord64# :: Integer -> GHC.Internal.Prim.Word64#
- integerXor :: Integer -> Integer -> Integer
- integerZero :: Integer
-
-module GHC.Num.Natural where
- -- Safety: None
- type Natural :: *
- data Natural = NS GHC.Internal.Prim.Word# | NB GHC.Internal.Prim.ByteArray#
- naturalAdd :: Natural -> Natural -> Natural
- naturalAnd :: Natural -> Natural -> Natural
- naturalAndNot :: Natural -> Natural -> Natural
- naturalBit :: GHC.Internal.Types.Word -> Natural
- naturalBit# :: GHC.Internal.Prim.Word# -> Natural
- naturalCheck :: Natural -> GHC.Internal.Types.Bool
- naturalCheck# :: Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalClearBit :: Natural -> GHC.Internal.Types.Word -> Natural
- naturalClearBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
- naturalCompare :: Natural -> Natural -> GHC.Internal.Types.Ordering
- naturalComplementBit :: Natural -> GHC.Internal.Types.Word -> Natural
- naturalComplementBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
- naturalEncodeDouble# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
- naturalEncodeFloat# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float#
- naturalEq :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalEq# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Natural
- naturalFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Natural #)
- naturalFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Natural
- naturalFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Natural #)
- naturalFromWord :: GHC.Internal.Types.Word -> Natural
- naturalFromWord# :: GHC.Internal.Prim.Word# -> Natural
- naturalFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> Natural
- naturalFromWordList :: [GHC.Internal.Types.Word] -> Natural
- naturalGcd :: Natural -> Natural -> Natural
- naturalGe :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalGe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalGt :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalGt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalIsOne :: Natural -> GHC.Internal.Types.Bool
- naturalIsPowerOf2# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #)
- naturalIsZero :: Natural -> GHC.Internal.Types.Bool
- naturalLcm :: Natural -> Natural -> Natural
- naturalLe :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalLe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalLog2 :: Natural -> GHC.Internal.Types.Word
- naturalLog2# :: Natural -> GHC.Internal.Prim.Word#
- naturalLogBase :: Natural -> Natural -> GHC.Internal.Types.Word
- naturalLogBase# :: Natural -> Natural -> GHC.Internal.Prim.Word#
- naturalLogBaseWord :: GHC.Internal.Types.Word -> Natural -> GHC.Internal.Types.Word
- naturalLogBaseWord# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word#
- naturalLt :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalLt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalMul :: Natural -> Natural -> Natural
- naturalNe :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalNe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalNegate :: Natural -> Natural
- naturalOne :: Natural
- naturalOr :: Natural -> Natural -> Natural
- naturalPopCount :: Natural -> GHC.Internal.Types.Word
- naturalPopCount# :: Natural -> GHC.Internal.Prim.Word#
- naturalPowMod :: Natural -> Natural -> Natural -> Natural
- naturalQuot :: Natural -> Natural -> Natural
- naturalQuotRem :: Natural -> Natural -> (Natural, Natural)
- naturalQuotRem# :: Natural -> Natural -> (# Natural, Natural #)
- naturalRem :: Natural -> Natural -> Natural
- naturalSetBit :: Natural -> GHC.Internal.Types.Word -> Natural
- naturalSetBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
- naturalShiftL :: Natural -> GHC.Internal.Types.Word -> Natural
- naturalShiftL# :: Natural -> GHC.Internal.Prim.Word# -> Natural
- naturalShiftR :: Natural -> GHC.Internal.Types.Word -> Natural
- naturalShiftR# :: Natural -> GHC.Internal.Prim.Word# -> Natural
- naturalSignum :: Natural -> Natural
- naturalSizeInBase# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word#
- naturalSqr :: Natural -> Natural
- naturalSub :: Natural -> Natural -> (# (# #) | Natural #)
- naturalSubThrow :: Natural -> Natural -> Natural
- naturalSubUnsafe :: Natural -> Natural -> Natural
- naturalTestBit :: Natural -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
- naturalTestBit# :: Natural -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- naturalToAddr :: Natural -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
- naturalToAddr# :: forall s. Natural -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- naturalToBigNat# :: Natural -> GHC.Internal.Bignum.BigNat.BigNat#
- naturalToMutableByteArray# :: forall s. Natural -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- naturalToWord :: Natural -> GHC.Internal.Types.Word
- naturalToWord# :: Natural -> GHC.Internal.Prim.Word#
- naturalToWordClamp :: Natural -> GHC.Internal.Types.Word
- naturalToWordClamp# :: Natural -> GHC.Internal.Prim.Word#
- naturalToWordMaybe# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #)
- naturalXor :: Natural -> Natural -> Natural
- naturalZero :: Natural
-
module GHC.OldList where
-- Safety: Safe
(!!) :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> GHC.Internal.Types.Int -> a
=====================================
testsuite/tests/interface-stability/base-exports.stdout-ws-32
=====================================
@@ -8550,340 +8550,6 @@ module GHC.Num where
quotRemInteger :: Integer -> Integer -> (# Integer, Integer #)
subtract :: forall a. Num a => a -> a -> a
-module GHC.Num.BigNat where
- -- Safety: None
- type BigNat :: *
- data BigNat = BN# {unBigNat :: BigNat#}
- type BigNat# :: GHC.Internal.Types.UnliftedType
- type BigNat# = GHC.Internal.Bignum.WordArray.WordArray#
- bigNatAdd :: BigNat# -> BigNat# -> BigNat#
- bigNatAddWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatAddWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatAnd :: BigNat# -> BigNat# -> BigNat#
- bigNatAndInt# :: BigNat# -> GHC.Internal.Prim.Int# -> BigNat#
- bigNatAndNot :: BigNat# -> BigNat# -> BigNat#
- bigNatAndNotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatAndWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatBit :: GHC.Internal.Types.Word -> BigNat#
- bigNatBit# :: GHC.Internal.Prim.Word# -> BigNat#
- bigNatCheck :: BigNat# -> GHC.Internal.Types.Bool
- bigNatCheck# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatClearBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatCompare :: BigNat# -> BigNat# -> GHC.Internal.Types.Ordering
- bigNatCompareWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Ordering
- bigNatCompareWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Types.Ordering
- bigNatComplementBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatCtz :: BigNat# -> GHC.Internal.Types.Word
- bigNatCtz# :: BigNat# -> GHC.Internal.Prim.Word#
- bigNatCtzWord :: BigNat# -> GHC.Internal.Types.Word
- bigNatCtzWord# :: BigNat# -> GHC.Internal.Prim.Word#
- bigNatEncodeDouble# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
- bigNatEq :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatEq# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatEqWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatFromAbsInt# :: GHC.Internal.Prim.Int# -> BigNat#
- bigNatFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromAddrBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromAddrLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromByteArrayBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromByteArrayLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
- bigNatFromWord :: GHC.Internal.Types.Word -> BigNat#
- bigNatFromWord# :: GHC.Internal.Prim.Word# -> BigNat#
- bigNatFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatFromWord64# :: GHC.Internal.Prim.Word64# -> BigNat#
- bigNatFromWordArray :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat
- bigNatFromWordArray# :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatFromWordList :: [GHC.Internal.Types.Word] -> BigNat#
- bigNatFromWordList# :: [GHC.Internal.Types.Word] -> GHC.Internal.Bignum.WordArray.WordArray#
- bigNatFromWordListUnsafe :: [GHC.Internal.Types.Word] -> BigNat#
- bigNatGcd :: BigNat# -> BigNat# -> BigNat#
- bigNatGcdWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
- bigNatGe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatGe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatGt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatGt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatGtWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
- bigNatGtWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatIndex :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Types.Word
- bigNatIndex# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word#
- bigNatIsOne :: BigNat# -> GHC.Internal.Types.Bool
- bigNatIsOne# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatIsPowerOf2# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #)
- bigNatIsTwo :: BigNat# -> GHC.Internal.Types.Bool
- bigNatIsTwo# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatIsZero :: BigNat# -> GHC.Internal.Types.Bool
- bigNatIsZero# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatLcm :: BigNat# -> BigNat# -> BigNat#
- bigNatLcmWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatLcmWordWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatLe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatLe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatLeWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
- bigNatLeWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatLog2 :: BigNat# -> GHC.Internal.Types.Word
- bigNatLog2# :: BigNat# -> GHC.Internal.Prim.Word#
- bigNatLogBase :: BigNat# -> BigNat# -> GHC.Internal.Types.Word
- bigNatLogBase# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word#
- bigNatLogBaseWord :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word
- bigNatLogBaseWord# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word#
- bigNatLt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatLt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatMul :: BigNat# -> BigNat# -> BigNat#
- bigNatMulWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatMulWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatNe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
- bigNatNe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatOne :: BigNat
- bigNatOne# :: (# #) -> BigNat#
- bigNatOr :: BigNat# -> BigNat# -> BigNat#
- bigNatOrWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatPopCount :: BigNat# -> GHC.Internal.Types.Word
- bigNatPopCount# :: BigNat# -> GHC.Internal.Prim.Word#
- bigNatPowMod :: BigNat# -> BigNat# -> BigNat# -> BigNat#
- bigNatPowModWord# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
- bigNatQuot :: BigNat# -> BigNat# -> BigNat#
- bigNatQuotRem# :: BigNat# -> BigNat# -> (# BigNat#, BigNat# #)
- bigNatQuotRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# BigNat#, GHC.Internal.Prim.Word# #)
- bigNatQuotWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatQuotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatRem :: BigNat# -> BigNat# -> BigNat#
- bigNatRemWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word
- bigNatRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
- bigNatSetBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatShiftL :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatShiftL# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatShiftR :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatShiftR# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatShiftRNeg# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatSize :: BigNat# -> GHC.Internal.Types.Word
- bigNatSize# :: BigNat# -> GHC.Internal.Prim.Int#
- bigNatSizeInBase :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word
- bigNatSizeInBase# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word#
- bigNatSqr :: BigNat# -> BigNat#
- bigNatSub :: BigNat# -> BigNat# -> (# (# #) | BigNat# #)
- bigNatSubUnsafe :: BigNat# -> BigNat# -> BigNat#
- bigNatSubWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# (# #) | BigNat# #)
- bigNatSubWordUnsafe :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
- bigNatSubWordUnsafe# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatTestBit :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
- bigNatTestBit# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- bigNatToAddr :: BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
- bigNatToAddr# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToAddrBE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToAddrLE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToInt :: BigNat# -> GHC.Internal.Types.Int
- bigNatToInt# :: BigNat# -> GHC.Internal.Prim.Int#
- bigNatToMutableByteArray# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToMutableByteArrayBE# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToMutableByteArrayLE# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- bigNatToWord :: BigNat# -> GHC.Internal.Types.Word
- bigNatToWord# :: BigNat# -> GHC.Internal.Prim.Word#
- bigNatToWord64# :: BigNat# -> GHC.Internal.Prim.Word64#
- bigNatToWordList :: BigNat# -> [GHC.Internal.Types.Word]
- bigNatToWordMaybe# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #)
- bigNatXor :: BigNat# -> BigNat# -> BigNat#
- bigNatXorWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
- bigNatZero :: BigNat
- bigNatZero# :: (# #) -> BigNat#
- gcdInt :: GHC.Internal.Types.Int -> GHC.Internal.Types.Int -> GHC.Internal.Types.Int
- gcdInt# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int#
- gcdWord :: GHC.Internal.Types.Word -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word
- gcdWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
- powModWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
- raiseDivZero_BigNat :: (# #) -> BigNat#
-
-module GHC.Num.Integer where
- -- Safety: None
- type Integer :: *
- data Integer = IS GHC.Internal.Prim.Int# | IP GHC.Internal.Prim.ByteArray# | IN GHC.Internal.Prim.ByteArray#
- integerAbs :: Integer -> Integer
- integerAdd :: Integer -> Integer -> Integer
- integerAnd :: Integer -> Integer -> Integer
- integerBit :: GHC.Internal.Types.Word -> Integer
- integerBit# :: GHC.Internal.Prim.Word# -> Integer
- integerCheck :: Integer -> GHC.Internal.Types.Bool
- integerCheck# :: Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerCompare :: Integer -> Integer -> GHC.Internal.Types.Ordering
- integerComplement :: Integer -> Integer
- integerDecodeDouble# :: GHC.Internal.Prim.Double# -> (# Integer, GHC.Internal.Prim.Int# #)
- integerDiv :: Integer -> Integer -> Integer
- integerDivMod :: Integer -> Integer -> (Integer, Integer)
- integerDivMod# :: Integer -> Integer -> (# Integer, Integer #)
- integerEncodeDouble :: Integer -> GHC.Internal.Types.Int -> GHC.Internal.Types.Double
- integerEncodeDouble# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
- integerEncodeFloat# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float#
- integerEq :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerEq# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Integer
- integerFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Integer #)
- integerFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer
- integerFromBigNatNeg# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer
- integerFromBigNatSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Bignum.BigNat.BigNat# -> Integer
- integerFromByteArray :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> Integer
- integerFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Integer #)
- integerFromInt :: GHC.Internal.Types.Int -> Integer
- integerFromInt# :: GHC.Internal.Prim.Int# -> Integer
- integerFromInt64# :: GHC.Internal.Prim.Int64# -> Integer
- integerFromNatural :: GHC.Internal.Bignum.Natural.Natural -> Integer
- integerFromWord :: GHC.Internal.Types.Word -> Integer
- integerFromWord# :: GHC.Internal.Prim.Word# -> Integer
- integerFromWord64# :: GHC.Internal.Prim.Word64# -> Integer
- integerFromWordList :: GHC.Internal.Types.Bool -> [GHC.Internal.Types.Word] -> Integer
- integerFromWordNeg# :: GHC.Internal.Prim.Word# -> Integer
- integerFromWordSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# -> Integer
- integerGcd :: Integer -> Integer -> Integer
- integerGcde :: Integer -> Integer -> (Integer, Integer, Integer)
- integerGcde# :: Integer -> Integer -> (# Integer, Integer, Integer #)
- integerGe :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerGe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerGt :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerGt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerIsNegative :: Integer -> GHC.Internal.Types.Bool
- integerIsNegative# :: Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerIsOne :: Integer -> GHC.Internal.Types.Bool
- integerIsPowerOf2# :: Integer -> (# (# #) | GHC.Internal.Prim.Word# #)
- integerIsZero :: Integer -> GHC.Internal.Types.Bool
- integerLcm :: Integer -> Integer -> Integer
- integerLe :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerLe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerLog2 :: Integer -> GHC.Internal.Types.Word
- integerLog2# :: Integer -> GHC.Internal.Prim.Word#
- integerLogBase :: Integer -> Integer -> GHC.Internal.Types.Word
- integerLogBase# :: Integer -> Integer -> GHC.Internal.Prim.Word#
- integerLogBaseWord :: GHC.Internal.Types.Word -> Integer -> GHC.Internal.Types.Word
- integerLogBaseWord# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word#
- integerLt :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerLt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerMod :: Integer -> Integer -> Integer
- integerMul :: Integer -> Integer -> Integer
- integerNe :: Integer -> Integer -> GHC.Internal.Types.Bool
- integerNe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
- integerNegate :: Integer -> Integer
- integerOne :: Integer
- integerOr :: Integer -> Integer -> Integer
- integerPopCount# :: Integer -> GHC.Internal.Prim.Int#
- integerPowMod# :: Integer -> Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #)
- integerQuot :: Integer -> Integer -> Integer
- integerQuotRem :: Integer -> Integer -> (Integer, Integer)
- integerQuotRem# :: Integer -> Integer -> (# Integer, Integer #)
- integerRecipMod# :: Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #)
- integerRem :: Integer -> Integer -> Integer
- integerShiftL :: Integer -> GHC.Internal.Types.Word -> Integer
- integerShiftL# :: Integer -> GHC.Internal.Prim.Word# -> Integer
- integerShiftR :: Integer -> GHC.Internal.Types.Word -> Integer
- integerShiftR# :: Integer -> GHC.Internal.Prim.Word# -> Integer
- integerSignum :: Integer -> Integer
- integerSignum# :: Integer -> GHC.Internal.Prim.Int#
- integerSizeInBase# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word#
- integerSqr :: Integer -> Integer
- integerSub :: Integer -> Integer -> Integer
- integerTestBit :: Integer -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
- integerTestBit# :: Integer -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- integerToAddr :: Integer -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
- integerToAddr# :: forall s. Integer -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- integerToBigNatClamp# :: Integer -> GHC.Internal.Bignum.BigNat.BigNat#
- integerToBigNatSign# :: Integer -> (# GHC.Internal.Prim.Int#, GHC.Internal.Bignum.BigNat.BigNat# #)
- integerToInt :: Integer -> GHC.Internal.Types.Int
- integerToInt# :: Integer -> GHC.Internal.Prim.Int#
- integerToInt64# :: Integer -> GHC.Internal.Prim.Int64#
- integerToMutableByteArray :: Integer -> GHC.Internal.Prim.MutableByteArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
- integerToMutableByteArray# :: forall s. Integer -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- integerToNatural :: Integer -> GHC.Internal.Bignum.Natural.Natural
- integerToNaturalClamp :: Integer -> GHC.Internal.Bignum.Natural.Natural
- integerToNaturalThrow :: Integer -> GHC.Internal.Bignum.Natural.Natural
- integerToWord :: Integer -> GHC.Internal.Types.Word
- integerToWord# :: Integer -> GHC.Internal.Prim.Word#
- integerToWord64# :: Integer -> GHC.Internal.Prim.Word64#
- integerXor :: Integer -> Integer -> Integer
- integerZero :: Integer
-
-module GHC.Num.Natural where
- -- Safety: None
- type Natural :: *
- data Natural = NS GHC.Internal.Prim.Word# | NB GHC.Internal.Prim.ByteArray#
- naturalAdd :: Natural -> Natural -> Natural
- naturalAnd :: Natural -> Natural -> Natural
- naturalAndNot :: Natural -> Natural -> Natural
- naturalBit :: GHC.Internal.Types.Word -> Natural
- naturalBit# :: GHC.Internal.Prim.Word# -> Natural
- naturalCheck :: Natural -> GHC.Internal.Types.Bool
- naturalCheck# :: Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalClearBit :: Natural -> GHC.Internal.Types.Word -> Natural
- naturalClearBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
- naturalCompare :: Natural -> Natural -> GHC.Internal.Types.Ordering
- naturalComplementBit :: Natural -> GHC.Internal.Types.Word -> Natural
- naturalComplementBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
- naturalEncodeDouble# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
- naturalEncodeFloat# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float#
- naturalEq :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalEq# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Natural
- naturalFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Natural #)
- naturalFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Natural
- naturalFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Natural #)
- naturalFromWord :: GHC.Internal.Types.Word -> Natural
- naturalFromWord# :: GHC.Internal.Prim.Word# -> Natural
- naturalFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> Natural
- naturalFromWordList :: [GHC.Internal.Types.Word] -> Natural
- naturalGcd :: Natural -> Natural -> Natural
- naturalGe :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalGe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalGt :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalGt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalIsOne :: Natural -> GHC.Internal.Types.Bool
- naturalIsPowerOf2# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #)
- naturalIsZero :: Natural -> GHC.Internal.Types.Bool
- naturalLcm :: Natural -> Natural -> Natural
- naturalLe :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalLe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalLog2 :: Natural -> GHC.Internal.Types.Word
- naturalLog2# :: Natural -> GHC.Internal.Prim.Word#
- naturalLogBase :: Natural -> Natural -> GHC.Internal.Types.Word
- naturalLogBase# :: Natural -> Natural -> GHC.Internal.Prim.Word#
- naturalLogBaseWord :: GHC.Internal.Types.Word -> Natural -> GHC.Internal.Types.Word
- naturalLogBaseWord# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word#
- naturalLt :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalLt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalMul :: Natural -> Natural -> Natural
- naturalNe :: Natural -> Natural -> GHC.Internal.Types.Bool
- naturalNe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
- naturalNegate :: Natural -> Natural
- naturalOne :: Natural
- naturalOr :: Natural -> Natural -> Natural
- naturalPopCount :: Natural -> GHC.Internal.Types.Word
- naturalPopCount# :: Natural -> GHC.Internal.Prim.Word#
- naturalPowMod :: Natural -> Natural -> Natural -> Natural
- naturalQuot :: Natural -> Natural -> Natural
- naturalQuotRem :: Natural -> Natural -> (Natural, Natural)
- naturalQuotRem# :: Natural -> Natural -> (# Natural, Natural #)
- naturalRem :: Natural -> Natural -> Natural
- naturalSetBit :: Natural -> GHC.Internal.Types.Word -> Natural
- naturalSetBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
- naturalShiftL :: Natural -> GHC.Internal.Types.Word -> Natural
- naturalShiftL# :: Natural -> GHC.Internal.Prim.Word# -> Natural
- naturalShiftR :: Natural -> GHC.Internal.Types.Word -> Natural
- naturalShiftR# :: Natural -> GHC.Internal.Prim.Word# -> Natural
- naturalSignum :: Natural -> Natural
- naturalSizeInBase# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word#
- naturalSqr :: Natural -> Natural
- naturalSub :: Natural -> Natural -> (# (# #) | Natural #)
- naturalSubThrow :: Natural -> Natural -> Natural
- naturalSubUnsafe :: Natural -> Natural -> Natural
- naturalTestBit :: Natural -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
- naturalTestBit# :: Natural -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
- naturalToAddr :: Natural -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
- naturalToAddr# :: forall s. Natural -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- naturalToBigNat# :: Natural -> GHC.Internal.Bignum.BigNat.BigNat#
- naturalToMutableByteArray# :: forall s. Natural -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
- naturalToWord :: Natural -> GHC.Internal.Types.Word
- naturalToWord# :: Natural -> GHC.Internal.Prim.Word#
- naturalToWordClamp :: Natural -> GHC.Internal.Types.Word
- naturalToWordClamp# :: Natural -> GHC.Internal.Prim.Word#
- naturalToWordMaybe# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #)
- naturalXor :: Natural -> Natural -> Natural
- naturalZero :: Natural
-
module GHC.OldList where
-- Safety: Safe
(!!) :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> GHC.Internal.Types.Int -> a
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/68515163eee98c9aff3e75b55c31aa2…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/68515163eee98c9aff3e75b55c31aa2…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T26625] base: deprecate GHC internals in GHC.Num
by Teo Camarasu (@teo) 11 Jan '26
by Teo Camarasu (@teo) 11 Jan '26
11 Jan '26
Teo Camarasu pushed to branch wip/T26625 at Glasgow Haskell Compiler / GHC
Commits:
af606b66 by Teo Camarasu at 2026-01-10T22:30:54+00:00
base: deprecate GHC internals in GHC.Num
Implements CLC proposal: https://github.com/haskell/core-libraries-committee/issues/360
- - - - -
2 changed files:
- libraries/base/changelog.md
- libraries/base/src/GHC/Num.hs
Changes:
=====================================
libraries/base/changelog.md
=====================================
@@ -13,6 +13,7 @@
* Fix bug where `naturalAndNot` was incorrectly truncating results ([CLC proposal #350](github.com/haskell/core-libraries-committee/issues/350))
* Remove extra laziness from `Data.Bifunctor.Bifunctor` instances for all tuples to have the same laziness as their `Data.Functor.Functor` counterparts (i.e. they became more strict than before) ([CLC proposal #339](https://github.com/haskell/core-libraries-committee/issues/339))
* Adjust the strictness of `Data.List.iterate'` to be more reasonable: every element of the output list is forced to WHNF when the `(:)` containing it is forced. ([CLC proposal #335)](https://github.com/haskell/core-libraries-committee/issues/335)
+ * GHC internals in `GHC.Num` have been deprecated and will be removed after one major release. ((CLC proposal #360)[https://github.com/haskell/core-libraries-committee/issues/360])
* Add `nubOrd` / `nubOrdBy` to `Data.List` and `Data.List.NonEmpty`. ([CLC proposal #336](https://github.com/haskell/core-libraries-committee/issues/336))
## 4.22.0.0 *TBA*
=====================================
libraries/base/src/GHC/Num.hs
=====================================
@@ -1,5 +1,7 @@
{-# LANGUAGE MagicHash #-}
{-# OPTIONS_HADDOCK not-home #-}
+-- don't warn that some but not all of Integer and Natural are deprecated
+{-# OPTIONS_GHC -Wno-incomplete-export-warnings -Wno-duplicate-exports #-}
-- |
-- Module : GHC.Num
@@ -15,191 +17,370 @@
module GHC.Num
( Num(..)
+ , Integer
+ , Natural
, subtract
, quotRemInteger
- , integerFromNatural
- , integerToNaturalClamp
- , integerToNaturalThrow
- , integerToNatural
- , integerToWord#
- , integerToInt#
- , integerToWord64#
- , integerToInt64#
- , integerAdd
- , integerMul
- , integerSub
- , integerNegate
- , integerAbs
- , integerPopCount#
- , integerQuot
- , integerRem
- , integerDiv
- , integerMod
- , integerDivMod#
- , integerQuotRem#
- , integerEncodeFloat#
- , integerEncodeDouble#
- , integerGcd
- , integerLcm
- , integerAnd
- , integerOr
- , integerXor
- , integerComplement
- , integerBit#
- , integerTestBit#
- , integerShiftL#
- , integerShiftR#
- , integerFromWord#
- , integerFromWord64#
- , integerFromInt64#
- , Integer(..)
- , integerBit
- , integerCheck
- , integerCheck#
- , integerCompare
- , integerDecodeDouble#
- , integerDivMod
- , integerEncodeDouble
- , integerEq
- , integerEq#
- , integerFromAddr
- , integerFromAddr#
- , integerFromBigNat#
- , integerFromBigNatNeg#
- , integerFromBigNatSign#
- , integerFromByteArray
- , integerFromByteArray#
- , integerFromInt
- , integerFromInt#
+ , integerToWord
, integerFromWord
- , integerFromWordList
- , integerFromWordNeg#
- , integerFromWordSign#
- , integerGcde
- , integerGcde#
- , integerGe
- , integerGe#
- , integerGt
- , integerGt#
- , integerIsNegative
- , integerIsNegative#
- , integerIsOne
- , integerIsPowerOf2#
- , integerIsZero
- , integerLe
- , integerLe#
- , integerLog2
- , integerLog2#
- , integerLogBase
- , integerLogBase#
- , integerLogBaseWord
- , integerLogBaseWord#
- , integerLt
- , integerLt#
- , integerNe
- , integerNe#
- , integerOne
- , integerPowMod#
- , integerQuotRem
- , integerRecipMod#
- , integerShiftL
- , integerShiftR
- , integerSignum
- , integerSignum#
- , integerSizeInBase#
- , integerSqr
- , integerTestBit
- , integerToAddr
- , integerToAddr#
- , integerToBigNatClamp#
- , integerToBigNatSign#
, integerToInt
- , integerToMutableByteArray
- , integerToMutableByteArray#
- , integerToWord
- , integerZero
- , naturalToWord#
- , naturalPopCount#
- , naturalShiftR#
- , naturalShiftL#
- , naturalAdd
- , naturalSub
- , naturalSubThrow
- , naturalSubUnsafe
- , naturalMul
- , naturalQuotRem#
- , naturalQuot
- , naturalRem
- , naturalAnd
- , naturalAndNot
- , naturalOr
- , naturalXor
- , naturalTestBit#
- , naturalBit#
- , naturalGcd
- , naturalLcm
- , naturalLog2#
- , naturalLogBaseWord#
- , naturalLogBase#
- , naturalPowMod
- , naturalSizeInBase#
- , Natural(..)
- , naturalBit
- , naturalCheck
- , naturalCheck#
- , naturalClearBit
- , naturalClearBit#
- , naturalCompare
- , naturalComplementBit
- , naturalComplementBit#
- , naturalEncodeDouble#
- , naturalEncodeFloat#
- , naturalEq
- , naturalEq#
- , naturalFromAddr
- , naturalFromAddr#
- , naturalFromBigNat#
- , naturalFromByteArray#
- , naturalFromWord
- , naturalFromWord#
- , naturalFromWord2#
- , naturalFromWordList
- , naturalGe
- , naturalGe#
- , naturalGt
- , naturalGt#
- , naturalIsOne
- , naturalIsPowerOf2#
- , naturalIsZero
- , naturalLe
- , naturalLe#
- , naturalLog2
- , naturalLogBase
- , naturalLogBaseWord
- , naturalLt
- , naturalLt#
- , naturalNe
- , naturalNe#
- , naturalNegate
- , naturalOne
- , naturalPopCount
- , naturalQuotRem
- , naturalSetBit
- , naturalSetBit#
- , naturalShiftL
- , naturalShiftR
- , naturalSignum
- , naturalSqr
- , naturalTestBit
- , naturalToAddr
- , naturalToAddr#
- , naturalToBigNat#
- , naturalToMutableByteArray#
- , naturalToWord
- , naturalToWordClamp
- , naturalToWordClamp#
- , naturalToWordMaybe#
- , naturalZero
+ , integerFromInt
+ , integerToNatural
+ , integerFromNatural
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ Integer(IN, IP, IS)
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ Natural(NS, NB)
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerToNaturalClamp
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerToNaturalThrow
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerToWord#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerToInt#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerToWord64#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerToInt64#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerAdd
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerMul
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerSub
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerNegate
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerAbs
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerPopCount#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerQuot
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerRem
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerDiv
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerMod
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerDivMod#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerQuotRem#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerEncodeFloat#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerEncodeDouble#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerGcd
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerLcm
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerAnd
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerOr
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerXor
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerComplement
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerBit#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerTestBit#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerShiftL#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerShiftR#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerFromWord#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerFromWord64#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerFromInt64#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerBit
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerCheck
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerCheck#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerCompare
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerDecodeDouble#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerDivMod
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerEncodeDouble
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerEq
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerEq#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerFromAddr
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerFromAddr#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerFromBigNat#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerFromBigNatNeg#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerFromBigNatSign#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerFromByteArray
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerFromByteArray#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerFromInt#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerFromWordList
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerFromWordNeg#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerFromWordSign#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerGcde
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerGcde#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerGe
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerGe#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerGt
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerGt#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerIsNegative
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerIsNegative#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerIsOne
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerIsPowerOf2#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerIsZero
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerLe
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerLe#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerLog2
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerLog2#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerLogBase
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerLogBase#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerLogBaseWord
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerLogBaseWord#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerLt
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerLt#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerNe
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerNe#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerOne
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerPowMod#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerQuotRem
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerRecipMod#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerShiftL
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerShiftR
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerSignum
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerSignum#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerSizeInBase#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerSqr
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerTestBit
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerToAddr
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerToAddr#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerToBigNatClamp#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerToBigNatSign#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerToMutableByteArray
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerToMutableByteArray#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ integerZero
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalToWord#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalPopCount#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalShiftR#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalShiftL#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalAdd
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalSub
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalSubThrow
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalSubUnsafe
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalMul
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalQuotRem#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalQuot
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalRem
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalAnd
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalAndNot
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalOr
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalXor
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalTestBit#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalBit#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalGcd
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalLcm
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalLog2#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalLogBaseWord#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalLogBase#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalPowMod
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalSizeInBase#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalBit
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalCheck
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalCheck#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalClearBit
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalClearBit#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalCompare
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalComplementBit
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalComplementBit#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalEncodeDouble#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalEncodeFloat#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalEq
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalEq#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalFromAddr
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalFromAddr#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalFromBigNat#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalFromByteArray#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalFromWord
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalFromWord#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalFromWord2#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalFromWordList
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalGe
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalGe#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalGt
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalGt#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalIsOne
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalIsPowerOf2#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalIsZero
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalLe
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalLe#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalLog2
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalLogBase
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalLogBaseWord
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalLt
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalLt#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalNe
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalNe#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalNegate
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalOne
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalPopCount
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalQuotRem
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalSetBit
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalSetBit#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalShiftL
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalShiftR
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalSignum
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalSqr
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalTestBit
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalToAddr
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalToAddr#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalToBigNat#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalToMutableByteArray#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalToWord
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalToWordClamp
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalToWordClamp#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalToWordMaybe#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
+ naturalZero
)
where
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/af606b665f31794868102496d994fd5…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/af606b665f31794868102496d994fd5…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Bodigrim pushed new branch wip/t23217 at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/t23217
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T26625] base: deprecate GHC internals in GHC.Num
by Teo Camarasu (@teo) 11 Jan '26
by Teo Camarasu (@teo) 11 Jan '26
11 Jan '26
Teo Camarasu pushed to branch wip/T26625 at Glasgow Haskell Compiler / GHC
Commits:
e6803f04 by Teo Camarasu at 2026-01-10T22:29:44+00:00
base: deprecate GHC internals in GHC.Num
Implements CLC proposal: https://github.com/haskell/core-libraries-committee/issues/360
- - - - -
2 changed files:
- libraries/base/changelog.md
- libraries/base/src/GHC/Num.hs
Changes:
=====================================
libraries/base/changelog.md
=====================================
@@ -13,6 +13,7 @@
* Fix bug where `naturalAndNot` was incorrectly truncating results ([CLC proposal #350](github.com/haskell/core-libraries-committee/issues/350))
* Remove extra laziness from `Data.Bifunctor.Bifunctor` instances for all tuples to have the same laziness as their `Data.Functor.Functor` counterparts (i.e. they became more strict than before) ([CLC proposal #339](https://github.com/haskell/core-libraries-committee/issues/339))
* Adjust the strictness of `Data.List.iterate'` to be more reasonable: every element of the output list is forced to WHNF when the `(:)` containing it is forced. ([CLC proposal #335)](https://github.com/haskell/core-libraries-committee/issues/335)
+ * GHC internals in `GHC.Num` have been deprecated and will be removed after one major release. ((CLC proposal #360)[https://github.com/haskell/core-libraries-committee/issues/360])
* Add `nubOrd` / `nubOrdBy` to `Data.List` and `Data.List.NonEmpty`. ([CLC proposal #336](https://github.com/haskell/core-libraries-committee/issues/336))
## 4.22.0.0 *TBA*
=====================================
libraries/base/src/GHC/Num.hs
=====================================
@@ -1,5 +1,7 @@
{-# LANGUAGE MagicHash #-}
{-# OPTIONS_HADDOCK not-home #-}
+-- don't warn that some but not all of Integer and Natural are deprecated
+{-# OPTIONS_GHC -Wno-incomplete-export-warnings -Wno-duplicate-exports #-}
-- |
-- Module : GHC.Num
@@ -15,191 +17,370 @@
module GHC.Num
( Num(..)
+ , Integer
+ , Natural
, subtract
, quotRemInteger
- , integerFromNatural
- , integerToNaturalClamp
- , integerToNaturalThrow
- , integerToNatural
- , integerToWord#
- , integerToInt#
- , integerToWord64#
- , integerToInt64#
- , integerAdd
- , integerMul
- , integerSub
- , integerNegate
- , integerAbs
- , integerPopCount#
- , integerQuot
- , integerRem
- , integerDiv
- , integerMod
- , integerDivMod#
- , integerQuotRem#
- , integerEncodeFloat#
- , integerEncodeDouble#
- , integerGcd
- , integerLcm
- , integerAnd
- , integerOr
- , integerXor
- , integerComplement
- , integerBit#
- , integerTestBit#
- , integerShiftL#
- , integerShiftR#
- , integerFromWord#
- , integerFromWord64#
- , integerFromInt64#
- , Integer(..)
- , integerBit
- , integerCheck
- , integerCheck#
- , integerCompare
- , integerDecodeDouble#
- , integerDivMod
- , integerEncodeDouble
- , integerEq
- , integerEq#
- , integerFromAddr
- , integerFromAddr#
- , integerFromBigNat#
- , integerFromBigNatNeg#
- , integerFromBigNatSign#
- , integerFromByteArray
- , integerFromByteArray#
- , integerFromInt
- , integerFromInt#
+ , integerToWord
, integerFromWord
- , integerFromWordList
- , integerFromWordNeg#
- , integerFromWordSign#
- , integerGcde
- , integerGcde#
- , integerGe
- , integerGe#
- , integerGt
- , integerGt#
- , integerIsNegative
- , integerIsNegative#
- , integerIsOne
- , integerIsPowerOf2#
- , integerIsZero
- , integerLe
- , integerLe#
- , integerLog2
- , integerLog2#
- , integerLogBase
- , integerLogBase#
- , integerLogBaseWord
- , integerLogBaseWord#
- , integerLt
- , integerLt#
- , integerNe
- , integerNe#
- , integerOne
- , integerPowMod#
- , integerQuotRem
- , integerRecipMod#
- , integerShiftL
- , integerShiftR
- , integerSignum
- , integerSignum#
- , integerSizeInBase#
- , integerSqr
- , integerTestBit
- , integerToAddr
- , integerToAddr#
- , integerToBigNatClamp#
- , integerToBigNatSign#
, integerToInt
- , integerToMutableByteArray
- , integerToMutableByteArray#
- , integerToWord
- , integerZero
- , naturalToWord#
- , naturalPopCount#
- , naturalShiftR#
- , naturalShiftL#
- , naturalAdd
- , naturalSub
- , naturalSubThrow
- , naturalSubUnsafe
- , naturalMul
- , naturalQuotRem#
- , naturalQuot
- , naturalRem
- , naturalAnd
- , naturalAndNot
- , naturalOr
- , naturalXor
- , naturalTestBit#
- , naturalBit#
- , naturalGcd
- , naturalLcm
- , naturalLog2#
- , naturalLogBaseWord#
- , naturalLogBase#
- , naturalPowMod
- , naturalSizeInBase#
- , Natural(..)
- , naturalBit
- , naturalCheck
- , naturalCheck#
- , naturalClearBit
- , naturalClearBit#
- , naturalCompare
- , naturalComplementBit
- , naturalComplementBit#
- , naturalEncodeDouble#
- , naturalEncodeFloat#
- , naturalEq
- , naturalEq#
- , naturalFromAddr
- , naturalFromAddr#
- , naturalFromBigNat#
- , naturalFromByteArray#
- , naturalFromWord
- , naturalFromWord#
- , naturalFromWord2#
- , naturalFromWordList
- , naturalGe
- , naturalGe#
- , naturalGt
- , naturalGt#
- , naturalIsOne
- , naturalIsPowerOf2#
- , naturalIsZero
- , naturalLe
- , naturalLe#
- , naturalLog2
- , naturalLogBase
- , naturalLogBaseWord
- , naturalLt
- , naturalLt#
- , naturalNe
- , naturalNe#
- , naturalNegate
- , naturalOne
- , naturalPopCount
- , naturalQuotRem
- , naturalSetBit
- , naturalSetBit#
- , naturalShiftL
- , naturalShiftR
- , naturalSignum
- , naturalSqr
- , naturalTestBit
- , naturalToAddr
- , naturalToAddr#
- , naturalToBigNat#
- , naturalToMutableByteArray#
- , naturalToWord
- , naturalToWordClamp
- , naturalToWordClamp#
- , naturalToWordMaybe#
- , naturalZero
+ , integerFromInt
+ , integerToNatural
+ , integerFromNatural
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ Integer(IN, IP, IS)
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ Natural(NS, NB)
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerToNaturalClamp
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerToNaturalThrow
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerToWord#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerToInt#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerToWord64#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerToInt64#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerAdd
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerMul
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerSub
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerNegate
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerAbs
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerPopCount#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerQuot
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerRem
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerDiv
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerMod
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerDivMod#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerQuotRem#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerEncodeFloat#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerEncodeDouble#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerGcd
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerLcm
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerAnd
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerOr
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerXor
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerComplement
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerBit#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerTestBit#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerShiftL#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerShiftR#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerFromWord#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerFromWord64#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerFromInt64#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerBit
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerCheck
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerCheck#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerCompare
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerDecodeDouble#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerDivMod
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerEncodeDouble
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerEq
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerEq#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerFromAddr
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerFromAddr#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerFromBigNat#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerFromBigNatNeg#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerFromBigNatSign#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerFromByteArray
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerFromByteArray#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerFromInt#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerFromWordList
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerFromWordNeg#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerFromWordSign#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerGcde
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerGcde#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerGe
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerGe#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerGt
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerGt#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerIsNegative
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerIsNegative#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerIsOne
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerIsPowerOf2#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerIsZero
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerLe
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerLe#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerLog2
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerLog2#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerLogBase
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerLogBase#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerLogBaseWord
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerLogBaseWord#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerLt
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerLt#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerNe
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerNe#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerOne
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerPowMod#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerQuotRem
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerRecipMod#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerShiftL
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerShiftR
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerSignum
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerSignum#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerSizeInBase#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerSqr
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerTestBit
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerToAddr
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerToAddr#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerToBigNatClamp#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerToBigNatSign#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerToMutableByteArray
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerToMutableByteArray#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ integerZero
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalToWord#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalPopCount#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalShiftR#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalShiftL#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalAdd
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalSub
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalSubThrow
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalSubUnsafe
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalMul
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalQuotRem#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalQuot
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalRem
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalAnd
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalAndNot
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalOr
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalXor
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalTestBit#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalBit#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalGcd
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalLcm
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalLog2#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalLogBaseWord#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalLogBase#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalPowMod
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalSizeInBase#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalBit
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalCheck
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalCheck#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalClearBit
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalClearBit#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalCompare
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalComplementBit
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalComplementBit#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalEncodeDouble#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalEncodeFloat#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalEq
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalEq#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalFromAddr
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalFromAddr#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalFromBigNat#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalFromByteArray#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalFromWord
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalFromWord#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalFromWord2#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalFromWordList
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalGe
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalGe#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalGt
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalGt#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalIsOne
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalIsPowerOf2#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalIsZero
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalLe
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalLe#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalLog2
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalLogBase
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalLogBaseWord
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalLt
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalLt#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalNe
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalNe#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalNegate
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalOne
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalPopCount
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalQuotRem
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalSetBit
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalSetBit#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalShiftL
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalShiftR
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalSignum
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalSqr
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalTestBit
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalToAddr
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalToAddr#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalToBigNat#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalToMutableByteArray#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalToWord
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalToWordClamp
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalToWordClamp#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalToWordMaybe#
+ , {-# DEPRECATED ["The internals of big numbers will be removed in base-XXX.", "Use ghc-bignum instead."] #-}
+ naturalZero
)
where
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e6803f049534a78ae2762c670a996ad…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e6803f049534a78ae2762c670a996ad…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T25262] Use template-haskell-lift/quasiquoter in boot libraries
by Teo Camarasu (@teo) 11 Jan '26
by Teo Camarasu (@teo) 11 Jan '26
11 Jan '26
Teo Camarasu pushed to branch wip/T25262 at Glasgow Haskell Compiler / GHC
Commits:
c05fa835 by Teo Camarasu at 2026-01-10T21:55:54+00:00
Use template-haskell-lift/quasiquoter in boot libraries
- - - - -
19 changed files:
- compiler/ghc.cabal.in
- ghc/ghc-bin.cabal.in
- hadrian/hadrian.cabal
- libraries/Cabal
- libraries/bytestring
- libraries/containers
- libraries/exceptions
- libraries/filepath
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghc-compact/ghc-compact.cabal
- libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal
- libraries/ghci/ghci.cabal.in
- libraries/haskeline
- libraries/os-string
- libraries/parsec
- libraries/text
- libraries/time
- libraries/unix
- utils/iserv/iserv.cabal.in
Changes:
=====================================
compiler/ghc.cabal.in
=====================================
@@ -118,7 +118,7 @@ Library
deepseq >= 1.4 && < 1.6,
directory >= 1 && < 1.4,
process >= 1 && < 1.7,
- bytestring >= 0.11 && < 0.13,
+ bytestring >= 0.11 && < 0.14,
binary == 0.8.*,
time >= 1.4 && < 1.16,
containers >= 0.6.2.1 && < 0.9,
=====================================
ghc/ghc-bin.cabal.in
=====================================
@@ -36,7 +36,7 @@ Executable ghc
GHC.Driver.Session.Mode
Build-Depends: base >= 4 && < 5,
array >= 0.1 && < 0.6,
- bytestring >= 0.9 && < 0.13,
+ bytestring >= 0.9 && < 0.14,
directory >= 1 && < 1.4,
process >= 1 && < 1.7,
filepath >= 1.5 && < 1.6,
=====================================
hadrian/hadrian.cabal
=====================================
@@ -155,7 +155,7 @@ executable hadrian
, TypeFamilies
build-depends: Cabal >= 3.13 && < 3.17
, base >= 4.11 && < 5
- , bytestring >= 0.10 && < 0.13
+ , bytestring >= 0.10 && < 0.14
, containers >= 0.5 && < 0.9
-- N.B. directory >=1.3.9 as earlier versions are
-- afflicted by #24382.
=====================================
libraries/Cabal
=====================================
@@ -1 +1 @@
-Subproject commit d9b0904b49dc84e0bfc79062daf2bbdf9d22a422
+Subproject commit bf964ddcc8e9c3c0a3ae46ab88c020046ac5e402
=====================================
libraries/bytestring
=====================================
@@ -1 +1 @@
-Subproject commit d984ad00644c0157bad04900434b9d36f23633c5
+Subproject commit 754b7a7741f050eb42706b8bbddbf21184a0f7d5
=====================================
libraries/containers
=====================================
@@ -1 +1 @@
-Subproject commit 801b06e5d4392b028e519d5ca116a2881d559721
+Subproject commit 8147f030783c23936f1e974f56e1b9b3993724f3
=====================================
libraries/exceptions
=====================================
@@ -1 +1 @@
-Subproject commit b6c4290124eb1138358bf04ad9f33e67f6c5c1d8
+Subproject commit 6268676cddc3dfc164896bcb981054fe49d6ba91
=====================================
libraries/filepath
=====================================
@@ -1 +1 @@
-Subproject commit cbcd0ccf92f47e6c10fb9cc513a7b26facfc19fe
+Subproject commit 14fb430d8c33948598226af83c120e02bb36ce32
=====================================
libraries/ghc-boot/ghc-boot.cabal.in
=====================================
@@ -77,7 +77,7 @@ Library
build-depends: base >= 4.7 && < 4.23,
binary == 0.8.*,
- bytestring >= 0.10 && < 0.13,
+ bytestring >= 0.10 && < 0.14,
containers >= 0.5 && < 0.9,
directory >= 1.2 && < 1.4,
filepath >= 1.3 && < 1.6,
=====================================
libraries/ghc-compact/ghc-compact.cabal
=====================================
@@ -40,7 +40,7 @@ library
CPP
build-depends: base >= 4.9.0 && < 4.23,
- bytestring >= 0.10.6.0 && <0.13
+ bytestring >= 0.10.6.0 && <0.14
ghc-options: -Wall
exposed-modules: GHC.Compact
=====================================
libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal
=====================================
@@ -53,7 +53,7 @@ executable ucd2haskell
Generator.WordEncoding
build-depends:
base >= 4.7 && < 5
- , bytestring >= 0.11 && < 0.13
+ , bytestring >= 0.11 && < 0.14
, directory >= 1.3.6 && < 1.4
, filepath >= 1.4.2 && < 1.6
, getopt-generics >= 0.13 && < 0.14
=====================================
libraries/ghci/ghci.cabal.in
=====================================
@@ -89,7 +89,7 @@ library
ghc-internal >= 9.1001.0 && <=@ProjectVersionForLib@.0,
ghc-prim >= 0.5.0 && < 0.14,
binary == 0.8.*,
- bytestring >= 0.10 && < 0.13,
+ bytestring >= 0.10 && < 0.14,
containers >= 0.5 && < 0.9,
deepseq >= 1.4 && < 1.6,
filepath >= 1.4 && < 1.6,
=====================================
libraries/haskeline
=====================================
@@ -1 +1 @@
-Subproject commit 991953cd5d3bb9e8057de4a0d8f2cae3455865d8
+Subproject commit c61650dc4cbbb4b7f5c8f96ccb23bb48dc5f580f
=====================================
libraries/os-string
=====================================
@@ -1 +1 @@
-Subproject commit 2e693aad07540173a0169971b27c9acac28eeff1
+Subproject commit cf53b19b2d5933b53d77abada1f08a88c455a8b7
=====================================
libraries/parsec
=====================================
@@ -1 +1 @@
-Subproject commit 552730e23e1fd2dae46a60d75138b8d173492462
+Subproject commit cbd35433d33a05676266d516e612b0aa31d5a5bc
=====================================
libraries/text
=====================================
@@ -1 +1 @@
-Subproject commit 5f343f668f421bfb30cead594e52d0ac6206ff67
+Subproject commit 3740ed564b0b2eb127d99e26657fe58e37fcda2c
=====================================
libraries/time
=====================================
@@ -1 +1 @@
-Subproject commit 507f50844802f1469ba6cadfeefd4e3fecee0416
+Subproject commit a6cb12065d8f52d6d3ef014ae580eb3a6ad82f09
=====================================
libraries/unix
=====================================
@@ -1 +1 @@
-Subproject commit c9b3e95b5c15b118e55522bd92963038c6a88160
+Subproject commit 2076de9eabaeeca54e6e5715f26798248abaf67d
=====================================
utils/iserv/iserv.cabal.in
=====================================
@@ -33,7 +33,7 @@ Executable iserv
Build-Depends: array >= 0.5 && < 0.6,
base >= 4 && < 5,
binary >= 0.7 && < 0.11,
- bytestring >= 0.10 && < 0.13,
+ bytestring >= 0.10 && < 0.14,
containers >= 0.5 && < 0.9,
deepseq >= 1.4 && < 1.6,
ghci == @ProjectVersionMunged@
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c05fa8358dca46a8ae80d11e514b557…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c05fa8358dca46a8ae80d11e514b557…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/andreask/ticked_joins] WIP: turn off case-of-case when join point occurs under prof ticks
by sheaf (@sheaf) 10 Jan '26
by sheaf (@sheaf) 10 Jan '26
10 Jan '26
sheaf pushed to branch wip/andreask/ticked_joins at Glasgow Haskell Compiler / GHC
Commits:
8b8e2154 by sheaf at 2026-01-10T11:31:45+01:00
WIP: turn off case-of-case when join point occurs under prof ticks
- - - - -
8 changed files:
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Types/Basic.hs
Changes:
=====================================
compiler/GHC/Core/Lint.hs
=====================================
@@ -672,7 +672,7 @@ lintRhs :: Id -> CoreExpr -> LintM (OutType, UsageEnv)
lintRhs bndr rhs
| JoinPoint arity <- idJoinPointHood bndr
= lintJoinLams arity (Just bndr) rhs
- | AlwaysTailCalled arity <- tailCallInfo (idOccInfo bndr)
+ | AlwaysTailCalled arity _ <- tailCallInfo (idOccInfo bndr)
= lintJoinLams arity Nothing rhs
-- Allow applications of the data constructor @StaticPtr@ at the top
=====================================
compiler/GHC/Core/Opt/OccurAnal.hs
=====================================
@@ -2585,7 +2585,13 @@ But it is not necessary to gather CoVars from the types of other binders.
occAnal env (Tick tickish body)
= WUD usage' (Tick tickish body')
where
- WUD usage body' = occAnal env body
+ WUD usage body' = occAnal env' body
+
+ env' = case tickish of
+ -- Set that we are inside a profiling tick
+ -- SLD TODO: explain why we need this info
+ ProfNote {} -> setInProfTick env
+ _ -> env
usage'
| tickishCanScopeJoin tickish
@@ -2809,6 +2815,13 @@ occAnalApp env (fun, args, ticks)
in WUD (markAllNonTail (fun_uds `andUDs` args_uds)) app_out
where
+ -- SLD TODO
+ -- !_ = pprTrace "occAnalApp fallback: marking all non-tail"
+ -- ( vcat [ text "fun:" <+> ppr fun
+ -- , text "args:" <+> ppr args
+ -- , text "ticks:" <+> ppr ticks
+ -- ])
+ -- ()
!(WUD args_uds app') = occAnalArgs env fun' args []
!(WUD fun_uds fun') = occAnal (addAppCtxt env args) fun
-- The addAppCtxt is a bit cunning. One iteration of the simplifier
@@ -2929,6 +2942,7 @@ scrutinised y).
data OccEnv
= OccEnv { occ_encl :: !OccEncl -- Enclosing context information
+ , occ_prof_ticks :: !Int
, occ_one_shots :: !OneShots -- See Note [OneShots]
, occ_unf_act :: Id -> Bool -- Which Id unfoldings are active
, occ_rule_act :: ActivationGhc -> Bool -- Which rules are active
@@ -2994,6 +3008,7 @@ type OneShots = [OneShotInfo]
initOccEnv :: OccEnv
initOccEnv
= OccEnv { occ_encl = OccVanilla
+ , occ_prof_ticks = 0
, occ_one_shots = []
-- To be conservative, we say that all
@@ -3072,6 +3087,9 @@ setTailCtxt !env = env { occ_encl = OccVanilla }
-- Preserve occ_one_shots, occ_join points
-- Do not use OccRhs for the RHS of a join point (which is a tail ctxt):
+setInProfTick :: OccEnv -> OccEnv
+setInProfTick !env = env { occ_prof_ticks = 1 + occ_prof_ticks env }
+
mkRhsOccEnv :: OccEnv -> RecFlag -> OccEncl -> JoinPointHood -> Id -> CoreExpr -> OccEnv
-- See Note [The OccEnv for a right hand side]
-- For a join point:
@@ -3813,7 +3831,7 @@ mkOneOcc !env id int_cxt arity
where
occ = OneOccL { lo_n_br = 1
, lo_int_cxt = int_cxt
- , lo_tail = AlwaysTailCalled arity }
+ , lo_tail = AlwaysTailCalled arity (occ_prof_ticks env) }
-- Add several occurrences, assumed not to be tail calls
add_many_occ :: Var -> OccInfoEnv -> OccInfoEnv
@@ -3866,13 +3884,20 @@ delBndrsFromUDs bndrs (UD { ud_env = env, ud_z_many = z_many
, ud_z_tail = z_tail `delVarEnvList` bndrs }
markAllMany, markAllInsideLam, markAllNonTail, markAllManyNonTail
- :: UsageDetails -> UsageDetails
+ :: HasDebugCallStack => UsageDetails -> UsageDetails
markAllMany ud@(UD { ud_env = env }) = ud { ud_z_many = env }
markAllInsideLam ud@(UD { ud_env = env }) = ud { ud_z_in_lam = env }
-markAllNonTail ud@(UD { ud_env = env }) = ud { ud_z_tail = env }
markAllManyNonTail = markAllMany . markAllNonTail -- effectively sets to noOccInfo
-markAllInsideLamIf, markAllNonTailIf :: Bool -> UsageDetails -> UsageDetails
+markAllNonTail ud@(UD { ud_env = env }) =
+ if isNullUFM env
+ then
+ ud { ud_z_tail = env }
+ else
+ -- SLD TODO pprTrace "markAllNonTail" ( text "zapping:" <+> ppr env $$ callStackDoc ) $
+ ud { ud_z_tail = env }
+
+markAllInsideLamIf, markAllNonTailIf :: HasDebugCallStack => Bool -> UsageDetails -> UsageDetails
markAllInsideLamIf True ud = markAllInsideLam ud
markAllInsideLamIf False ud = ud
@@ -3969,7 +3994,7 @@ adjustNonRecRhs mb_join_arity (WTUD (TUD rhs_ja uds) rhs)
where
exact_join = mb_join_arity == JoinPoint rhs_ja
-adjustTailUsage :: Bool -- True <=> Exactly-matching join point; don't do markNonTail
+adjustTailUsage :: HasDebugCallStack => Bool -- True <=> Exactly-matching join point; don't do markNonTail
-> CoreExpr -- Rhs usage, AFTER occAnalLamTail
-> UsageDetails
-> UsageDetails
@@ -3981,7 +4006,7 @@ adjustTailUsage exact_join rhs uds
where
one_shot = isOneShotFun rhs
-adjustTailArity :: JoinPointHood -> TailUsageDetails -> UsageDetails
+adjustTailArity :: HasDebugCallStack => JoinPointHood -> TailUsageDetails -> UsageDetails
adjustTailArity mb_rhs_ja (TUD ja usage)
= markAllNonTailIf (mb_rhs_ja /= JoinPoint ja) usage
@@ -4015,7 +4040,7 @@ tagNonRecBinder :: TopLevelFlag -- At top level?
-- Precondition: OccInfo is not IAmDead
tagNonRecBinder lvl occ bndr
| okForJoinPoint lvl bndr tail_call_info
- , AlwaysTailCalled ar <- tail_call_info
+ , AlwaysTailCalled ar _ <- tail_call_info
= (setBinderOcc occ bndr, JoinPoint ar)
| otherwise
= (setBinderOcc zapped_occ bndr, NotJoinPoint)
@@ -4102,7 +4127,7 @@ okForJoinPoint lvl bndr tail_call_info
= False
where
valid_join | NotTopLevel <- lvl
- , AlwaysTailCalled arity <- tail_call_info
+ , AlwaysTailCalled arity _ <- tail_call_info
, -- Invariant 1 as applied to LHSes of rules
all (ok_rule arity) (idCoreRules bndr)
@@ -4120,8 +4145,8 @@ okForJoinPoint lvl bndr tail_call_info
lost_join | JoinPoint ja <- idJoinPointHood bndr
= not valid_join ||
(case tail_call_info of -- Valid join but arity differs
- AlwaysTailCalled ja' -> ja /= ja'
- _ -> False)
+ AlwaysTailCalled ja' _ -> ja /= ja'
+ _ -> False)
| otherwise = False
ok_rule _ BuiltinRule{} = False -- only possible with plugin shenanigans
@@ -4143,7 +4168,7 @@ okForJoinPoint lvl bndr tail_call_info
, text "tc:" <+> ppr tail_call_info
, text "rules:" <+> ppr (idCoreRules bndr)
, case tail_call_info of
- AlwaysTailCalled arity ->
+ AlwaysTailCalled arity _ ->
vcat [ text "ok_unf:" <+> ppr (ok_unfolding arity (realIdUnfolding bndr))
, text "ok_type:" <+> ppr (isValidJoinPointType arity (idType bndr)) ]
_ -> empty ]
@@ -4206,6 +4231,6 @@ orLocalOcc (OneOccL { lo_n_br = nbr1, lo_int_cxt = int_cxt1, lo_tail = tci1 })
orLocalOcc occ1 occ2 = andLocalOcc occ1 occ2
andTailCallInfo :: TailCallInfo -> TailCallInfo -> TailCallInfo
-andTailCallInfo info@(AlwaysTailCalled arity1) (AlwaysTailCalled arity2)
- | arity1 == arity2 = info
+andTailCallInfo (AlwaysTailCalled arity1 p1) (AlwaysTailCalled arity2 p2)
+ | arity1 == arity2 = AlwaysTailCalled arity1 (max p1 p2)
andTailCallInfo _ _ = NoTailCallInfo
=====================================
compiler/GHC/Core/Opt/Simplify/Env.hs
=====================================
@@ -201,6 +201,8 @@ data SimplEnv
, seCaseDepth :: !Int -- Depth of multi-branch case alternatives
+ , seProfTicks :: !Int -- SLD TODO
+
, seInlineDepth :: !Int -- 0 initially, 1 when we inline an already-simplified
-- unfolding, and simplify again; and so on
-- See Note [Inline depth]
@@ -588,6 +590,7 @@ mkSimplEnv mode fam_envs
, seIdSubst = emptyVarEnv
, seRecIds = emptyUnVarSet
, seCaseDepth = 0
+ , seProfTicks = 0
, seInlineDepth = 0 }
-- The top level "enclosing CC" is "SUBSUMED".
=====================================
compiler/GHC/Core/Opt/Simplify/Iteration.hs
=====================================
@@ -39,7 +39,7 @@ import GHC.Core.Opt.Arity ( ArityType, exprArity, arityTypeBotSigs_maybe
, pushCoTyArg, pushCoValArg, exprIsDeadEnd
, typeArity, arityTypeArity, etaExpandAT )
import GHC.Core.SimpleOpt ( exprIsConApp_maybe, joinPointBinding_maybe, joinPointBindings_maybe )
-import GHC.Core.FVs ( mkRuleInfo {- exprsFreeIds -} )
+import GHC.Core.FVs ( mkRuleInfo )
import GHC.Core.Rules ( lookupRule, getRules )
import GHC.Core.Multiplicity
@@ -57,10 +57,11 @@ import GHC.Types.Unique ( hasKey )
import GHC.Types.Basic
import GHC.Types.Tickish
import GHC.Types.Var ( isTyCoVar )
+
import GHC.Builtin.Types.Prim( realWorldStatePrimTy )
import GHC.Builtin.Names( runRWKey, seqHashKey )
-import GHC.Data.Maybe ( isNothing, orElse, mapMaybe )
+import GHC.Data.Maybe ( isNothing, orElse, fromMaybe, mapMaybe )
import GHC.Data.FastString
import GHC.Unit.Module ( moduleName )
import GHC.Utils.Outputable
@@ -1442,7 +1443,10 @@ simplTick env tickish expr cont
no_floating_past_tick =
do { let (inc,outc) = splitCont cont
- ; (floats, expr1) <- simplExprF env expr inc
+ env' = case tickish of
+ ProfNote {} -> env { seProfTicks = seProfTicks env + 1 }
+ _ -> env
+ ; (floats, expr1) <- simplExprF env' expr inc
; let expr2 = wrapFloats floats expr1
tickish' = simplTickish env tickish
; rebuild env (mkTick tickish' expr2) outc
@@ -2051,8 +2055,8 @@ simplNonRecJoinPoint :: SimplEnv -> InId -> InExpr
-> InExpr -> SimplCont
-> SimplM (SimplFloats, OutExpr)
simplNonRecJoinPoint env bndr rhs body cont
- = assert (isJoinId bndr ) $
- wrapJoinCont env cont $ \ env cont ->
+ = assert (isJoinId bndr) $
+ wrapJoinCont do_case_case env cont $ \ env cont ->
do { -- We push join_cont into the join RHS and the body;
-- and wrap wrap_cont around the whole thing
; let mult = contHoleScaling cont
@@ -2062,14 +2066,19 @@ simplNonRecJoinPoint env bndr rhs body cont
; (floats1, env3) <- simplJoinBind NonRecursive cont (bndr,env) (bndr2,env2) (rhs,env)
; (floats2, body') <- simplExprF env3 body cont
; return (floats1 `addFloats` floats2, body') }
+ where
+ do_case_case
+ | Just occMaxProfTicks <- occursUnderProfTick (idOccInfo bndr)
+ , occMaxProfTicks > seProfTicks env
+ = False
+ | otherwise
+ = seCaseCase env
-
-------------------
simplRecJoinPoint :: SimplEnv -> [(InId, InExpr)]
-> InExpr -> SimplCont
-> SimplM (SimplFloats, OutExpr)
simplRecJoinPoint env pairs body cont
- = wrapJoinCont env cont $ \ env cont ->
+ = wrapJoinCont do_case_case env cont $ \ env cont ->
do { let bndrs = map fst pairs
mult = contHoleScaling cont
res_ty = contResultType cont
@@ -2079,30 +2088,38 @@ simplRecJoinPoint env pairs body cont
; (floats1, env2) <- simplRecBind env1 (BC_Join Recursive cont) pairs
; (floats2, body') <- simplExprF env2 body cont
; return (floats1 `addFloats` floats2, body') }
+ where
+ do_case_case
+ | any ((seProfTicks env <) . fromMaybe 0 . occursUnderProfTick . idOccInfo . fst) pairs
+ = False
+ | otherwise
+ = seCaseCase env
--------------------
-wrapJoinCont :: SimplEnv -> SimplCont
+wrapJoinCont :: Bool
+ -> SimplEnv -> SimplCont
-> (SimplEnv -> SimplCont -> SimplM (SimplFloats, OutExpr))
-> SimplM (SimplFloats, OutExpr)
-- Deal with making the continuation duplicable if necessary,
-- and with the no-case-of-case situation.
-wrapJoinCont env cont thing_inside
+wrapJoinCont do_case_case env cont thing_inside
| contIsStop cont -- Common case; no need for fancy footwork
= thing_inside env cont
- | not (seCaseCase env)
- -- See Note [Join points with -fno-case-of-case]
- = do { (floats1, expr1) <- thing_inside env (mkBoringStop (contHoleType cont))
- ; let (floats2, expr2) = wrapJoinFloatsX floats1 expr1
- ; (floats3, expr3) <- rebuild (env `setInScopeFromF` floats2) expr2 cont
- ; return (floats2 `addFloats` floats3, expr3) }
-
- | otherwise
- -- Normal case; see Note [Join points and case-of-case]
+ | do_case_case
+ -- Normal situation: do the "case-of-case" transformation.
+ -- See Note [Join points and case-of-case].
= do { (floats1, cont') <- mkDupableCont env cont
; (floats2, result) <- thing_inside (env `setInScopeFromF` floats1) cont'
; return (floats1 `addFloats` floats2, result) }
+ | otherwise
+ -- No "case-of-case" transformation.
+ -- See Note [Join points with -fno-case-of-case].
+ = do { (floats1, expr1) <- thing_inside env (mkBoringStop (contHoleType cont))
+ ; let (floats2, expr2) = wrapJoinFloatsX floats1 expr1
+ ; (floats3, expr3) <- rebuild (env `setInScopeFromF` floats2) expr2 cont
+ ; return (floats2 `addFloats` floats3, expr3) }
--------------------
trimJoinCont :: Id -- Used only in error message
@@ -2151,13 +2168,13 @@ evaluation context E):
As is evident from the example, there are two components to this behavior:
- 1. When entering the RHS of a join point, copy the context inside.
- 2. When a join point is invoked, discard the outer context.
+ (wrapJoinCont) When entering the RHS of a join point, copy the context inside.
+ (trimJoinCont) When a join point is invoked, discard the outer context.
We need to be very careful here to remain consistent---neither part is
optional!
-We need do make the continuation E duplicable (since we are duplicating it)
+We need to make the continuation E duplicable (since we are duplicating it)
with mkDupableCont.
@@ -2184,7 +2201,8 @@ case-of-case we may then end up with this totally bogus result
This would be OK in the language of the paper, but not in GHC: j is no longer
a join point. We can only do the "push continuation into the RHS of the
join point j" if we also push the continuation right down to the /jumps/ to
-j, so that it can evaporate there. If we are doing case-of-case, we'll get to
+j, so that it can evaporate there (trimJoinCont). Then, if we are doing
+case-of-case, we'll get to
join x = case <j-rhs> of <outer-alts> in
case y of
=====================================
compiler/GHC/Core/SimpleOpt.hs
=====================================
@@ -1076,7 +1076,7 @@ joinPointBinding_maybe bndr rhs
| isJoinId bndr
= Just (bndr, rhs)
- | AlwaysTailCalled join_arity <- tailCallInfo (idOccInfo bndr)
+ | AlwaysTailCalled join_arity _ <- tailCallInfo (idOccInfo bndr)
, (bndrs, body) <- etaExpandToJoinPoint join_arity rhs
, let str_sig = idDmdSig bndr
str_arity = count isId bndrs -- Strictness demands are for Ids only
=====================================
compiler/GHC/Core/Utils.hs
=====================================
@@ -1977,7 +1977,7 @@ altsAreExhaustive (Alt con1 _ _ : alts)
-- Takes the function we are applying as argument.
etaExpansionTick :: Id -> GenTickish pass -> Bool
etaExpansionTick id t
- = hasNoBinding id &&
+ = ( hasNoBinding id || isJoinId id ) && -- SLD TODO
( tickishFloatable t || isProfTick t )
{- Note [exprOkForSpeculation and type classes]
=====================================
compiler/GHC/CoreToStg/Prep.hs
=====================================
@@ -1130,7 +1130,10 @@ cpeApp top_env expr
hd = getIdFromTrivialExpr_maybe e2
-- Determine number of required arguments. See Note [Ticks and mandatory eta expansion]
min_arity = case hd of
- Just v_hd -> if hasNoBinding v_hd then Just $! (idArity v_hd) else Nothing
+ Just v_hd ->
+ if hasNoBinding v_hd || isJoinId v_hd -- SLD TODO (re-use cantEtaReduceFun?)
+ then Just $! idArity v_hd
+ else Nothing
Nothing -> Nothing
-- ; pprTraceM "cpe_app:stricts:" (ppr v <+> ppr args $$ ppr stricts $$ ppr (idCbvMarks_maybe v))
; (app, floats, unsat_ticks) <- rebuild_app env args e2 emptyFloats stricts min_arity
=====================================
compiler/GHC/Types/Basic.hs
=====================================
@@ -70,7 +70,7 @@ module GHC.Types.Basic (
BranchCount, oneBranch,
InterestingCxt(..),
TailCallInfo(..), tailCallInfo, zapOccTailCallInfo,
- isAlwaysTailCalled,
+ isAlwaysTailCalled, occursUnderProfTick,
EP(..),
@@ -1150,7 +1150,7 @@ instance Monoid InsideLam where
-----------------
data TailCallInfo
- = AlwaysTailCalled {-# UNPACK #-} !JoinArity -- See Note [TailCallInfo]
+ = AlwaysTailCalled {-# UNPACK #-} !JoinArity !Int-- See Note [TailCallInfo]
| NoTailCallInfo
deriving (Eq)
@@ -1167,9 +1167,15 @@ isAlwaysTailCalled occ
= case tailCallInfo occ of AlwaysTailCalled{} -> True
NoTailCallInfo -> False
+occursUnderProfTick :: OccInfo -> Maybe Int
+occursUnderProfTick occ =
+ case tailCallInfo occ of
+ AlwaysTailCalled _ b -> Just b
+ NoTailCallInfo -> Nothing
+
instance Outputable TailCallInfo where
- ppr (AlwaysTailCalled ar) = sep [ text "Tail", int ar ]
- ppr _ = empty
+ ppr (AlwaysTailCalled ar b) = sep [ text "Tail", brackets (int b), int ar ]
+ ppr _ = text "NoTailCallInfo" --empty
-----------------
strongLoopBreaker, weakLoopBreaker :: OccInfo
@@ -1217,7 +1223,8 @@ instance Outputable OccInfo where
pp_tail = pprShortTailCallInfo tail_info
pprShortTailCallInfo :: TailCallInfo -> SDoc
-pprShortTailCallInfo (AlwaysTailCalled ar) = char 'T' <> brackets (int ar)
+pprShortTailCallInfo (AlwaysTailCalled ar p)
+ = char 'T' <> (brackets (text "P" <+> int p)) <> brackets (int ar)
pprShortTailCallInfo NoTailCallInfo = empty
{-
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8b8e2154801f619b716b9e46e69c65b…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8b8e2154801f619b716b9e46e69c65b…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/romes/hadrian-cross-stage2-rebase_SVEN_FINAL] Always refer to default.host.target for the host's Target
by Sven Tennie (@supersven) 10 Jan '26
by Sven Tennie (@supersven) 10 Jan '26
10 Jan '26
Sven Tennie pushed to branch wip/romes/hadrian-cross-stage2-rebase_SVEN_FINAL at Glasgow Haskell Compiler / GHC
Commits:
10c94ce9 by Sven Tennie at 2026-01-10T13:11:39+01:00
Always refer to default.host.target for the host's Target
Otherwise, arguments get messed and mixed up.
- - - - -
1 changed file:
- hadrian/src/Hadrian/Oracles/TextFile.hs
Changes:
=====================================
hadrian/src/Hadrian/Oracles/TextFile.hs
=====================================
@@ -125,18 +125,7 @@ getBuildTarget = getTargetConfig buildTargetFile
-- | Get the host target configuration through 'getTargetConfig'
getHostTarget :: Action Toolchain.Target
-getHostTarget = do
- -- MP: If we are not cross compiling then we should use the target file in order to
- -- build things for the host, in particular we want to use the configured values for the
- -- target for building the RTS (ie are we using Libffi for adjustors, and the wordsize)
- -- TODO: Use "flag CrossCompiling"
- ht <- getTargetConfig hostTargetFile
- tt <- getTargetConfig targetTargetFile
- if (Toolchain.targetPlatformTriple ht) == (Toolchain.targetPlatformTriple tt)
- then return tt
- else return ht
- -- where
- -- msg = "The host's target configuration file " ++ quote hostTargetFile ++ " does not exist! ghc-toolchain might have failed to generate it."
+getHostTarget = getTargetConfig hostTargetFile
-- | Get the target target configuration through 'getTargetConfig'
getTargetTarget :: Action Toolchain.Target
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/10c94ce97d7f875b3b0865beecd80eb…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/10c94ce97d7f875b3b0865beecd80eb…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/andreask/ticked_joins] 256 commits: Add a perf test for #26425
by sheaf (@sheaf) 10 Jan '26
by sheaf (@sheaf) 10 Jan '26
10 Jan '26
sheaf pushed to branch wip/andreask/ticked_joins at Glasgow Haskell Compiler / GHC
Commits:
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.
- - - - -
4038a28b by Andreas Klebinger at 2025-10-30T12:38:52-04:00
Add a perf test for #26425
- - - - -
f997618e by Andreas Klebinger at 2025-10-30T12:38:52-04:00
OccAnal: Be stricter for better compiler perf.
In particular we are now stricter:
* When combining usageDetails.
* When computing binder info.
In combineUsageDetails when combining the underlying adds we compute a
new `LocalOcc` for each entry by combining the two existing ones.
Rather than wait for those entries to be forced down the road we now
force them immediately. Speeding up T26425 by about 10% with little
effect on the common case.
We also force binders we put into the Core AST everywhere now.
Failure to do so risks leaking the occ env used to set the binders
OccInfo.
For T26425 compiler residency went down by a factor of ~10x.
Compile time also improved by a factor of ~1.6.
-------------------------
Metric Decrease:
T18698a
T26425
T9233
-------------------------
- - - - -
5618645b by Vladislav Zavialov at 2025-10-30T12:39:33-04:00
Fix namespace specifiers in subordinate exports (#12488)
This patch fixes an oversight in the `lookupChildrenExport` function that
caused explicit namespace specifiers of subordinate export items to be
ignored:
module M (T (type A)) where -- should be rejected
data T = A
Based on the `IEWrappedName` data type, there are 5 cases to consider:
1. Unadorned name: P(X)
2. Named default: P(default X)
3. Pattern synonym: P(pattern X)
4. Type name: P(type X)
5. Data name: P(data X)
Case 1 is already handled correctly; cases 2 and 3 are parse errors; and
it is cases 4 and 5 that we are concerned with in this patch.
Following the precedent established in `LookupExactName`, we introduce
a boolean flag in `LookupChildren` to control whether to look up in all
namespaces or in a specific one. If an export item is accompanied by an
explicit namespace specifier `type` or `data`, we restrict the lookup in
`lookupGRE` to a specific namespace.
The newly introduced diagnostic `TcRnExportedSubordinateNotFound`
provides error messages and suggestions more tailored to this context
than the previously used `reportUnboundName`.
- - - - -
f75ab223 by Peter Trommler at 2025-10-31T18:43:13-04:00
ghc-toolchain: detect PowerPC 64 bit ABI
Check preprocessor macro defined for ABI v2 and assume v1 otherwise.
Fixes #26521
- - - - -
d086c474 by Peter Trommler at 2025-10-31T18:43:13-04:00
ghc-toolchain: refactor, move lastLine to Utils
- - - - -
995dfe0d by Vladislav Zavialov at 2025-10-31T18:43:54-04:00
Tests for -Wduplicate-exports, -Wdodgy-exports
Add test cases for the previously untested diagnostics:
[GHC-51876] TcRnDupeModuleExport
[GHC-64649] TcRnNullExportedModule
This also revealed a typo (incorrect capitalization of "module") in the
warning text for TcRnDupeModuleExport, which is now fixed.
- - - - -
f6961b02 by Cheng Shao at 2025-11-01T00:08:01+01:00
wasm: reformat dyld source code
This commit reformats dyld source code with prettier, to avoid
introducing unnecessary diffs in subsequent patches when they're
formatted before committing.
- - - - -
0c9032a0 by Cheng Shao at 2025-11-01T00:08:01+01:00
wasm: simplify _initialize logic in dyld
This commit simplifies how we _initialize a wasm shared library in
dyld and removes special treatment for libc.so, see added comment for
detailed explanation.
- - - - -
ec1b40bd by Cheng Shao at 2025-11-01T00:08:01+01:00
wasm: support running dyld fully client side in the browser
This commit refactors the wasm dyld script so that it can be used to
load and run wasm shared libraries fully client-side in the browser
without needing a wasm32-wasi-ghci backend:
- A new `DyLDBrowserHost` class is exported, which runs in the browser
and uses the in-memory vfs without any RPC calls. This meant to be
used to create a `rpc` object for the fully client side use cases.
- The exported `main` function now can be used to load user-specified
shared libraries, and the user can use the returned `DyLD` instance
to run their own exported Haskell functions.
- The in-browser wasi implementation is switched to
https://github.com/haskell-wasm/browser_wasi_shim for bugfixes and
major performance improvements not landed upstream yet.
- When being run by deno, it now correctly switches to non-nodejs code
paths, so it's more convenient to test dyld logic with deno.
See added comments for details, as well as the added `playground001`
test case for an example of using it to build an in-browser Haskell
playground.
- - - - -
8f3e481f by Cheng Shao at 2025-11-01T00:08:01+01:00
testsuite: add playground001 to test haskell playground
This commit adds the playground001 test case to test the haskell
playground in browser, see comments for details.
- - - - -
af40606a by Cheng Shao at 2025-11-01T00:08:04+01:00
Revert "testsuite: add T26431 test case"
This reverts commit 695036686f8c6d78611edf3ed627608d94def6b7. T26431
is now retired, wasm ghc internal-interpreter logic is tested by
playground001.
- - - - -
86c82745 by Vladislav Zavialov at 2025-11-01T07:24:29-04:00
Supplant TcRnExportHiddenComponents with TcRnDodgyExports (#26534)
Remove a bogus special case in lookup_ie_kids_all,
making TcRnExportHiddenComponents obsolete.
- - - - -
fcf6331e by Richard Eisenberg at 2025-11-03T08:33:05+00:00
Refactor fundep solving
This commit is a large-scale refactor of the increasingly-messy code that
handles functional dependencies. It has virtually no effect on what compiles
but improves error messages a bit. And it does the groundwork for #23162.
The big picture is described in
Note [Overview of functional dependencies in type inference]
in GHC.Tc.Solver.FunDeps
* New module GHC.Tc.Solver.FunDeps contains all the fundep-handling
code for the constraint solver.
* Fundep-equalities are solved in a nested scope; they may generate
unifications but otherwise have no other effect.
See GHC.Tc.Solver.FunDeps.solveFunDeps
The nested needs to start from the Givens in the inert set, but
not the Wanteds; hence a new function `resetInertCans`, used in
`nestFunDepsTcS`.
* That in turn means that fundep equalities never show up in error
messages, so the complicated FunDepOrigin tracking can all disappear.
* We need to be careful about tracking unifications, so we kick out
constraints from the inert set after doing unifications. Unification
tracking has been majorly reformed: see Note [WhatUnifications] in
GHC.Tc.Utils.Unify.
A good consequence is that the hard-to-grok `resetUnificationFlag`
has been replaced with a simpler use of
`reportCoarseGrainUnifications`
Smaller things:
* Rename `FunDepEqn` to `FunDepEqns` since it contains multiple
type equalities.
Some compile time improvement
Metrics: compile_time/bytes allocated
Baseline
Test value New value Change
---------------------- --------------------------------------
T5030(normal) 173,839,232 148,115,248 -14.8% GOOD
hard_hole_fits(normal) 286,768,048 284,015,416 -1.0%
geo. mean -0.2%
minimum -14.8%
maximum +0.3%
Metric Decrease:
T5030
- - - - -
231adc30 by Simon Peyton Jones at 2025-11-03T08:33:05+00:00
QuickLook's tcInstFun should make instantiation variables directly
tcInstFun must make "instantiation variables", not regular
unification variables, when instantiating function types. That was
previously implemented by a hack: set the /ambient/ level to QLInstTyVar.
But the hack finally bit me, when I was refactoring WhatUnifications.
And it was always wrong: see the now-expunged (TCAPP2) note.
This commit does it right, by making tcInstFun call its own
instantiation functions. That entails a small bit of duplication,
but the result is much, much cleaner.
- - - - -
39d4a24b by Simon Peyton Jones at 2025-11-03T08:33:05+00:00
Build implication for constraints from (static e)
This commit addresses #26466, by buiding an implication for the
constraints arising from a (static e) form. The implication has
a special ic_info field of StaticFormSkol, which tells the constraint
solver to use an empty set of Givens.
See (SF3) in Note [Grand plan for static forms]
in GHC.Iface.Tidy.StaticPtrTable
This commit also reinstates an `assert` in GHC.Tc.Solver.Equality.
The test `StaticPtrTypeFamily` was failing with an assertion failure,
but it now works.
- - - - -
2e2aec1e by Simon Peyton Jones at 2025-11-03T08:33:05+00:00
Comments about defaulting representation equalities
- - - - -
52a4d1da by Simon Peyton Jones at 2025-11-03T08:33:05+00:00
Improve tracking of rewriter-sets
This refactor substantially improves the treatment of so-called
"rewriter-sets" in the constraint solver.
The story is described in the rewritten
Note [Wanteds rewrite Wanteds: rewriter-sets]
in GHC.Tc.Types.Constraint
Some highlights
* Trace the free coercion holes of a filled CoercionHole,
in CoercionPlusHoles. See Note [Coercion holes] (COH5)
This avoids taking having to take the free coercion variables
of a coercion when zonking a rewrriter-set
* Many knock on changes
* Make fillCoercionHole take CoercionPlusHoles as its argument
rather than to separate arguments.
* Similarly setEqIfWanted, setWantedE, wrapUnifierAndEmit.
* Be more careful about passing the correct CoHoleSet to
`rewriteEqEvidence` and friends
* Make kickOurAfterFillingCoercionHole more clever. See
new Note [Kick out after filling a coercion hole]
Smaller matters
* Rename RewriterSet to CoHoleSet
* Add special-case helper `rewriteEqEvidenceSwapOnly`
- - - - -
3e78e1ba by Simon Peyton Jones at 2025-11-03T08:33:05+00:00
Tidy up constraint solving for foralls
* In `can_eq_nc_forall` make sure to track Givens that are used
in the nested solve step.
* Tiny missing-swap bug-fix in `lookup_eq_in_qcis`
* Fix some leftover mess from
commit 14123ee646f2b9738a917b7cec30f9d3941c13de
Author: Simon Peyton Jones <simon.peytonjones(a)gmail.com>
Date: Wed Aug 20 00:35:48 2025 +0100
Solve forall-constraints via an implication, again
Specifically, trySolveImplication is now dead.
- - - - -
973f2c25 by Simon Peyton Jones at 2025-11-03T08:33:05+00:00
Do not treat CoercionHoles as free variables in coercions
This fixes a long-standing wart in the free-variable finder;
now CoercionHoles are no longer treated as a "free variable"
of a coercion.
I got big and unexpected performance regressions when making
this change. Turned out that CallArity didn't discover that
the free variable finder could be eta-expanded, which gave very
poor code.
So I re-used Note [The one-shot state monad trick] for Endo,
resulting in GHC.Utils.EndoOS. Very simple, big win.
- - - - -
c2b8a0f9 by Simon Peyton Jones at 2025-11-03T08:33:05+00:00
Update debug-tracing in CallArity
No effect on behaviour, and commented out anyway
- - - - -
9aa5ee99 by Simon Peyton Jones at 2025-11-03T08:33:28+00:00
Comments only -- remove dangling Note references
- - - - -
6683f183 by Simon Peyton Jones at 2025-11-03T08:33:28+00:00
Accept error message wibbles
- - - - -
3ba3d9f9 by Luite Stegeman at 2025-11-04T00:59:41-05:00
rts: fix eager black holes: record mutated closure and fix assertion
This fixes two problems with handling eager black holes, introduced
by a1de535f762bc23d4cf23a5b1853591dda12cdc9.
- the closure mutation must be recorded even for eager black holes,
since the mutator has mutated it before calling threadPaused
- The assertion that an unmarked eager black hole must be owned by
the TSO calling threadPaused is incorrect, since multiple threads
can race to claim the black hole.
fixes #26495
- - - - -
b5508f2c by Rodrigo Mesquita at 2025-11-04T14:10:56+00:00
build: Relax ghc/ghc-boot Cabal bound to 3.16
Fixes #26202
- - - - -
c5b3541f by Rodrigo Mesquita at 2025-11-04T14:10:56+00:00
cabal-reinstall: Use haddock-api +in-tree-ghc
Fixes #26202
- - - - -
c6d4b945 by Rodrigo Mesquita at 2025-11-04T14:10:56+00:00
cabal-reinstall: Pass --strict to Happy
This is necessary to make the generated Parser build successfully
This mimics Hadrian, which always passes --strict to happy.
Fixes #26202
- - - - -
79df1e0e by Rodrigo Mesquita at 2025-11-04T14:10:56+00:00
genprimopcode: Require higher happy version
I've bumped the happy version to forbid deprecated Happy versions which
don't successfully compile.
- - - - -
fa5d33de by Simon Peyton Jones at 2025-11-05T08:35:40-05:00
Add a HsWrapper optimiser
This MR addresses #26349, by introduceing optSubTypeHsWrapper.
There is a long
Note [Deep subsumption and WpSubType]
in GHC.Tc.Types.Evidence that explains what is going on.
- - - - -
ea58cae5 by Simon Peyton Jones at 2025-11-05T08:35:40-05:00
Improve mkWpFun_FRR
This commit ensures that `mkWpFun_FRR` directly produces a `FunCo` in
the cases where it can.
(Previously called `mkWpFun` which in turn optimised to a `FunCo`, but
that made the smarts in `mkWpFun` /essential/ rather than (as they
should be) optional.
- - - - -
5cdcfaed by Ben Gamari at 2025-11-06T09:01:36-05:00
compiler: Exclude units with no exposed modules from unused package check
Such packages cannot be "used" in the Haskell sense of the word yet
are nevertheless necessary as they may provide, e.g., C object code or
link flags.
Fixes #24120.
- - - - -
74b8397a by Brandon Chinn at 2025-11-06T09:02:19-05:00
Replace deprecated argparse.FileType
- - - - -
36ddf988 by Ben Gamari at 2025-11-06T09:03:01-05:00
Bump unix submodule to 2.8.8.0
Closes #26474.
- - - - -
c32b3a29 by fendor at 2025-11-06T09:03:43-05:00
Fix assertion in `postStringLen` to account for \0 byte
We fix the assertion to handle trailing \0 bytes in `postStringLen`.
Before this change, the assertion looked like this:
ASSERT(eb->begin + eb->size > eb->pos + len + 1);
Let's assume some values to see why this is actually off by one:
eb->begin = 0
eb->size = 1
eb->pos = 0
len = 1
then the assertion would trigger correctly:
0 + 1 > 0 + 1 + 1 => 1 > 2 => false
as there is not enough space for the \0 byte (which is the trailing +1).
However, if we change `eb->size = 2`, then we do have enough space for a
string of length 1, but the assertion still fails:
0 + 2 > 0 + 1 + 1 => 2 > 2 => false
Which causes the assertion to fail if there is exactly enough space for
the string with a trailing \0 byte.
Clearly, the assertion should be `>=`!
If we switch around the operand, it should become more obvious that `<=`
is the correct comparison:
ASSERT(eb->pos + len + 1 <= eb->begin + eb->size);
This is expresses more naturally that the current position plus the
length of the string (and the null byte) must be smaller or equal to the
overall size of the buffer.
This change also is in line with the implementation in
`hasRoomForEvent` and `hasRoomForVariableEvent`:
```
StgBool hasRoomForEvent(EventsBuf *eb, EventTypeNum eNum)
{
uint32_t size = ...;
if (eb->pos + size > eb->begin + eb->size)
...
```
the check `eb->pos + size > eb->begin + eb->size` is identical to
`eb->pos + size <= eb->begin + eb->size` plus a negation.
- - - - -
3034a6f2 by Ben Gamari at 2025-11-06T09:04:24-05:00
Bump os-string submodule to 2.0.8
- - - - -
39567e85 by Cheng Shao at 2025-11-06T09:05:06-05:00
rts: use computed goto for instruction dispatch in the bytecode interpreter
This patch uses computed goto for instruction dispatch in the bytecode
interpreter. Previously instruction dispatch is done by a classic
switch loop, so executing the next instruction requires two jumps: one
to the start of the switch loop and another to the case block based on
the instruction tag. By using computed goto, we can build a jump table
consisted of code addresses indexed by the instruction tags
themselves, so executing the next instruction requires only one jump,
to the destination directly fetched from the jump table.
Closes #12953.
- - - - -
93fc7265 by sheaf at 2025-11-06T21:33:24-05:00
Correct hasFixedRuntimeRep in matchExpectedFunTys
This commit fixes a bug in the representation-polymormorphism check in
GHC.Tc.Utils.Unify.matchExpectedFunTys. The problem was that we put
the coercion resulting from hasFixedRuntimeRep in the wrong place,
leading to the Core Lint error reported in #26528.
The change is that we have to be careful when using 'mkWpFun': it
expects **both** the expected and actual argument types to have a
syntactically fixed RuntimeRep, as explained in Note [WpFun-FRR-INVARIANT]
in GHC.Tc.Types.Evidence.
On the way, this patch improves some of the commentary relating to
other usages of 'mkWpFun' in the compiler, in particular in the view
pattern case of 'tc_pat'. No functional changes, but some stylistic
changes to make the code more readable, and make it easier to understand
how we are upholding the WpFun-FRR-INVARIANT.
Fixes #26528
- - - - -
c052c724 by Simon Peyton Jones at 2025-11-06T21:34:06-05:00
Fix a horrible shadowing bug in implicit parameters
Fixes #26451. The change is in GHC.Tc.Solver.Monad.updInertDicts
where we now do /not/ delete /Wanted/ implicit-parameeter constraints.
This bug has been in GHC since 9.8! But it's quite hard to provoke;
I contructed a tests in T26451, but it was hard to do so.
- - - - -
b253013e by Georgios Karachalias at 2025-11-07T17:21:57-05:00
Remove the `CoreBindings` constructor from `LinkablePart`
Adjust HscRecompStatus to disallow unhydrated WholeCoreBindings
from being passed as input to getLinkDeps (which would previously
panic in this case).
Fixes #26497
- - - - -
ac7b737e by Sylvain Henry at 2025-11-07T17:22:51-05:00
Testsuite: pass ext-interp test way (#26552)
Note that some tests are still marked as broken with the ext-interp way
(see #26552 and #14335)
- - - - -
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>
- - - - -
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.
- - - - -
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.
- - - - -
0a64a78b by Sven Tennie at 2025-11-15T20:31:10-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.)
- - - - -
15b311be by sheaf at 2025-11-15T20:32:02-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).
- - - - -
b33284c7 by sheaf at 2025-11-15T20:32:02-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
-------------------------
- - - - -
b6faf5d0 by sheaf at 2025-11-15T20:32:02-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.
- - - - -
682bf979 by Mike Pilgrem at 2025-11-16T16:44:14+00:00
Fix #26293 Valid stack.yaml for hadrian
- - - - -
acc70c3a by Simon Peyton Jones at 2025-11-18T16:21:20-05:00
Fix a bug in defaulting
Addresses #26582
Defaulting was doing some unification but then failing to
iterate. Silly.
I discovered that the main solver was unnecessarily iterating even
if there was a unification for an /outer/ unification variable, so
I fixed that too.
- - - - -
c12fa73e by Simon Peyton Jones at 2025-11-19T02:55:01-05:00
Make PmLit be in Ord, and use it in Map
This MR addresses #26514, by changing from
data PmAltConSet = PACS !(UniqDSet ConLike) ![PmLit]
to
data PmAltConSet = PACS !(UniqDSet ConLike) !(Map PmLit PmLit)
This matters when doing pattern-match overlap checking, when there
is a very large set of patterns. For most programs it makes
no difference at all.
For the N=5000 case of the repro case in #26514, compiler
mutator time (with `-fno-code`) goes from 1.9s to 0.43s.
All for the price for an Ord instance for PmLit
- - - - -
41b84f40 by sheaf at 2025-11-19T02:55:52-05:00
Add passing tests for #26311 and #26072
This commit adds two tests cases that now pass since landing the changes
to typechecking of data constructors in b33284c7.
Fixes #26072 #26311
- - - - -
1faa758a by sheaf at 2025-11-19T02:55:52-05:00
mkCast: weaken bad cast warning for multiplicity
This commit weakens the warning message emitted when constructing a bad
cast in mkCast to ignore multiplicity.
Justification: since b33284c7, GHC uses sub-multiplicity coercions to
typecheck data constructors. The coercion optimiser is free to discard
these coercions, both for performance reasons, and because GHC's Core
simplifier does not (yet) preserve linearity.
We thus weaken 'mkCast' to use 'eqTypeIgnoringMultiplicity' instead of
'eqType', to avoid getting many spurious warnings about mismatched
multiplicities.
- - - - -
55eab80d by Sylvain Henry at 2025-11-20T17:33:13-05:00
Build external interpreter program on demand (#24731)
This patch teaches GHC how to build the external interpreter program
when it is missing. As long as we have the `ghci` library, doing this is
trivial so most of this patch is refactoring for doing it sanely.
- - - - -
08bbc028 by Rodrigo Mesquita at 2025-11-20T17:33:54-05:00
Add tests for #23973 and #26565
These were fixed by 4af4f0f070f83f948e49ad5d7835fd91b8d3f0e6 in !10417
- - - - -
6b42232c by sheaf at 2025-11-20T17:34:35-05:00
Mark T26410_ffi as fragile on Windows
As seen in #26595, this test intermittently fails on Windows.
This commit marks it as fragile, until we get around to fixing it.
- - - - -
b7b7c049 by Andrew Lelechenko at 2025-11-21T21:04:01+00:00
Add nubOrd / nubOrdBy to Data.List and Data.List.NonEmpty
As per https://github.com/haskell/core-libraries-committee/issues/336
- - - - -
352d5462 by Marc Scholten at 2025-11-22T10:33:03-05:00
Fix haddock test runner to handle UTF-8 output
xhtml 3000.4.0.0 now produces UTF-8 output instead of escaping non-ASCII characters.
When using --test-accept it previously wrote files in the wrong encoding
because they have not been decoded properly when reading the files.
- - - - -
48a3ed57 by Simon Peyton Jones at 2025-11-25T15:33:54+00:00
Add a fast-path for args=[] to occAnalApp
In the common case of having not arguments, occAnalApp
was doing redundant work.
- - - - -
951e5ed9 by Simon Peyton Jones at 2025-11-25T15:33:54+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
- - - - -
f1959dfc by Simon Peyton Jones at 2025-11-26T11:58:07+00:00
Remove a quadratic-cost assertion check in mkCoreApp
See the new Note [Assertion checking in mkCoreApp]
- - - - -
98fa0d36 by Simon Hengel at 2025-11-27T17:54:57-05:00
Fix typo in docs/users_guide/exts/type_families.rst
- - - - -
5b97e5ce by Simon Hengel at 2025-11-27T17:55:37-05:00
Fix broken RankNTypes example in user's guide
- - - - -
fa2aaa00 by Simon Peyton Jones at 2025-11-27T17:56:18-05:00
Switch off specialisation in ExactPrint
In !15057 (where we re-introduced -fpolymoprhic-specialisation) we found
that ExactPrint's compile time blew up by a factor of 5. It turned out
to be caused by bazillions of specialisations of `markAnnotated`.
Since ExactPrint isn't perf-critical, it does not seem worth taking
the performance hit, so this patch switches off specialisation in
this one module.
- - - - -
1fd25987 by Simon Peyton Jones at 2025-11-27T17:56:18-05:00
Switch -fpolymorphic-specialisation on by default
This patch addresses #23559.
Now that !10479 has landed and #26329 is fixed, we can switch on
polymorphic specialisation by default, addressing a bunch of other
tickets listed in #23559.
Metric changes:
* CoOpt_Singleton: +4% compiler allocations: we just get more
specialisations
* info_table_map_perf: -20% decrease in compiler allocations.
This is caused by using -fno-specialise in ExactPrint.hs
Without that change we get a 4x blow-up in compile time;
see !15058 for details
Metric Decrease:
info_table_map_perf
Metric Increase:
CoOpt_Singletons
- - - - -
b7fe7445 by Matthew Pickering at 2025-11-27T17:56:59-05:00
rts: Fix a deadlock with eventlog flush interval and RTS shutdown
The ghc_ticker thread attempts to flush at the eventlog tick interval, this requires
waiting to take all capabilities.
At the same time, the main thread is shutting down, the schedule is
stopped and then we wait for the ticker thread to finish.
Therefore we are deadlocked.
The solution is to use `newBoundTask/exitMyTask`, so that flushing can
cooperate with the scheduler shutdown.
Fixes #26573
- - - - -
1d4a1229 by sheaf at 2025-11-27T17:58:02-05:00
SimpleOpt: don't subst in pushCoercionIntoLambda
It was noticed in #26589 that the change in 15b311be was incorrect:
the simple optimiser carries two different substitution-like pieces of
information: 'soe_subst' (from InVar to OutExpr) and 'soe_inl'
(from InId to InExpr). It is thus incorrect to have 'pushCoercionIntoLambda'
apply the substitution from 'soe_subst' while discarding 'soe_inl'
entirely, which is what was done in 15b311be.
Instead, we change back pushCoercionIntoLambda to take an InScopeSet,
and optimise the lambda before calling 'pushCoercionIntoLambda' to avoid
mixing InExpr with OutExpr, or mixing two InExpr with different
environments. We can then call 'soeZapSubst' without problems.
Fixes #26588 #26589
- - - - -
84a087d5 by Sylvain Henry at 2025-11-28T17:35:28-05:00
Fix PIC jump tables on Windows (#24016)
Avoid overflows in jump tables by using a base label closer to the jump
targets. See added Note [Jump tables]
- - - - -
82db7042 by Zubin Duggal at 2025-11-28T17:36:10-05:00
rts/linker/PEi386: Copy strings before they are inserted into LoadedDllCache. The original strings are temporary and might be freed at an arbitrary point.
Fixes #26613
- - - - -
ff3f0d09 by Ben Gamari at 2025-11-29T18:34:28-05:00
gitlab-ci: Run ghcup-metadata jobs on OpenCape runners
This significantly reduces our egress traffic
and makes the jobs significantly faster.
- - - - -
ef0dc33b by Matthew Pickering at 2025-11-29T18:35:10-05:00
Use 'OsPath' in getModificationTimeIfExists
This part of the compiler is quite hot during recompilation checking in
particular since the filepaths will be translated to a string. It is
better to use the 'OsPath' native function, which turns out to be easy
to do.
- - - - -
fa3bd0a6 by Georgios Karachalias at 2025-11-29T18:36:05-05:00
Use OsPath in PkgDbRef and UnitDatabase, not FilePath
- - - - -
0d7c05ec by Ben Gamari at 2025-12-01T03:13:46-05:00
hadrian: Place user options after package arguments
This makes it easier for the user to override the default package
arguments with `UserSettings.hs`.
Fixes #25821.
-------------------------
Metric Decrease:
T14697
-------------------------
- - - - -
3b2c4598 by Vladislav Zavialov at 2025-12-01T03:14:29-05:00
Namespace-specified wildcards in import/export lists (#25901)
This change adds support for top-level namespace-specified wildcards
`type ..` and `data ..` to import and export lists.
Examples:
import M (type ..) -- imports all type and class constructors from M
import M (data ..) -- imports all data constructors and terms from M
module M (type .., f) where
-- exports all type and class constructors defined in M,
-- plus the function 'f'
The primary intended usage of this feature is in combination with module
aliases, allowing namespace disambiguation:
import Data.Proxy as T (type ..) -- T.Proxy is unambiguously the type constructor
import Data.Proxy as D (data ..) -- D.Proxy is unambiguously the data constructor
The patch accounts for the interactions of wildcards with:
* Imports with `hiding` clauses
* Import warnings -Wunused-imports, -Wdodgy-imports
* Export warnings -Wduplicate-exports, -Wdodgy-exports
Summary of the changes:
1. Move the NamespaceSpecifier type from GHC.Hs.Binds to GHC.Hs.Basic,
making it possible to use it in more places in the AST.
2. Extend the AST (type: IE) with a representation of `..`, `type ..`,
and `data ..` (constructor: IEWholeNamespace). Per the proposal, the
plain `..` is always rejected with a dedicated error message.
3. Extend the grammar in Parser.y with productions for `..`, `type ..`,
and `data ..` in both import and export lists.
4. Implement wildcard imports by updating the `filterImports` function
in GHC.Rename.Names; the logic for IEWholeNamespace is roughly
modeled after the Nothing (no explicit import list) case.
5. Implement wildcard exports by updating the `exports_from_avail`
function in GHC.Tc.Gen.Export; the logic for IEWholeNamespace is
closely modeled after the IEModuleContents case.
6. Refactor and extend diagnostics to report the new warnings and
errors. See PsErrPlainWildcardImport, DodgyImportsWildcard,
PsErrPlainWildcardExport, DodgyExportsWildcard,
TcRnDupeWildcardExport.
Note that this patch is specifically about top-level import/export
items. Subordinate import/export items are left unchanged.
- - - - -
c71faa76 by Luite Stegeman at 2025-12-01T03:16:05-05:00
rts: Handle overflow of ELF section header string table
If the section header string table is stored in a section greater
than or equal to SHN_LORESERVE (0xff00), the 16-bit field e_shstrndx
in the ELF header does not contain the section number, but rather
an overflow value SHN_XINDEX (0xffff) indicating that we need to look
elsewhere.
This fixes the linker by not using e_shstrndx directly but calling
elf_shstrndx, which correctly handles the SHN_XINDEX value.
Fixes #26603
- - - - -
ab20eb54 by Mike Pilgrem at 2025-12-01T22:46:55+00:00
Re CLC issue 292 Warn GHC.Internal.List.{init,last} are partial
Also corrects the warning for `tail` to refer to `Data.List.uncons` (like the existing warning for `head`).
In module `Settings.Warnings`, applies `-Wno-x-partial` to the `filepath`, and `parsec` packages (outside GHC's repository).
Also bumps submodules.
- - - - -
fc1d7f79 by Jade Lovelace at 2025-12-02T11:04:09-05:00
docs: fix StandaloneKindSignatures in DataKinds docs
These should be `type` as otherwise GHC reports a duplicate definition
error.
- - - - -
beae879b by Rodrigo Mesquita at 2025-12-03T15:42:37+01:00
task: Substitute some datatypes for newtypes
* Substitutes some data type declarations for newtype declarations
* Adds comment to `LlvmConfigCache`, which must decidedly not be a
newtype.
Fixes #23555
- - - - -
3bd7dd44 by mangoiv at 2025-12-04T04:36:45-05:00
Renamer: reinstate the template haskell level check in notFound
Out-of-scope names might be caused by a staging error, as is explained by
Note [Out of scope might be a staging error] in GHC.Tc.Utils.Env.hs.
This logic was assumed to be dead code after 217caad1 and has thus been
removed. This commit reintroduces it and thus fixes issue #26099.
- - - - -
0318010b by Zubin Duggal at 2025-12-04T04:37:27-05:00
testlib: Optionally include the way name in the expected output file
This allows us to have different outputs for different ways.
- - - - -
6d945fdd by Zubin Duggal at 2025-12-04T04:37:27-05:00
testsuite: Accept output of tests failing in ext-interp way due to differing compilation requirements
Fixes #26552
- - - - -
0ffc5243 by Cheng Shao at 2025-12-04T04:38:09-05:00
devx: minor fixes for compile_flags.txt
This patch includes minor fixes for compile_flags.txt to improve
developer experience when using clangd as language server to hack on
RTS C sources:
- Ensure `-fPIC` is passed and `__PIC__` is defined, to be coherent
with `-DDYNAMIC` and ensure the `__PIC__` guarded code paths are
indexed
- Add the missing `-DRtsWay` definition, otherwise a few source files
like `RtsUtils.c` and `Trace.c` would produce clangd errors
- - - - -
e36a5fcb by Matthew Pickering at 2025-12-05T16:25:57-05:00
Add support for building bytecode libraries
A bytecode library is a collection of bytecode files (.gbc) and a
library which combines together additional object files.
A bytecode library is created by invoking GHC with the `-bytecodelib`
flag.
A library can be created from in-memory `ModuleByteCode` linkables or
by passing `.gbc` files as arguments on the command line.
Fixes #26298
- - - - -
8f9ae339 by Matthew Pickering at 2025-12-05T16:25:57-05:00
Load bytecode libraries to satisfy package dependencies
This commit allows you to use a bytecode library to satisfy a package
dependency when using the interpreter.
If a user enables `-fprefer-byte-code`, then if a package provides a
bytecode library, that will be loaded and used to satisfy the
dependency.
The main change is to separate the relevant parts of the `LoaderState`
into external and home package byte code. Bytecode is loaded into either
the home package or external part (similar to HPT/EPS split), HPT
bytecode can be unloaded. External bytecode is never unloaded.
The unload function has also only been called with an empty list of
"stable linkables" for a long time. It has been modified to directly
implement a complete unloading of the home package bytecode linkables.
At the moment, the bytecode libraries are found in the "library-dirs"
field from the package description. In the future when `Cabal`
implements support for "bytecode-library-dirs" field, we can read the
bytecode libraries from there. No changes to the Cabal submodule are
necessary at the moment.
Four new tests are added in testsuite/tests/cabal, which generate fake
package descriptions and test loading the libraries into GHCi.
Fixes #26298
- - - - -
54458ce4 by mangoiv at 2025-12-05T16:26:50-05:00
ExplicitLevelImports: improve documentation of the code
- more explicit names for variable names like `flg` or `topLevel`
- don't pass the same value twice to functions
- some explanations of interesting but undocumented code paths
- adjust comment to not mention non-existent error message
- - - - -
c7061392 by mangoiv at 2025-12-05T16:27:42-05:00
driver: don't expect nodes to exist when checking paths between them
In `mgQueryZero`, previously node lookups were expected to never fail,
i.e. it was expected that when calculating the path between two nodes in
a zero level import graph, both nodes would always exist. This is not
the case, e.g. in some situations involving exact names (see the
test-case). The fix is to first check whether the node is present in the
graph at all, instead of panicking, just to report that there is no
path.
Closes #26568
- - - - -
d6cf8463 by Peng Fan at 2025-12-06T11:06:28-05:00
NCG/LA64: Simplify genCCall into two parts
genCCall is too long, so it's been simplified into two parts:
genPrim and genLibCCall.
Suggested by Andreas Klebinger
- - - - -
9d371d23 by Matthew Pickering at 2025-12-06T11:07:09-05:00
hadrian: Use a response file to invoke GHC for dep gathering.
In some cases we construct an argument list too long for GHC to
handle directly on windows. This happens when we generate
the dependency file because the command line will contain
references to a large number of .hs files.
To avoid this we now invoke GHC using a response file when
generating dependencies to sidestep length limitations.
Note that we only pass the actual file names in the dependency
file. Why? Because this side-steps #26560
- - - - -
0043bfb0 by Marc Scholten at 2025-12-06T11:08:03-05:00
update xhtml to 3000.4.0.0
haddock-api: bump xhtml bounds
haddock-api: use lazy text instead of string to support xhtml 3000.4.0.0
Bumping submodule xhtml to 3000.4.0.0
add xhtml to stage0Packages
remove unused import of writeUtf8File
Remove redundant import
Update haddock golden files for xhtml 3000.4.0.0
Metric Decrease:
haddock.Cabal
haddock.base
- - - - -
fc958fc9 by Julian Ospald at 2025-12-06T11:08:53-05:00
rts: Fix object file format detection in loadArchive
Commit 76d1041dfa4b96108cfdd22b07f2b3feb424dcbe seems to
have introduced this bug, ultimately leading to failure of
test T11788. I can only theorize that this test isn't run
in upstream's CI, because they don't build a static GHC.
The culprit is that we go through the thin archive, trying
to follow the members on the filesystem, but don't
re-identify the new object format of the member. This pins
`object_fmt` to `NotObject` from the thin archive.
Thanks to @angerman for spotting this.
- - - - -
0f297f6e by mangoiv at 2025-12-06T11:09:44-05:00
users' guide: don't use f strings in the python script to ensure compatibility with python 3.5
- - - - -
3bfe7aa2 by Matthew Pickering at 2025-12-07T12:18:57-05:00
ci: Try using multi repl in ghc-in-ghci test
This should be quite a bit faster than the ./hadrian/ghci command as it
doesn't properly build all the dependencies.
- - - - -
2ef1601a by Rodrigo Mesquita at 2025-12-07T12:19:38-05:00
Stack.Decode: Don't error on bitmap size 0
A RET_BCO may have a bitmap with no payload.
In that case, the bitmap = 0.
One can observe this by using -ddump-bcos and interpreting
```
main = pure ()
```
Observe, for instance, that the BCO for this main function has size 0:
```
ProtoBCO Main.main#0:
\u []
break<main:Main,0>() GHC.Internal.Base.pure
GHC.Internal.Base.$fApplicativeIO GHC.Internal.Tuple.()
bitmap: 0 []
BRK_FUN <breakarray> main:Main 0 <cc>
PACK () 0
PUSH_G GHC.Internal.Base.$fApplicativeIO
PUSH_APPLY_PP
PUSH_G GHC.Internal.Base.pure
ENTER
```
Perhaps we never tried to decode a stack in which a BCO like this was
present. However, for the debugger, we want to decode stacks of threads
stopped at breakpoints, and these kind of BCOs do get on a stack under
e.g. `stg_apply_interp_info` frames.
See the accompanying test in the next commit for an example to trigger
the bug this commit fixes.
Fixes #26640
- - - - -
747153d2 by Rodrigo Mesquita at 2025-12-07T12:19:38-05:00
Add test for #26640
- - - - -
d4b1e353 by Simon Hengel at 2025-12-10T00:00:02-05:00
Fix syntax error in gadt_syntax.rst
- - - - -
91cc8be6 by Cheng Shao at 2025-12-10T00:00:43-05:00
ci: fix "ci.sh clean" to address frequent out of space error on windows runners
This patch fixes the `ci.sh clean` logic to address frequent out of
space error on windows runners; previously it didn't clean up the
inplace mingw blobs, which is the largest source of space leak on
windows runners. See added comment for detailed explanation.
- - - - -
fe2b79f4 by Recursion Ninja at 2025-12-10T08:34:18-05:00
Narrow before optimising MUL/DIV/REM into shifts
The MUL/DIV/REM operations can be optimised into shifts when one of the
operands is a constant power of 2. However, as literals in Cmm are
stored as 'Integer', for this to be correct we first need to narrow the
literal to the appropriate width before checking whether the literal is
a power of 2.
Fixes #25664
- - - - -
06c2349c by Recursion Ninja at 2025-12-10T08:34:58-05:00
Decouple 'Language.Haskell.Syntax.Type' from 'GHC.Utils.Panic'
- Remove the *original* defintion of 'hsQTvExplicit' defined within 'Language.Haskell.Syntax.Type'
- Redefine 'hsQTvExplicit' as 'hsq_explicit' specialized to 'GhcPass' exported by 'GHC.Utils.Panic'
- Define 'hsQTvExplicitBinders' as 'hsq_explicit' specialized to 'DocNameI' exported by 'Haddock.GhcUtils'.
- Replace all call sites of the original 'hsQTvExplicit' definition with either:
1. 'hsQTvExplicit' updated definition
2. 'hsQTvExplicitBinders'
All call sites never entered the 'XLHsQTyVars' constructor branch, but a call to 'panic' existed on this code path because the type system was not strong enought to guarantee that the 'XLHsQTyVars' construction was impossible.
These two specialized functions provide the type system with enough information to make that guarantee, and hence the dependancy on 'panic' can be removed.
- - - - -
ac0815d5 by sheaf at 2025-12-10T23:39:57-05:00
Quantify arg before mult in function arrows
As noted in #23764, we expect quantification order to be left-to-right,
so that in a type such as
a %m -> b
the inferred quantification order should be [a, m, b] and not [m, a, b].
This was addressed in commit d31fbf6c, but that commit failed to update
some other functions such as GHC.Core.TyCo.FVs.tyCoFVsOfType.
This affects Haddock, as whether we print an explicit forall or not
depends on whether the inferred quantification order matches the actual
quantification order.
- - - - -
2caf796e by sheaf at 2025-12-10T23:39:57-05:00
Haddock: improvements to ty-var quantification
This commit makes several improvements to how Haddock deals with the
quantification of type variables:
1. In pattern synonyms, Haddock used to jumble up universal and
existential quantification. That is now fixed, fixing #26252.
Tested in the 'PatternSyns2' haddock-html test.
2. The logic for computing whether to use an explicit kind annotation
for a type variable quantified in a forall was not even wrong.
This commit improves the heuristic, but it will always remain an
imperfect heuristic (lest we actually run kind inference again).
In the future (#26271), we hope to avoid reliance on this heuristic.
- - - - -
b14bdd59 by Teo Camarasu at 2025-12-10T23:40:38-05:00
Add explicit export list to GHC.Num
Let's make clear what this module exports to allow us to easily deprecate and remove some of these in the future. Resolves https://gitlab.haskell.org/ghc/ghc/-/issues/26625
- - - - -
d99f8326 by Cheng Shao at 2025-12-11T19:14:18-05:00
compiler: remove unused CPP code in foreign stub
This patch removes unused CPP code in the generated foreign stub:
- `#define IN_STG_CODE 0` is not needed, since `Rts.h` already
includes this definition
- The `if defined(__cplusplus)` code paths are not needed in the `.c`
file, since we don't generate C++ stubs and don't include C++
headers in our stubs. But it still needs to be present in the `.h`
header since it might be later included into C++ source files.
- - - - -
46c9746f by Cheng Shao at 2025-12-11T19:14:57-05:00
configure: bump LlvmMaxVersion to 22
This commit bumps LlvmMaxVersion to 22; 21.x releases have been
available since Aug 26th, 2025 and there's no regressions with 21.x so
far. This bump is also required for updating fedora image to 43.
- - - - -
96fce8d0 by Cheng Shao at 2025-12-12T01:17:51+01:00
hadrian: add support for building with UndefinedBehaviorSanitizer
This patch adds a +ubsan flavour transformer to hadrian to build all
stage1+ C/C++ code with UndefinedBehaviorSanitizer. This is
particularly useful to catch potential undefined behavior in the RTS
codebase.
- - - - -
f7a06d8c by Cheng Shao at 2025-12-12T01:17:51+01:00
ci: update alpine/fedora & add ubsan job
This patch updates alpine image to 3.23, fedora image to 43, and adds
a `x86_64-linux-fedora43-validate+debug_info+ubsan` job that's run in
validate/nightly pipelines to catch undefined behavior in the RTS
codebase.
- - - - -
2ccd11ca by Cheng Shao at 2025-12-12T01:17:51+01:00
rts: fix zero-length VLA undefined behavior in interpretBCO
This commit fixes a zero-length VLA undefined behavior in interpretBCO, caught by UBSan:
```
+rts/Interpreter.c:3133:19: runtime variable length array bound evaluates to non-positive value 0
```
- - - - -
4156ed19 by Cheng Shao at 2025-12-12T01:17:51+01:00
rts: fix unaligned ReadSpB in interpretBCO
This commit fixes unaligned ReadSpB in interpretBCO, caught by UBSan:
```
+rts/Interpreter.c:2174:64: runtime load of misaligned address 0x004202059dd1 for type 'StgWord', which requires 8 byte alignment
```
To perform proper unaligned read, we define StgUnalignedWord as a type
alias of StgWord with aligned(1) attribute, and load StgUnalignedWord
instead of StgWord in ReadSpB, so the C compiler is aware that we're
not loading with natural alignment.
- - - - -
fef89fb9 by Cheng Shao at 2025-12-12T01:17:51+01:00
rts: fix signed integer overflow in subword arithmetic in interpretBCO
This commit fixes signed integer overflow in subword arithmetic in
interpretBCO, see added note for detailed explanation.
- - - - -
3c001377 by Cheng Shao at 2025-12-13T05:03:15-05:00
ci: use treeless fetch for perf notes
This patch improves the ci logic for fetching perf notes by using
treeless fetch
(https://github.blog/open-source/git/get-up-to-speed-with-partial-clone-and-…)
to avoid downloading all blobs of the perf notes repo at once, and
only fetch the actually required blobs on-demand when needed. This
makes the initial `test-metrics.sh pull` operation much faster, and
also more robust, since we are seeing an increasing rate of 504 errors
in CI when fetching all perf notes at once, which is a major source of
CI flakiness at this point.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
123a8d77 by Peter Trommler at 2025-12-13T05:03:57-05:00
Cmm: remove restriction in MachOp folding
- - - - -
0b54b5fd by Andreas Klebinger at 2025-12-13T05:04:38-05:00
Remove explicit Typeable deriviations.
- - - - -
08b13f7b by Cheng Shao at 2025-12-13T05:05:18-05:00
ci: set gc.auto=0 during setup stage
This patch sets `gc.auto=0` during `setup` stage of CI, see added
comment for detailed explanation.
- - - - -
3b5aecb5 by Ben Gamari at 2025-12-13T23:43:10+01:00
Bump exceptions submodule to 0.10.11
- - - - -
c32de3b0 by Johan Förberg at 2025-12-15T02:36:03-05:00
base: Define Semigroup and Monoid instances for lazy ST
CLC proposal:
https://github.com/haskell/core-libraries-committee/issues/374
Fixes #26581
- - - - -
4f8b660c by mangoiv at 2025-12-15T02:37:05-05:00
ci: do not require nightly cabal-reinstall job to succeed
- - - - -
2c2a3ef3 by Cheng Shao at 2025-12-15T11:51:53-05:00
docs: drop obsolete warning about -fexternal-interpreter on windows
This patch drops an obsolete warning about -fexternal-interpreter not
supported on windows; it is supported since a long time ago, including
the profiled way.
- - - - -
68573aa5 by Marc Scholten at 2025-12-15T11:53:00-05:00
haddock: Drop Haddock.Backends.HaddockDB as it's unused
- - - - -
b230d549 by mangoiv at 2025-12-16T15:17:45-05:00
base: generalize delete{Firsts,}By
When we delete{Firsts,}By we should not require the
lists to be the same type. This is an especially useful
generalisation in the case of deleteFirstsBy because we
can skip an invocation of the map function.
This change was discussed on the core-libraries-committee's bug
tracker at https://github.com/haskell/core-libraries-committee/issues/372.
- - - - -
6a2b43e3 by Cheng Shao at 2025-12-16T15:18:30-05:00
compiler: clean up redundant LANGUAGE pragmas
This patch bumps `default-language` of `ghc`/`ghc-bin` from `GHC2021`
to `GHC2024` (which is supported in ghc 9.10, current boot ghc lower
version bound), and also cleans up redundant `LANGUAGE` pragmas (as
well as `default-extensions`/`other-extensions`) that are already
implied by `GHC2024`.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
fca9cd7c by sheaf at 2025-12-18T13:18:18-05:00
X86 CodeGen: fix assign_eax_sse_regs
We must set %al to the number of SSE2 registers that contain arguments
(in case we are dealing with a varargs function). The logic for counting
how many arguments reside in SSE2 registers was incorrect, as it used
'isFloatFormat', which incorrectly ignores vector registers.
We now instead do case analysis on the register class:
is_sse_reg r =
case targetClassOfReg platform r of
RcFloatOrVector -> True
RcInteger -> False
This change is necessary to prevent segfaults in T20030_test1j, because
subsequent commits change the format calculations, resulting in vector
formats more often.
- - - - -
53150617 by sheaf at 2025-12-18T13:18:19-05:00
X86 regUsageOfInstr: fix format for IMUL
When used with 8-bit operands, the IMUL instruction returns the result
in the lower 16 bits of %rax (also known as %ax). This is different
than for the other sizes, where an input at 16, 32 or 64 bits will
result in 16, 32 or 64 bits of output in both %rax and %rdx.
This doesn't affect the behaviour of the compiler, because we don't
allow partial writes at sub-word sizes. The rationale is explained
in Wrinkle [Don't allow scalar partial writes] in Note [Register formats in liveness analysis],
in GHC.CmmToAsm.Reg.Liveness.
- - - - -
c7a56dd1 by sheaf at 2025-12-18T13:18:19-05:00
Liveness analysis: consider register formats
This commit updates the register allocator to be a bit more careful in
situations in which a single register is used at multiple different
formats, e.g. when xmm1 is used both to store a Double# and a DoubleX2#.
This is done by introducing the 'Regs' newtype around 'UniqSet RegWithFormat',
for which the combining operations take the larger of the two formats
instead of overriding the format.
Operations on 'Regs' are defined in 'GHC.CmmToAsm.Reg.Regs'. There is
a modest compile-time cost for the additional overhead for tracking
register formats, which causes the metric increases of this commit.
The subtle aspects of the implementation are outlined in
Note [Register formats in liveness analysis] in GHC.CmmToAsm.Reg.Liveness.
Fixes #26411 #26611
-------------------------
Metric Increase:
T12707
T26425
T3294
-------------------------
- - - - -
c2e83339 by sheaf at 2025-12-18T13:18:19-05:00
Register allocator: reload at same format as spill
This commit ensures that if we spill a register onto the stack at a
given format, we then always reload the register at this same format.
This ensures we don't end up in a situation where we spill F64x2 but end
up only reloading the lower F64. This first reload would make us believe
the whole data is in a register, thus silently losing the upper 64 bits
of the spilled register's contents.
Fixes #26526
- - - - -
55ab583b by sheaf at 2025-12-18T13:18:19-05:00
Register allocation: writes redefine format
As explained in Note [Allocated register formats] in GHC.CmmToAsm.Reg.Linear,
we consider all writes to redefine the format of the register.
This ensures that in a situation such as
movsd .Ln6m(%rip),%v1
shufpd $0,%v1,%v1
we properly consider the broadcast operation to change the format of %v1
from F64 to F64x2.
This completes the fix to #26411 (test in T26411b).
- - - - -
951402ed by Vladislav Zavialov at 2025-12-18T13:19:05-05:00
Parser: improve mkModuleImpExp, remove checkImportSpec
1. The `mkModuleImpExp` helper now knows whether it is processing an import or
export list item, and uses this information to produce a more accurate error
message for `import M (T(..,x))` with PatternSynonyms disabled.
The old message incorrectly referred to this case as an export form.
2. The `checkImportSpec` helper is removed in favor of more comprehensive error
checking in `mkModuleImpExp`.
3. Additionaly, the invariants of `ImpExpList` and `ImpExpAllWith` have been
made more explicit in the comments and assertions (calls to 'panic').
Test case: import-syntax-no-ext
- - - - -
47d83d96 by Vladislav Zavialov at 2025-12-18T13:19:06-05:00
Subordinate namespace-specified wildcards (#25901)
Add support for subordinate namespace-specified wildcards
`X(type ..)` and `X(data ..)` to import and export lists.
Examples:
import M (Cls(type ..)) -- imports Cls and all its associated types
import M (Cls(data ..)) -- imports Cls and all its methods
module M (R(data ..), C(type ..)) where
-- exports R and all its data constructors and record fields;
-- exports C and all its associated types, but not its methods
The scope of this change is limited to the case where the wildcard is the only
subordinate import/export item, whereas the more complex forms `X(type .., f)`
or `X(type .., data ..)` are unsupported and raise the newly introduced
PsErrUnsupportedExplicitNamespace error. This restriction may be lifted later.
Summary of the changes:
1. Refactor IEThingAll to store its extension field XIEThingAll as a record
IEThingAllExt instead of a tuple.
2. Extend the AST by adding a NamespaceSpecifier field to IEThingAllExt,
representing an optional namespace specifier `type` or `data` in front
of a subordinate wildcard `X(..)`.
3. Extend the grammar in Parser.y with productions for `type ..` and `data ..`
in subordinate import/export items.
4. Introduce `filterByNamespaceGREs` to filter [GlobalRdrElt] by a
NamespaceSpecifier; use it in `filterImports` and `exports_from_avail`
to account for the namespace specifier in IEThingAll.
5. Improve diagnostics by storing more information in DodgyImportsEmptyParent
and DodgyExportsEmptyParent.
Test cases:
T25901_sub_e T25901_sub_f T25901_sub_g T25901_sub_a
T25901_sub_b T25901_sub_c T25901_sub_d T25901_sub_w
DodgyImports02 DodgyImports03 DodgyImports04
- - - - -
eac418bb by Recursion Ninja at 2025-12-18T13:19:48-05:00
Removing the 'Data' instance for 'InstEnv'.
The 'Data' instance is blocking work on Trees that Grow, and the
'Data' instance seem to have been added without a clear purpose.
- - - - -
e920e038 by Recursion Ninja at 2025-12-18T13:19:48-05:00
'Decouple Language.Haskell.Syntax.Decls' from 'GHC.Unit.Module.Warnings'
- - - - -
bd38b76c by Cheng Shao at 2025-12-18T13:20:31-05:00
testsuite: improve coverage of foundation test
This patch refactors the `foundation` test a bit to improve coverage:
- Instead of using a hard-coded seed, a random seed is now taken from
the command line, and printed upon test failure. This improves test
coverage over many future CI runs, and shall a failure occur, the
seed is available in the CI log for local reproduction.
- The iterations count is bumped to 1000 instead of 100, similar to
the bump in `test-primops`. Runtime timeout is bumped 2x just to be
safe.
- Improve `newLCGGen` by using non-atomic loads/stores on a
`MutableByteArray#` for storing mutable `Word64`, this test doesn't
use parallelism in the first place
- Fixed a few compiler warnings and removed redundant pragmas and
imports
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
3995187c by Sylvain Henry at 2025-12-18T13:21:45-05:00
Doc: document -pgmi "" (#26634)
- - - - -
5729418c by Cheng Shao at 2025-12-18T13:22:29-05:00
rts: use __builtin_mul_overflow for hs_mulIntMayOflo
This patch uses `__builtin_mul_overflow` to implement
`hs_mulIntMayOflo`. This is a GNU C checked arithmetic builtin
function supported by gcc/clang, is type-generic so works for both
32-bit/64-bit, and makes the code both more efficient and easier to
read/maintain than the previous hand rolled logic.
- - - - -
1ca4b49a by Cheng Shao at 2025-12-18T13:23:11-05:00
compiler/rts: fix ABI mismatch in barf() invocations
This patch fixes a long-standing issue of ABI mismatch in `barf()`
invocations, both in compiler-emitted code and in hand written Cmm
code:
- In RTS, we have `barf()` which reports a fatal internal error
message and exits the program.
- `barf()` is a variadic C function! When used as a callee of a
foreign call with `ccall` calling convention instead of `capi`,
there is an ABI mismatch between the caller and the callee!
- Unfortunately, both the compiler and the Cmm sources contain many
places where we call `barf()` via `ccall` convention!! Like, when
you write `foreign "C" barf("foo object (%p) entered!", R1)`, it
totally doesn't do what you think it'll do at all!! The second
argument `R1` is not properly passed in `va_list`, and the behavior
is completely undefined!!
- Even more unfortunately, this issue has been sitting around long
enough because the ABI mismatch is subtle enough on normie platforms
like x64 and arm64.
- But there are platforms like wasm32 that are stricter about ABI, and
the broken `barf()` invocations already causes trouble for wasm
backend: we had to use ugly hacks like `barf(errmsg, NULL)` to make
`wasm-ld` happy, and even with this band-aid, compiler-generated
`barf()` invocations are still broken, resulting in regressions in
certain debug-related functionality, e.g. `-dtag-inference-checks`
is broken on wasm32 (#22882).
This patch properly fixes the issue:
- We add non-variadic `barf` wrappers in the RTS that can be used as
`ccall` callees
- Both the compiler `emitBarf` logic and the hand-written Cmm are
changed to call these wrappers
- `emitBarf` now also properly annotates the foreign call as
`CmmNeverReturns` to indicate it's a noreturn call to enable more
efficient code generation
`-dtag-inference-checks` now works on wasm. Closes #22882.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
b3dd23b9 by Vilim Lendvaj at 2025-12-18T13:23:57-05:00
Remove outdated comment
The Traversable instance for ZipList is no longer in
GHC.Internal.Data.Traversable. In fact, it is right below this very comment.
- - - - -
9a9c2f03 by Cheng Shao at 2025-12-18T13:24:39-05:00
compiler: remove unused OtherSection logic
This patch removes the OtherSection logic in Cmm, given it's never
actually used by any of our backends.
- - - - -
91edd292 by Wolfgang Jeltsch at 2025-12-19T03:18:19-05:00
Remove unused known-key and name variables for generics
This removes the known-key and corresponding name variables for `K1`,
`M1`, `R`, `D`, `C`, `S`, and `URec` from `GHC.Generics`, as they are
apparently nowhere used in GHC’s source code.
- - - - -
73ee7e38 by Wolfgang Jeltsch at 2025-12-19T03:19:02-05:00
Remove unused known keys and names for generics classes
This removes the known-key and corresponding name variables for
`Datatype`, `Constructor`, and `Selector` from `GHC.Generics`, as they
are apparently nowhere used in GHC’s source code.
- - - - -
f69c5f14 by Cheng Shao at 2025-12-19T03:19:45-05:00
wasm: fix handling of ByteArray#/MutableByteArray# arguments in JSFFI imports
This patch fixes the handling of ByteArray#/MutableByteArray#
arguments in JSFFI imports, see the amended note and manual for
explanation. Also adds a test to witness the fix.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
224446a2 by Cheng Shao at 2025-12-20T07:49:54-05:00
rts: workaround -Werror=maybe-uninitialized false positives
In some cases gcc might report -Werror=maybe-uninitialized that we
know are false positives, but need to workaround it to make validate
builds with -Werror pass.
- - - - -
251ec087 by Cheng Shao at 2025-12-20T07:49:54-05:00
hadrian: use -Og as C/C++ optimization level when debugging
This commit enables -Og as optimization level when compiling the debug
ways of rts. According to gcc documentation
(https://gcc.gnu.org/onlinedocs/gcc/Optimize-Options.html#index-Og)
-Og is a better choice than -O0 for producing debuggable code. It's
also supported by clang as well, so it makes sense to use it as a
default for debugging. Also add missing -g3 flag to C++ compilation
flags in +debug_info flavour transformer.
- - - - -
fb586c67 by Cheng Shao at 2025-12-20T07:50:36-05:00
compiler: replace DList with OrdList
This patch removes `DList` logic from the compiler and replaces it
with `OrdList` which also supports O(1) concatenation and should be
more memory efficient than the church-encoded `DList`.
- - - - -
8149c987 by Cheng Shao at 2025-12-20T17:06:51-05:00
hadrian: add with_profiled_libs flavour transformer
This patch adds a `with_profiled_libs` flavour transformer to hadrian
which is the exact opposite of `no_profiled_libs`. It adds profiling
ways to stage1+ rts/library ways, and doesn't alter other flavour
settings. It is useful when needing to test profiling logic locally
with a quick flavour.
- - - - -
746b18cd by Cheng Shao at 2025-12-20T17:06:51-05:00
hadrian: fix missing profiled dynamic libraries in profiled_ghc
This commit fixes the profiled_ghc flavour transformer to include
profiled dynamic libraries as well, since they're supported by GHC
since !12595.
- - - - -
4dd7e3b9 by Cheng Shao at 2025-12-20T17:07:33-05:00
ci: set http.postBuffer to mitigate perf notes timeout on some runners
This patch sets http.postBuffer to mitigate the timeout when fetching
perf notes on some runners with slow internet connection. Fixes #26684.
- - - - -
bc36268a by Wolfgang Jeltsch at 2025-12-21T16:23:24-05:00
Remove unused known keys and names for type representations
This removes the known-key and corresponding name variables for
`TrName`, `TrNameD`, `TypeRep`, `KindRepTypeLitD`, `TypeLitSort`, and
`mkTrType`, as they are apparently nowhere used in GHC’s source code.
- - - - -
ff5050e9 by Wolfgang Jeltsch at 2025-12-21T16:24:04-05:00
Remove unused known keys and names for natural operations
This removes the known-key and corresponding name variables for
`naturalAndNot`, `naturalLog2`, `naturalLogBaseWord`, `naturalLogBase`,
`naturalPowMod`, `naturalSizeInBase`, `naturalToFloat`, and
`naturalToDouble`, as they are apparently nowhere used in GHC’s source
code.
- - - - -
424388c2 by Wolfgang Jeltsch at 2025-12-21T16:24:45-05:00
Remove the unused known key and name for `Fingerprint`
This removes the variables for the known key and the name of the
`Fingerprint` data constructor, as they are apparently nowhere used in
GHC’s source code.
- - - - -
a1ed86fe by Wolfgang Jeltsch at 2025-12-21T16:25:26-05:00
Remove the unused known key and name for `failIO`
This removes the variables for the known key and the name of the
`failIO` operation, as they are apparently nowhere used in GHC’s source
code.
- - - - -
b8220daf by Wolfgang Jeltsch at 2025-12-21T16:26:07-05:00
Remove the unused known key and name for `liftM`
This removes the variables for the known key and the name of the `liftM`
operation, as they are apparently nowhere used in GHC’s source code.
- - - - -
eb0628b1 by Wolfgang Jeltsch at 2025-12-21T16:26:47-05:00
Fix the documentation of `hIsClosed`
- - - - -
db1ce858 by sheaf at 2025-12-22T17:11:17-05:00
Do deep subsumption when computing valid hole fits
This commit makes a couple of improvements to the code that
computes "valid hole fits":
1. It uses deep subsumption for data constructors.
This matches up the multiplicities, as per
Note [Typechecking data constructors].
This fixes #26338 (test: LinearHoleFits).
2. It now suggests (non-unidirectional) pattern synonyms as valid
hole fits. This fixes #26339 (test: PatSynHoleFit).
3. It uses 'stableNameCmp', to make the hole fit output deterministic.
-------------------------
Metric Increase:
hard_hole_fits
-------------------------
- - - - -
72ee9100 by sheaf at 2025-12-22T17:11:17-05:00
Speed up hole fits with a quick pre-test
This speeds up the machinery for valid hole fits by doing a small
check to rule out obviously wrong hole fits, such as:
1. A hole fit identifier whose type has a different TyCon at the head,
after looking through foralls and (=>) arrows, e.g.:
hole_ty = Int
cand_ty = Maybe a
or
hole_ty = forall a b. a -> b
cand_ty = forall x y. Either x y
2. A hole fit identifier that is not polymorphic when the hole type
is polymorphic, e.g.
hole_ty = forall a. a -> a
cand_ty = Int -> Int
-------------------------
Metric Decrease:
hard_hole_fits
-------------------------
- - - - -
30e513ba by Cheng Shao at 2025-12-22T17:12:00-05:00
configure: remove unused win32-tarballs.md5sum
This patch removes the unused `win32-tarballs.md5sum` file from the
tree. The current mingw tarball download logic in
`mk/get-win32-tarballs.py` fetches and checks against `SHA256SUM` from
the same location where the tarballs are fetched, and this file has
been unused for a few years.
- - - - -
a2d52b3b by Wolfgang Jeltsch at 2025-12-23T04:47:33-05:00
Add an operation `System.IO.hGetNewlineMode`
This commit also contains some small code and documentation changes for
related operations, for the sake of consistency.
- - - - -
b26d134a by Cheng Shao at 2025-12-23T04:48:15-05:00
rts: opportunistically reclaim slop space in shrinkMutableByteArray#
Previously, `shrinkMutableByteArray#` shrinks a `MutableByteArray#`
in-place by assigning the new size to it, and zeroing the extra slop
space. That slop space is not reclaimed and wasted. But it's often the
case that we allocate a `MutableByteArray#` upfront, then shrink it
shortly after, so the `MutableByteArray#` closure sits right at the
end of a nursery block; this patch identifies such chances, and also
shrink `bd->free` if possible, reducing heap space fragmentation.
Co-authored-by: Codex <codex(a)openai.com>
-------------------------
Metric Decrease:
T10678
-------------------------
- - - - -
c72ddabf by Cheng Shao at 2025-12-23T16:13:23-05:00
hadrian: fix bootstrapping with ghc-9.14
This patch fixes bootstrapping GHC with ghc-9.14, tested locally with
ghc-9.14.1 release as bootstrapping GHC.
- - - - -
0fd6d8e4 by Cheng Shao at 2025-12-23T16:14:05-05:00
hadrian: pass -keep-tmp-files to test ghc when --keep-test-files is enabled
This patch makes hadrian pass `-keep-tmp-files` to test ghc when
`--keep-test-files` is enabled, so you can check the ghc intermediate
files when debugging certain test failures. Closes #26688.
- - - - -
81d10134 by Cheng Shao at 2025-12-24T06:11:52-05:00
configure: remove dead code in configure scripts
This patch removes dead code in our configure scripts, including:
- Variables and auto-detected programs that are not used
- autoconf functions that are not used, or export a variable that's
not used
- `AC_CHECK_HEADERS` invocations that don't have actual corresponding
`HAVE_XXX_H` usage
- Other dead code (e.g. stray `AC_DEFUN()`)
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
fb1381c3 by Wolfgang Jeltsch at 2025-12-24T06:12:34-05:00
Remove unused known keys and names for list operations
This removes the known-key and corresponding name variables for
`concat`, `filter`, `zip`, and `(++)`, as they are apparently nowhere
used in GHC’s source code.
- - - - -
7b9c20f4 by Recursion Ninja at 2025-12-24T10:35:36-05:00
Decoupling Language.Haskell.Syntax.Binds from GHC.Types.Basic
by transferring InlinePragma types between the modules.
* Moved InlinePragma data-types to Language.Haskell.Syntax.Binds.InlinePragma
* Partitioned of Arity type synonyms to GHC.Types.Arity
* InlinePragma is now extensible via Trees That Grow
* Activation is now extensible via Trees That Grow
* Maybe Arity change to more descriptive InlineSaturation data-type
* InlineSaturation information removed from InlinePragma during GHS parsing pass
* Cleaned up the exposed module interfaces of the new modules
- - - - -
a3afae0c by Simon Peyton Jones at 2025-12-25T15:26:36-05:00
Check for rubbish literals in Lint
Addresses #26607.
See new Note [Checking for rubbish literals] in GHC.Core.Lint
- - - - -
8a317b6f by Aaron Allen at 2026-01-01T03:05:15-05:00
[#26183] Associated Type Iface Fix
When determining "extras" for class decl interface entries, axioms for
the associated types need to included so that dependent modules will be
recompiled if those axioms change.
resolves #26183
- - - - -
ae1aeaab by Cheng Shao at 2026-01-01T03:06:32-05:00
testsuite: run numeric tests with optasm when available
This patch adds the `optasm` extra way to nueric tests when NCG is
available. Some numeric bugs only surface with optimization, omitting
this can hide these bugs and even make them slip into release! (e.g. #26711)
- - - - -
6213bb57 by maralorn at 2026-01-02T16:30:32+01:00
GHC.Internal.Exception.Context: Fix comment
on addExceptionAnnotation
- - - - -
b820ff50 by Janis Voigtlaender at 2026-01-05T02:43:18-05:00
GHC.Internal.Control.Monad.replicateM: Fix comment
- - - - -
a8a94aad by Cheng Shao at 2026-01-05T16:24:04-05:00
hadrian: drops unused PE linker script for windows
This patch drops unused PE linker script for windows in the
`MergeObjects` builder of hadrian. The linker script is used for
merging object files into a single `HS*.o` object file and undoing the
effect of split sections, when building the "ghci library" object
file. However, we don't build the ghci library on windows, and this
code path is actually unreachable.
- - - - -
53038ea9 by Cheng Shao at 2026-01-05T16:24:04-05:00
hadrian: drop unused logic for building ghci libraries
This patch drops the unused logic for building ghci libraries in
hadrian:
- The term "ghci library" refers to an optional object file per
library `HS*.o`, which is merged from multiple object files in that
library using the `MergeObjects` builder in hadrian.
- The original rationale of having a ghci library object, in addition
to normal archives, was to speedup ghci loading, since the combined
object is linked with a linker script to undo the effects of
`-fsplit-sections` to reduce section count and make it easier for
the RTS linker to handle.
- However, most GHC builds enable `dynamicGhcPrograms` by default, in
such cases the ghci library would already not be built.
- `dynamicGhcPrograms` is disabled on Windows, but still we don't
build the ghci library due to lack of functioning merge objects
command.
- The only case that we actually build ghci library objects, are
alpine fully static bindists. However, for other reasons, split
sections is already disabled for fully static builds anyway!
- There will not be any regression if the ghci library objects are
absent from a GHC global libdir when `dynamicGhcPrograms` is
disabled. The RTS linker can already load the archives without any
issue.
Hence the removal. We now forcibly disable ghci libraries for all
Cabal components, and rip out all logic related to `MergeObjects` and
ghci libraries in hadrian. This also nicely cleans up some old todos
and fixmes that are no longer relevant.
Note that MergeObjects in hadrian is not the same thing as merge
objects in the GHC driver. The latter is not affected by this patch.
-------------------------
Metric Decrease:
libdir
-------------------------
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
8f209336 by Simon Jakobi at 2026-01-05T16:24:48-05:00
User's guide: Fix link to language extensions
Instead of linking to haddocks, it seemed more useful to link
to the extension overview in the user's guide.
Closes #26614.
- - - - -
0b7df6db by Simon Peyton Jones at 2026-01-06T09:32:23-05:00
Improved fundeps for closed type families
The big payload of this commit is to execute the plan suggested
in #23162, by improving the way that we generate functional
dependencies for closed type families.
It is all described in Note [Exploiting closed type families]
Most of the changes are in GHC.Tc.Solver.FunDeps
Other small changes
* GHC.Tc.Solver.bumpReductionDepth. This function brings together the code that
* Bumps the depth
* Checks for overflow
Previously the two were separated, sometimes quite widely.
* GHC.Core.Unify.niFixSubst: minor improvement, removing an unnecessary
itraetion in the base case.
* GHC.Core.Unify: no need to pass an InScopeSet to
tcUnifyTysForInjectivity. It can calculate one for itself; and it is
never inspected anyway so it's free to do so.
* GHC.Tc.Errors.Ppr: slight impovement to the error message for
reduction-stack overflow, when a constraint (rather than a type) is
involved.
* GHC.Tc.Solver.Monad.wrapUnifier: small change to the API
- - - - -
fde8bd88 by Simon Peyton Jones at 2026-01-06T09:32:23-05:00
Add missing (KK4) to kick-out criteria
There was a missing case in kick-out that meant we could fail
to solve an eminently-solvable constraint.
See the new notes about (KK4)
- - - - -
00082844 by Simon Peyton Jones at 2026-01-06T09:32:23-05:00
Some small refactorings of error reporting in the typechecker
This is just a tidy-up commit.
* Add ei_insoluble to ErrorItem, to cache insolubility.
Small tidy-up.
* Remove `is_ip` and `mkIPErr` from GHC.Tc.Errors; instead enhance mkDictErr
to handle implicit parameters. Small refactor.
- - - - -
fe4cb252 by Simon Peyton Jones at 2026-01-06T09:32:24-05:00
Improve recording of insolubility for fundeps
This commit addresses #22652, by recording when the fundeps for
a constraint are definitely insoluble. That in turn improves the
perspicacity of the pattern-match overlap checker.
See Note [Insoluble fundeps]
- - - - -
df0ffaa5 by Simon Peyton Jones at 2026-01-06T09:32:24-05:00
Fix a buglet in niFixSubst
The MR of which this is part failed an assertion check extendTvSubst
because we extended the TvSubst with a CoVar. Boo.
This tiny patch fixes it, and adds the regression test from #13882
that showed it up.
- - - - -
3d6aba77 by konsumlamm at 2026-01-06T09:33:16-05:00
Fix changelog formatting
- - - - -
69e0ab59 by Cheng Shao at 2026-01-06T19:37:56-05:00
compiler: add targetHasRTSWays function
This commit adds a `targetHasRTSWays` util function in
`GHC.Driver.Session` to query if the target RTS has a given Ways (e.g.
WayThreaded).
- - - - -
25a0ab94 by Cheng Shao at 2026-01-06T19:37:56-05:00
compiler: link on-demand external interpreter with threaded RTS
This commit makes the compiler link the on-demand external interpreter
program with threaded RTS if it is available in the target RTS ways.
This is a better default than the previous single-threaded RTS, and it
enables the external interpreter to benefit from parallelism when
deserializing CreateBCOs messages.
- - - - -
92404a2b by Cheng Shao at 2026-01-06T19:37:56-05:00
hadrian: link iserv with threaded RTS
This commit makes hadrian link iserv with threaded RTS if it's
available in the RTS ways. Also cleans up the iserv main C program
which can be replaced by the `-fkeep-cafs` link-time option.
- - - - -
a20542d2 by Cheng Shao at 2026-01-06T19:38:38-05:00
ghc-internal: remove unused GMP macros
This patch removes unused GMP related macros from `ghc-internal`. The
in-tree GMP version was hard coded and outdated, but it was not used
anywhere anyway.
- - - - -
4079dcd6 by Cheng Shao at 2026-01-06T19:38:38-05:00
hadrian: fix in-tree gmp configure error on newer c compilers
Building in-tree gmp on newer c compilers that default to c23 fails at
configure stage, this patch fixes it, see added comment for
explanation.
- - - - -
414d1fe1 by Cheng Shao at 2026-01-06T19:39:20-05:00
compiler: fix LLVM backend pdep/pext handling for i386 target
This patch fixes LLVM backend's pdep/pext handling for i386 target,
and also removes non-existent 128/256/512 bit hs_pdep/hs_pext callees.
See amended note for more explanation. Fixes #26450.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
c7f6fba3 by Cheng Shao at 2026-01-06T19:39:20-05:00
ci: remove allow_failure flag for i386 alpine job
The LLVM codegen issue for i386 has been fixed, and the i386 alpine
job should pass now. This commit removes the allow_failure flag so
that other i386 regressions in the future are signaled more timely.
- - - - -
52d00c05 by Simon Peyton Jones at 2026-01-07T10:24:21-05:00
Add missing InVar->OutVar lookup in SetLevels
As #26681 showed, the SetLevels pass was failing to map an InVar to
an OutVar. Very silly! I'm amazed it hasn't broken before now.
I have improved the type singatures (to mention InVar and OutVar)
so it's more obvious what needs to happen.
- - - - -
ab0a5594 by Cheng Shao at 2026-01-07T10:25:04-05:00
hadrian: drop deprecated pkgHashSplitObjs code path
This patch drops deprecated `pkgHashSplitObjs` code path from hadrian,
since GHC itself has removed split objs support many versions ago and
this code path is unused.
- - - - -
bb3a2ba1 by Cheng Shao at 2026-01-07T10:25:44-05:00
hadrian: remove linting/assertion in quick-validate flavour
The `quick-validate` flavour is meant for testing ghc and passing the
testsuite locally with similar settings to `validate` but faster. This
patch removes the linting/assertion overhead in `quick-validate` to
improve developer experience. I also took the chance to simplify
redundant logic of rts/library way definition in `validate` flavour.
- - - - -
7971f5dd by Cheng Shao at 2026-01-07T10:26:26-05:00
deriveConstants: clean up unused constants
This patch cleans up unused constants from `deriveConstants`, they are
not used by C/Cmm code in the RTS, nor compiler-generated code.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
4df96993 by Cheng Shao at 2026-01-07T10:27:08-05:00
hadrian: pass -fno-omit-frame-pointer with +debug_info
This patch adds `-fno-omit-frame-pointer` as C/C++ compilation flag
when compiling with `+debug_info` flavour transformer. It's a sane
default when you care about debugging and reliable backtraces, and
makes debugging/profiling with bpf easier.
- - - - -
8a3900a3 by Aaron Allen at 2026-01-07T10:27:57-05:00
[26705] Include TyCl instances in data fam iface entry
Ensures dependent modules are recompiled when the class instances for a
data family instance change.
resolves #26705
- - - - -
a0b980af by Cheng Shao at 2026-01-07T10:28:38-05:00
hadrian: remove unused Hp2Ps/Hpc builders
This patch removes the Hp2Ps/Hpc builders from hadrian, they are
unused in the build system. Note that the hp2ps/hpc programs are still
built and not affected.
- - - - -
50a58757 by Cheng Shao at 2026-01-07T10:29:20-05:00
hadrian: only install js files to libdir for wasm/js targets
There are certain js files required for wasm/js targets to work, and
previously hadrian would install those js files to libdir
unconditionally on other targets as well. This could be a minor
annoyance for packagers especially when the unused js files contain
shebangs that interfere with the packaging process. This patch makes
hadrian only selectively install the right js files for the right
targets.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
da40e553 by Simon Peyton Jones at 2026-01-07T10:30:00-05:00
Add flavour transformer assertions_stage1
This allows us to enable -DDEBUG assertions in the stage1 compiler
- - - - -
8be3308e by Andreas Klebinger at 2026-01-08T11:13:41+01:00
Allow join jumps below sccs
- - - - -
5490142c by Andreas Klebinger at 2026-01-08T11:13:41+01:00
Use a predicate for joinablility
- - - - -
38b782f0 by sheaf at 2026-01-09T17:04:22+01:00
WIP: turn off case-of-case when join point occurs under prof ticks
- - - - -
1412 changed files:
- .gitattributes
- .gitlab-ci.yml
- .gitlab/ci.sh
- .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
- .gitlab/rel_eng/upload_ghc_libs.py
- .gitlab/test-metrics.sh
- .gitmodules
- cabal.project-reinstall
- compile_flags.txt
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/PrimOps.hs
- compiler/GHC/Builtin/PrimOps/Ids.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Literals.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Builtin/Uniques.hs
- compiler/GHC/Builtin/Utils.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/Breakpoints.hs
- compiler/GHC/ByteCode/InfoTable.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Linker.hs
- + compiler/GHC/ByteCode/Serialize.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Cmm.hs
- compiler/GHC/Cmm/BlockId.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/CommonBlockElim.hs
- compiler/GHC/Cmm/Config.hs
- compiler/GHC/Cmm/ContFlowOpt.hs
- compiler/GHC/Cmm/Dataflow.hs
- compiler/GHC/Cmm/Dataflow/Block.hs
- compiler/GHC/Cmm/Dataflow/Graph.hs
- compiler/GHC/Cmm/Dataflow/Label.hs
- compiler/GHC/Cmm/DebugBlock.hs
- compiler/GHC/Cmm/Dominators.hs
- compiler/GHC/Cmm/Expr.hs
- compiler/GHC/Cmm/Graph.hs
- compiler/GHC/Cmm/Info.hs
- compiler/GHC/Cmm/Info/Build.hs
- compiler/GHC/Cmm/LRegSet.hs
- compiler/GHC/Cmm/LayoutStack.hs
- compiler/GHC/Cmm/Lint.hs
- compiler/GHC/Cmm/Liveness.hs
- compiler/GHC/Cmm/MachOp.hs
- compiler/GHC/Cmm/Node.hs
- compiler/GHC/Cmm/Opt.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Cmm/Pipeline.hs
- compiler/GHC/Cmm/ProcPoint.hs
- compiler/GHC/Cmm/Reducibility.hs
- compiler/GHC/Cmm/Reg.hs
- compiler/GHC/Cmm/Sink.hs
- compiler/GHC/Cmm/Switch.hs
- compiler/GHC/Cmm/Switch/Implement.hs
- compiler/GHC/Cmm/ThreadSanitizer.hs
- compiler/GHC/Cmm/UniqueRenamer.hs
- compiler/GHC/Cmm/Utils.hs
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/CmmToAsm/AArch64/RegInfo.hs
- compiler/GHC/CmmToAsm/BlockLayout.hs
- compiler/GHC/CmmToAsm/CFG.hs
- compiler/GHC/CmmToAsm/CPrim.hs
- compiler/GHC/CmmToAsm/Config.hs
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Format.hs
- compiler/GHC/CmmToAsm/LA64/CodeGen.hs
- compiler/GHC/CmmToAsm/LA64/Ppr.hs
- compiler/GHC/CmmToAsm/Monad.hs
- compiler/GHC/CmmToAsm/PPC/CodeGen.hs
- compiler/GHC/CmmToAsm/PPC/Ppr.hs
- compiler/GHC/CmmToAsm/PPC/RegInfo.hs
- compiler/GHC/CmmToAsm/Ppr.hs
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToAsm/Reg/Graph.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Coalesce.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs
- compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs
- compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs
- compiler/GHC/CmmToAsm/Reg/Linear.hs
- compiler/GHC/CmmToAsm/Reg/Linear/Base.hs
- compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs
- compiler/GHC/CmmToAsm/Reg/Linear/State.hs
- compiler/GHC/CmmToAsm/Reg/Linear/X86.hs
- compiler/GHC/CmmToAsm/Reg/Linear/X86_64.hs
- compiler/GHC/CmmToAsm/Reg/Liveness.hs
- + compiler/GHC/CmmToAsm/Reg/Regs.hs
- compiler/GHC/CmmToAsm/Reg/Target.hs
- compiler/GHC/CmmToAsm/Wasm.hs
- compiler/GHC/CmmToAsm/Wasm/Asm.hs
- compiler/GHC/CmmToAsm/Wasm/FromCmm.hs
- compiler/GHC/CmmToAsm/Wasm/Types.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/CmmToLlvm/Data.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion.hs-boot
- compiler/GHC/Core/Coercion/Axiom.hs
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/FamInstEnv.hs
- compiler/GHC/Core/InstEnv.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/LateCC/TopLevelBinds.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Lint/Interactive.hs
- compiler/GHC/Core/Make.hs
- compiler/GHC/Core/Map/Expr.hs
- compiler/GHC/Core/Map/Type.hs
- compiler/GHC/Core/Multiplicity.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CSE.hs
- compiler/GHC/Core/Opt/CallArity.hs
- compiler/GHC/Core/Opt/CallerCC.hs
- compiler/GHC/Core/Opt/ConstantFold.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Monad.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/Pipeline.hs
- compiler/GHC/Core/Opt/Pipeline/Types.hs
- compiler/GHC/Core/Opt/SetLevels.hs
- compiler/GHC/Core/Opt/Simplify.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/Simplify/Monad.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Opt/WorkWrap.hs
- compiler/GHC/Core/PatSyn.hs
- compiler/GHC/Core/Ppr.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/RoughMap.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/TyCo/Compare.hs
- compiler/GHC/Core/TyCo/FVs.hs
- compiler/GHC/Core/TyCo/Ppr.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/TyCo/Subst.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/TyCon/Env.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Type.hs-boot
- compiler/GHC/Core/Unfold/Make.hs
- compiler/GHC/Core/Unify.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/CoreToStg.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Data/Bag.hs
- compiler/GHC/Data/FastString.hs
- compiler/GHC/Data/FlatBag.hs
- compiler/GHC/Data/Graph/Collapse.hs
- compiler/GHC/Data/Graph/Color.hs
- compiler/GHC/Data/Graph/Directed.hs
- compiler/GHC/Data/List/Infinite.hs
- compiler/GHC/Data/List/NonEmpty.hs
- compiler/GHC/Data/Maybe.hs
- compiler/GHC/Data/OsPath.hs
- compiler/GHC/Data/Pair.hs
- compiler/GHC/Data/SmallArray.hs
- compiler/GHC/Data/Stream.hs
- compiler/GHC/Data/Strict.hs
- compiler/GHC/Data/StringBuffer.hs
- compiler/GHC/Data/TrieMap.hs
- compiler/GHC/Data/Word64Map.hs
- compiler/GHC/Data/Word64Map/Internal.hs
- compiler/GHC/Data/Word64Map/Lazy.hs
- compiler/GHC/Driver/Backend.hs
- compiler/GHC/Driver/Backpack.hs
- + compiler/GHC/Driver/ByteCode.hs
- compiler/GHC/Driver/CmdLine.hs
- compiler/GHC/Driver/CodeOutput.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- compiler/GHC/Driver/Config/Core/Lint.hs
- compiler/GHC/Driver/Config/Core/Lint/Interactive.hs
- compiler/GHC/Driver/Config/Core/Opt/Simplify.hs
- compiler/GHC/Driver/Config/Finder.hs
- + compiler/GHC/Driver/Config/Interpreter.hs
- compiler/GHC/Driver/Config/Linker.hs
- compiler/GHC/Driver/Config/Stg/Debug.hs
- compiler/GHC/Driver/Config/StgToCmm.hs
- compiler/GHC/Driver/Config/Tidy.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Env.hs
- compiler/GHC/Driver/Env/KnotVars.hs
- compiler/GHC/Driver/Env/Types.hs
- compiler/GHC/Driver/Errors.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/GenerateCgIPEStub.hs
- compiler/GHC/Driver/Hooks.hs
- compiler/GHC/Driver/LlvmConfigCache.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Driver/MakeSem.hs
- compiler/GHC/Driver/Messager.hs
- compiler/GHC/Driver/Monad.hs
- compiler/GHC/Driver/Phases.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Pipeline/LogQueue.hs
- compiler/GHC/Driver/Pipeline/Monad.hs
- compiler/GHC/Driver/Pipeline/Phases.hs
- compiler/GHC/Driver/Plugins.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Driver/Session/Inspect.hs
- compiler/GHC/Driver/Session/Units.hs
- compiler/GHC/Hs.hs
- compiler/GHC/Hs/Basic.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Doc.hs
- compiler/GHC/Hs/Doc.hs-boot
- compiler/GHC/Hs/DocString.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Expr.hs-boot
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Lit.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Pat.hs-boot
- compiler/GHC/Hs/Stats.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/HsToCore/Arrows.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Breakpoints.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Foreign/C.hs
- compiler/GHC/HsToCore/Foreign/Decl.hs
- compiler/GHC/HsToCore/Foreign/JavaScript.hs
- compiler/GHC/HsToCore/Foreign/Wasm.hs
- compiler/GHC/HsToCore/ListComp.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Match/Literal.hs
- compiler/GHC/HsToCore/Monad.hs
- compiler/GHC/HsToCore/Pmc.hs
- compiler/GHC/HsToCore/Pmc/Check.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Pmc/Solver.hs
- compiler/GHC/HsToCore/Pmc/Solver/Types.hs
- compiler/GHC/HsToCore/Pmc/Types.hs
- compiler/GHC/HsToCore/Pmc/Utils.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/HsToCore/Usage.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/Iface/Binary.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Env.hs
- compiler/GHC/Iface/Errors.hs
- compiler/GHC/Iface/Errors/Ppr.hs
- compiler/GHC/Iface/Errors/Types.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Ext/Debug.hs
- compiler/GHC/Iface/Ext/Types.hs
- compiler/GHC/Iface/Ext/Utils.hs
- compiler/GHC/Iface/Flags.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Iface/Recomp/Flags.hs
- compiler/GHC/Iface/Rename.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Tidy.hs
- compiler/GHC/Iface/Tidy/StaticPtrTable.hs
- compiler/GHC/Iface/Type.hs
- compiler/GHC/Iface/Warnings.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/JS/Ident.hs
- compiler/GHC/JS/JStg/Monad.hs
- compiler/GHC/JS/JStg/Syntax.hs
- compiler/GHC/JS/Make.hs
- compiler/GHC/JS/Optimizer.hs
- compiler/GHC/JS/Ppr.hs
- compiler/GHC/JS/Syntax.hs
- compiler/GHC/JS/Transform.hs
- + compiler/GHC/Linker/ByteCode.hs
- compiler/GHC/Linker/Config.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Dynamic.hs
- + compiler/GHC/Linker/Executable.hs
- − compiler/GHC/Linker/ExtraObj.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/MacOS.hs
- compiler/GHC/Linker/Static.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Linker/Windows.hs
- compiler/GHC/Llvm/MetaData.hs
- compiler/GHC/Llvm/Ppr.hs
- compiler/GHC/Llvm/Types.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Errors/Basic.hs
- 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/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Parser/String.hs
- compiler/GHC/Parser/Types.hs
- compiler/GHC/Platform.hs
- compiler/GHC/Platform/Reg.hs
- compiler/GHC/Platform/Reg/Class.hs
- compiler/GHC/Platform/Reg/Class/NoVectors.hs
- compiler/GHC/Platform/Reg/Class/Separate.hs
- compiler/GHC/Platform/Reg/Class/Unified.hs
- compiler/GHC/Prelude/Basic.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Expr.hs-boot
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Rename/Unbound.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Runtime/Debugger.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Heap/Layout.hs
- compiler/GHC/Runtime/Interpreter.hs
- + compiler/GHC/Runtime/Interpreter/C.hs
- + compiler/GHC/Runtime/Interpreter/Init.hs
- compiler/GHC/Runtime/Interpreter/JS.hs
- compiler/GHC/Runtime/Interpreter/Process.hs
- compiler/GHC/Runtime/Interpreter/Types.hs
- compiler/GHC/Runtime/Interpreter/Types/SymbolCache.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/EnforceEpt/Rewrite.hs
- compiler/GHC/Stg/EnforceEpt/TagSig.hs
- compiler/GHC/Stg/EnforceEpt/Types.hs
- compiler/GHC/Stg/FVs.hs
- compiler/GHC/Stg/Lift/Analysis.hs
- compiler/GHC/Stg/Lift/Monad.hs
- compiler/GHC/Stg/Lift/Types.hs
- compiler/GHC/Stg/Lint.hs
- compiler/GHC/Stg/Pipeline.hs
- compiler/GHC/Stg/Syntax.hs
- compiler/GHC/Stg/Unarise.hs
- compiler/GHC/Stg/Utils.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm.hs
- compiler/GHC/StgToCmm/ArgRep.hs
- compiler/GHC/StgToCmm/Bind.hs
- compiler/GHC/StgToCmm/CgUtils.hs
- compiler/GHC/StgToCmm/Closure.hs
- compiler/GHC/StgToCmm/ExtCode.hs
- compiler/GHC/StgToCmm/InfoTableProv.hs
- compiler/GHC/StgToCmm/Lit.hs
- compiler/GHC/StgToCmm/Monad.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToCmm/Utils.hs
- compiler/GHC/StgToJS/Apply.hs
- compiler/GHC/StgToJS/Arg.hs
- compiler/GHC/StgToJS/CodeGen.hs
- compiler/GHC/StgToJS/DataCon.hs
- compiler/GHC/StgToJS/Deps.hs
- compiler/GHC/StgToJS/Expr.hs
- compiler/GHC/StgToJS/ExprCtx.hs
- compiler/GHC/StgToJS/FFI.hs
- compiler/GHC/StgToJS/Heap.hs
- compiler/GHC/StgToJS/Ids.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/StgToJS/Linker/Opt.hs
- compiler/GHC/StgToJS/Linker/Types.hs
- compiler/GHC/StgToJS/Literal.hs
- compiler/GHC/StgToJS/Monad.hs
- compiler/GHC/StgToJS/Object.hs
- compiler/GHC/StgToJS/Prim.hs
- compiler/GHC/StgToJS/Regs.hs
- compiler/GHC/StgToJS/Rts/Rts.hs
- compiler/GHC/StgToJS/Rts/Types.hs
- compiler/GHC/StgToJS/Sinker/Collect.hs
- compiler/GHC/StgToJS/Sinker/Sinker.hs
- compiler/GHC/StgToJS/Sinker/StringsUnfloat.hs
- compiler/GHC/StgToJS/Types.hs
- compiler/GHC/StgToJS/Utils.hs
- compiler/GHC/SysTools.hs
- compiler/GHC/SysTools/Ar.hs
- compiler/GHC/SysTools/BaseDir.hs
- compiler/GHC/SysTools/Cpp.hs
- compiler/GHC/SysTools/Tasks.hs
- compiler/GHC/SysTools/Terminal.hs
- compiler/GHC/Tc/Deriv.hs
- compiler/GHC/Tc/Deriv/Functor.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/Hole.hs
- compiler/GHC/Tc/Errors/Hole/FitTypes.hs
- compiler/GHC/Tc/Errors/Hole/Plugin.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Errors/Types/PromotionErr.hs
- compiler/GHC/Tc/Gen/Annotation.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Default.hs
- compiler/GHC/Tc/Gen/Do.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Expr.hs-boot
- compiler/GHC/Tc/Gen/Foreign.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Gen/Match.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/Instance/Family.hs
- compiler/GHC/Tc/Instance/FunDeps.hs
- compiler/GHC/Tc/Instance/Typeable.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/FunDeps.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Irred.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Rewrite.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/Solver/Solve.hs-boot
- compiler/GHC/Tc/Solver/Types.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Build.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/ErrCtxt.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Backpack.hs
- compiler/GHC/Tc/Utils/Concrete.hs
- compiler/GHC/Tc/Utils/Env.hs
- compiler/GHC/Tc/Utils/Instantiate.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/Monad.hs
- compiler/GHC/Tc/Zonk/TcType.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Types/Annotations.hs
- + compiler/GHC/Types/Arity.hs
- compiler/GHC/Types/Avail.hs
- compiler/GHC/Types/Basic.hs
- compiler/GHC/Types/CompleteMatch.hs
- compiler/GHC/Types/CostCentre.hs
- compiler/GHC/Types/CostCentre/State.hs
- compiler/GHC/Types/DefaultEnv.hs
- compiler/GHC/Types/Demand.hs
- compiler/GHC/Types/Error.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/FieldLabel.hs
- compiler/GHC/Types/Fixity.hs
- compiler/GHC/Types/ForeignCall.hs
- compiler/GHC/Types/ForeignStubs.hs
- compiler/GHC/Types/GREInfo.hs
- compiler/GHC/Types/Hint.hs
- compiler/GHC/Types/Hint/Ppr.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Info.hs
- compiler/GHC/Types/Id/Make.hs
- + compiler/GHC/Types/InlinePragma.hs
- compiler/GHC/Types/Literal.hs
- compiler/GHC/Types/Name.hs
- compiler/GHC/Types/Name/Cache.hs
- compiler/GHC/Types/Name/Occurrence.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Types/Name/Set.hs
- compiler/GHC/Types/PkgQual.hs
- compiler/GHC/Types/RepType.hs
- compiler/GHC/Types/SaneDouble.hs
- compiler/GHC/Types/SourceError.hs
- compiler/GHC/Types/SourceText.hs
- compiler/GHC/Types/SptEntry.hs
- compiler/GHC/Types/SrcLoc.hs
- compiler/GHC/Types/Tickish.hs
- compiler/GHC/Types/TyThing.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/DSet.hs
- compiler/GHC/Types/Unique/FM.hs
- compiler/GHC/Types/Unique/Map.hs
- compiler/GHC/Types/Unique/SDFM.hs
- compiler/GHC/Types/Unique/Set.hs
- compiler/GHC/Types/Unique/Supply.hs
- compiler/GHC/Types/Var.hs
- compiler/GHC/Types/Var/Env.hs
- compiler/GHC/Unit.hs
- compiler/GHC/Unit/Env.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Finder/Types.hs
- compiler/GHC/Unit/Home/ModInfo.hs
- compiler/GHC/Unit/Home/PackageTable.hs
- compiler/GHC/Unit/Info.hs
- compiler/GHC/Unit/Module.hs
- compiler/GHC/Unit/Module/Deps.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Unit/Module/Location.hs
- compiler/GHC/Unit/Module/ModIface.hs
- compiler/GHC/Unit/Module/ModSummary.hs
- compiler/GHC/Unit/Module/Status.hs
- compiler/GHC/Unit/Module/Warnings.hs
- compiler/GHC/Unit/Module/WholeCoreBindings.hs
- compiler/GHC/Unit/State.hs
- compiler/GHC/Unit/Types.hs
- compiler/GHC/Unit/Types.hs-boot
- compiler/GHC/Utils/Binary.hs
- compiler/GHC/Utils/Binary/Typeable.hs
- + compiler/GHC/Utils/EndoOS.hs
- compiler/GHC/Utils/Error.hs
- compiler/GHC/Utils/Exception.hs
- compiler/GHC/Utils/Json.hs
- compiler/GHC/Utils/Logger.hs
- compiler/GHC/Utils/Misc.hs
- compiler/GHC/Utils/Monad/Codensity.hs
- compiler/GHC/Utils/Outputable.hs
- compiler/GHC/Utils/Panic.hs
- compiler/GHC/Utils/Panic/Plain.hs
- compiler/GHC/Wasm/ControlFlow.hs
- compiler/GHC/Wasm/ControlFlow/FromCmm.hs
- compiler/Language/Haskell/Syntax.hs
- compiler/Language/Haskell/Syntax/Basic.hs
- compiler/Language/Haskell/Syntax/Binds.hs
- + compiler/Language/Haskell/Syntax/Binds/InlinePragma.hs
- compiler/Language/Haskell/Syntax/Decls.hs
- compiler/Language/Haskell/Syntax/Expr.hs
- compiler/Language/Haskell/Syntax/Expr.hs-boot
- compiler/Language/Haskell/Syntax/Extension.hs
- compiler/Language/Haskell/Syntax/ImpExp.hs
- compiler/Language/Haskell/Syntax/Lit.hs
- compiler/Language/Haskell/Syntax/Pat.hs
- compiler/Language/Haskell/Syntax/Pat.hs-boot
- compiler/Language/Haskell/Syntax/Type.hs
- compiler/Setup.hs
- compiler/ghc.cabal.in
- configure.ac
- docs/users_guide/9.16.1-notes.rst
- docs/users_guide/bugs.rst
- docs/users_guide/compare-flags.py
- 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/arrows.rst
- docs/users_guide/exts/data_kinds.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/explicit_namespaces.rst
- docs/users_guide/exts/gadt.rst
- docs/users_guide/exts/gadt_syntax.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/pragmas.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/table.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/exts/type_families.rst
- docs/users_guide/ghci.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-optimisation.rst
- docs/users_guide/using.rst
- docs/users_guide/wasm.rst
- docs/users_guide/win32-dlls.rst
- − driver/utils/merge_sections.ld
- − driver/utils/merge_sections_pe.ld
- ghc/GHC/Driver/Session/Lint.hs
- ghc/GHC/Driver/Session/Mode.hs
- ghc/GHCi/Leak.hs
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Exception.hs
- ghc/GHCi/UI/Info.hs
- ghc/GHCi/UI/Monad.hs
- ghc/Main.hs
- ghc/ghc-bin.cabal.in
- hadrian/bindist/config.mk.in
- hadrian/cabal.project
- hadrian/doc/flavours.md
- hadrian/hadrian.cabal
- hadrian/src/Base.hs
- hadrian/src/Builder.hs
- hadrian/src/Context.hs
- hadrian/src/Flavour.hs
- hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
- hadrian/src/Hadrian/Haskell/Cabal/Type.hs
- hadrian/src/Hadrian/Haskell/Hash.hs
- hadrian/src/Hadrian/Oracles/ArgsHash.hs
- hadrian/src/Hadrian/Oracles/Cabal/Type.hs
- hadrian/src/Hadrian/Oracles/DirectoryContents.hs
- hadrian/src/Hadrian/Oracles/Path.hs
- hadrian/src/Hadrian/Oracles/TextFile.hs
- hadrian/src/Hadrian/Utilities.hs
- hadrian/src/Oracles/Flag.hs
- hadrian/src/Oracles/Flavour.hs
- hadrian/src/Oracles/ModuleFiles.hs
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Packages.hs
- hadrian/src/Rules.hs
- hadrian/src/Rules/Gmp.hs
- hadrian/src/Rules/Libffi.hs
- hadrian/src/Rules/Library.hs
- hadrian/src/Rules/Register.hs
- hadrian/src/Rules/ToolArgs.hs
- hadrian/src/Settings.hs
- hadrian/src/Settings/Builders/Cabal.hs
- hadrian/src/Settings/Builders/Common.hs
- hadrian/src/Settings/Builders/DeriveConstants.hs
- hadrian/src/Settings/Builders/Ghc.hs
- hadrian/src/Settings/Builders/Hsc2Hs.hs
- − hadrian/src/Settings/Builders/MergeObjects.hs
- hadrian/src/Settings/Builders/RunTest.hs
- hadrian/src/Settings/Builders/SplitSections.hs
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Flavours/Validate.hs
- hadrian/src/Settings/Packages.hs
- hadrian/src/Settings/Warnings.hs
- hadrian/stack.yaml
- hadrian/stack.yaml.lock
- libraries/base/base.cabal.in
- libraries/base/changelog.md
- libraries/base/src/Data/List.hs
- libraries/base/src/Data/List/NonEmpty.hs
- + libraries/base/src/Data/List/NubOrdSet.hs
- libraries/base/src/GHC/Base.hs
- libraries/base/src/GHC/Exts.hs
- libraries/base/src/GHC/Num.hs
- libraries/base/src/System/IO.hs
- libraries/base/tests/all.T
- libraries/exceptions
- libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs
- libraries/ghc-boot/GHC/Unit/Database.hs
- libraries/ghc-boot/Setup.hs
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghc-experimental/CHANGELOG.md
- libraries/ghc-experimental/src/GHC/Stack/Annotation/Experimental.hs
- + libraries/ghc-internal/cbits/RtsIface.c
- libraries/ghc-internal/cbits/Stack_c.c
- − libraries/ghc-internal/cbits/mulIntMayOflo.c
- libraries/ghc-internal/configure.ac
- libraries/ghc-internal/ghc-internal.cabal.in
- libraries/ghc-internal/include/HsIntegerGmp.h.in
- + libraries/ghc-internal/include/RtsIfaceSymbols.h
- libraries/ghc-internal/src/GHC/Internal/Control/Monad.hs
- libraries/ghc-internal/src/GHC/Internal/Control/Monad/ST/Lazy/Imp.hs
- libraries/ghc-internal/src/GHC/Internal/Data/OldList.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs
- libraries/ghc-internal/src/GHC/Internal/Float.hs
- libraries/ghc-internal/src/GHC/Internal/Functor/ZipList.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Handle.hs
- libraries/ghc-internal/src/GHC/Internal/List.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/System/IO.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Monad.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Quote.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Syntax.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-prim/changelog.md
- libraries/os-string
- + libraries/template-haskell-lift
- + libraries/template-haskell-quasiquoter
- libraries/template-haskell/vendored-filepath/System/FilePath/Posix.hs
- libraries/template-haskell/vendored-filepath/System/FilePath/Windows.hs
- libraries/unix
- libraries/xhtml
- linters/lint-codes/LintCodes/Static.hs
- − m4/find_ghc_bootstrap_prog.m4
- m4/fp_check_pthreads.m4
- − m4/fp_copy_shellvar.m4
- − m4/fp_prog_ld_flag.m4
- − m4/fp_prog_sort.m4
- m4/fptools_alex.m4
- m4/fptools_happy.m4
- m4/prep_target_file.m4
- − mk/win32-tarballs.md5sum
- + rts/.ubsan-suppressions
- rts/Apply.cmm
- rts/BuiltinClosures.c
- rts/CloneStack.h
- rts/Compact.cmm
- rts/ContinuationOps.cmm
- rts/Exception.cmm
- rts/Interpreter.c
- rts/Jumps.h
- rts/Prelude.h
- rts/PrimOps.cmm
- rts/Printer.c
- rts/RtsAPI.c
- rts/RtsMessages.c
- rts/RtsStartup.c
- rts/RtsSymbols.c
- + rts/RtsToHsIface.c
- rts/StgMiscClosures.cmm
- rts/StgStartup.cmm
- rts/StgStdThunks.cmm
- rts/ThreadPaused.c
- rts/configure.ac
- rts/eventlog/EventLog.c
- − rts/external-symbols.list.in
- rts/gen_event_types.py
- rts/include/Rts.h
- rts/include/RtsAPI.h
- rts/include/Stg.h
- rts/include/rts/Bytecodes.h
- rts/include/rts/Messages.h
- + rts/include/rts/RtsToHsIface.h
- rts/include/rts/Types.h
- rts/include/rts/storage/Block.h
- rts/include/stg/Prim.h
- rts/include/stg/Types.h
- rts/linker/Elf.c
- rts/linker/InitFini.c
- rts/linker/LoadArchive.c
- rts/linker/PEi386.c
- rts/posix/OSMem.c
- rts/posix/Signals.c
- 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
- + 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/NonMoving.c
- rts/sm/NonMovingMark.c
- rts/sm/Sanity.c
- rts/sm/Scav.c
- rts/wasm/JSFFI.c
- rts/wasm/scheduler.cmm
- rts/win32/libHSghc-internal.def
- testsuite/config/ghc
- testsuite/driver/cpu_features.py
- testsuite/driver/runtests.py
- testsuite/driver/testglobals.py
- testsuite/driver/testlib.py
- testsuite/mk/boilerplate.mk
- testsuite/tests/backpack/should_fail/T19244a.stderr
- + testsuite/tests/bytecode/T23973.hs
- + testsuite/tests/bytecode/T23973.script
- + testsuite/tests/bytecode/T23973.stdout
- testsuite/tests/bytecode/T24634/T24634a.stdout
- testsuite/tests/bytecode/T24634/T24634b.stdout
- + testsuite/tests/bytecode/T26565.hs
- + testsuite/tests/bytecode/T26565.script
- + testsuite/tests/bytecode/T26565.stdout
- + testsuite/tests/bytecode/T26640.hs
- + testsuite/tests/bytecode/T26640.script
- + testsuite/tests/bytecode/T26640.stdout
- testsuite/tests/bytecode/all.T
- + testsuite/tests/cabal/Bytecode.hs
- + testsuite/tests/cabal/BytecodeForeign.c
- + testsuite/tests/cabal/BytecodeForeign.hs
- testsuite/tests/cabal/Makefile
- testsuite/tests/cabal/all.T
- + testsuite/tests/cabal/bytecode.pkg
- + testsuite/tests/cabal/bytecode.script
- + testsuite/tests/cabal/bytecode_foreign.pkg
- + testsuite/tests/cabal/bytecode_foreign.script
- testsuite/tests/cabal/ghcpkg03.stderr
- testsuite/tests/cabal/ghcpkg03.stderr-mingw32
- testsuite/tests/cabal/ghcpkg05.stderr
- testsuite/tests/cabal/ghcpkg05.stderr-mingw32
- + testsuite/tests/cabal/pkg_bytecode.stderr
- + testsuite/tests/cabal/pkg_bytecode.stdout
- + testsuite/tests/cabal/pkg_bytecode_foreign.stderr
- + testsuite/tests/cabal/pkg_bytecode_foreign.stdout
- + testsuite/tests/cabal/pkg_bytecode_with_gbc.stderr
- + testsuite/tests/cabal/pkg_bytecode_with_gbc.stdout
- + testsuite/tests/cabal/pkg_bytecode_with_o.stderr
- + testsuite/tests/cabal/pkg_bytecode_with_o.stdout
- + testsuite/tests/cmm/opt/T25664.hs
- + testsuite/tests/cmm/opt/T25664.stdout
- testsuite/tests/cmm/opt/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/T24016.hs
- + testsuite/tests/codeGen/should_run/T24016.stdout
- + testsuite/tests/codeGen/should_run/T26537.hs
- + testsuite/tests/codeGen/should_run/T26537.stdout
- testsuite/tests/codeGen/should_run/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/default/default-fail05.stderr
- testsuite/tests/dependent/should_fail/T11334b.stderr
- testsuite/tests/dependent/should_fail/T13135_simple.stderr
- testsuite/tests/deriving/should_fail/T3621.stderr
- testsuite/tests/diagnostic-codes/codes.stdout
- testsuite/tests/driver/Makefile
- testsuite/tests/driver/T11429c.stderr
- + testsuite/tests/driver/T20696/T20696.stderr-ext-interp
- testsuite/tests/driver/T21682.stderr
- + testsuite/tests/driver/T24120.hs
- + testsuite/tests/driver/T24731.hs
- + testsuite/tests/driver/T26551.hs
- + testsuite/tests/driver/T26551.stderr
- testsuite/tests/driver/all.T
- + 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_object20.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object21.stderr
- + testsuite/tests/driver/bytecode-object/bytecode_object21.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object23.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object24.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/fat-iface/fat012.stderr-ext-interp
- + testsuite/tests/driver/fat-iface/fat015.stderr-ext-interp
- testsuite/tests/driver/j-space/jspace.hs
- + testsuite/tests/driver/recomp26183/M.hs
- + testsuite/tests/driver/recomp26183/M2A.hs
- + testsuite/tests/driver/recomp26183/M2B.hs
- + testsuite/tests/driver/recomp26183/Makefile
- + testsuite/tests/driver/recomp26183/all.T
- + testsuite/tests/driver/recomp26183/recomp26183.stderr
- + testsuite/tests/driver/recomp26705/M.hs
- + testsuite/tests/driver/recomp26705/M2A.hs
- + testsuite/tests/driver/recomp26705/M2B.hs
- + testsuite/tests/driver/recomp26705/Makefile
- + testsuite/tests/driver/recomp26705/all.T
- + testsuite/tests/driver/recomp26705/recomp26705.stderr
- testsuite/tests/generics/T10604/T10604_deriving.stderr
- + testsuite/tests/ghc-api-browser/README.md
- + testsuite/tests/ghc-api-browser/all.T
- + testsuite/tests/ghc-api-browser/index.html
- + testsuite/tests/ghc-api-browser/playground001.hs
- + testsuite/tests/ghc-api-browser/playground001.js
- + testsuite/tests/ghc-api-browser/playground001.sh
- testsuite/tests/ghci-wasm/T26431.stdout → testsuite/tests/ghc-api-browser/playground001.stdout
- testsuite/tests/ghc-api/T10942.hs
- + testsuite/tests/ghc-api/T26264.hs
- + testsuite/tests/ghc-api/T26264.stdout
- testsuite/tests/ghc-api/all.T
- testsuite/tests/ghc-api/annotations-literals/literals.hs
- testsuite/tests/ghc-e/should_fail/T9930fail.stderr
- testsuite/tests/ghc-e/should_fail/all.T
- − testsuite/tests/ghci-wasm/T26431.hs
- testsuite/tests/ghci-wasm/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/T8353.stderr
- testsuite/tests/ghci/scripts/T8959b.stderr
- testsuite/tests/ghci/scripts/ghci051.stderr
- 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/indexed-types/should_compile/CEqCanOccursCheck.hs
- testsuite/tests/indexed-types/should_compile/T12538.stderr
- testsuite/tests/indexed-types/should_fail/T12522a.hs
- testsuite/tests/indexed-types/should_fail/T14369.stderr
- testsuite/tests/indexed-types/should_fail/T14887.stderr
- testsuite/tests/indexed-types/should_fail/T1897b.stderr
- testsuite/tests/indexed-types/should_fail/T21092.hs
- − testsuite/tests/indexed-types/should_fail/T21092.stderr
- testsuite/tests/indexed-types/should_fail/T26176.stderr
- testsuite/tests/indexed-types/should_fail/all.T
- 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/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/jsffi/all.T
- + testsuite/tests/jsffi/bytearrayarg.hs
- + testsuite/tests/jsffi/bytearrayarg.mjs
- + testsuite/tests/jsffi/bytearrayarg.stdout
- + testsuite/tests/linear/should_compile/LinearEtaExpansions.hs
- testsuite/tests/linear/should_compile/all.T
- testsuite/tests/linear/should_fail/T19361.stderr
- testsuite/tests/linear/should_fail/TypeClass.hs
- testsuite/tests/linear/should_fail/TypeClass.stderr
- testsuite/tests/linear/should_run/LinearGhci.stdout
- + testsuite/tests/linear/should_run/T26311.hs
- + testsuite/tests/linear/should_run/T26311.stdout
- testsuite/tests/linear/should_run/all.T
- testsuite/tests/linters/all.T
- testsuite/tests/linters/notes.stdout
- testsuite/tests/llvm/should_run/all.T
- + testsuite/tests/module/T25901_exp_plain_wc.hs
- + testsuite/tests/module/T25901_exp_plain_wc.stderr
- + testsuite/tests/module/T25901_imp_plain_wc.hs
- + testsuite/tests/module/T25901_imp_plain_wc.stderr
- testsuite/tests/module/all.T
- testsuite/tests/module/mod4.stderr
- testsuite/tests/numeric/should_compile/T16402.stderr-ws-64
- testsuite/tests/numeric/should_run/all.T
- testsuite/tests/numeric/should_run/foundation.hs
- testsuite/tests/numeric/should_run/foundation.stdout
- testsuite/tests/overloadedrecflds/should_compile/BootFldReexport.stderr
- testsuite/tests/overloadedrecflds/should_fail/DRFHoleFits.stderr
- testsuite/tests/overloadedrecflds/should_fail/T16745.stderr
- testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.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_compile/DumpTypecheckedAst.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/T12488c.hs
- + testsuite/tests/parser/should_fail/T12488c.stderr
- + testsuite/tests/parser/should_fail/T12488d.hs
- + testsuite/tests/parser/should_fail/T12488d.stderr
- testsuite/tests/parser/should_fail/T20654a.stderr
- testsuite/tests/parser/should_fail/all.T
- testsuite/tests/partial-sigs/should_fail/T14584a.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/patsyn/should_fail/import-syntax-no-ext.hs
- + testsuite/tests/patsyn/should_fail/import-syntax-no-ext.stderr
- testsuite/tests/perf/compiler/Makefile
- + testsuite/tests/perf/compiler/MultiLayerModulesDefsGhciWithBytecodeFiles.script
- + testsuite/tests/perf/compiler/T26425.hs
- testsuite/tests/perf/compiler/all.T
- testsuite/tests/perf/compiler/hard_hole_fits.stderr
- testsuite/tests/perf/should_run/T3586.hs
- testsuite/tests/perf/should_run/UniqLoop.hs
- testsuite/tests/perf/should_run/all.T
- testsuite/tests/plugins/test-hole-plugin.stderr
- testsuite/tests/pmcheck/should_compile/T15753c.hs
- + testsuite/tests/pmcheck/should_compile/T15753c.stderr
- testsuite/tests/pmcheck/should_compile/T15753d.hs
- + testsuite/tests/pmcheck/should_compile/T15753d.stderr
- + testsuite/tests/pmcheck/should_compile/T22652.hs
- + testsuite/tests/pmcheck/should_compile/T22652a.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/pmcheck/should_compile/pmcOrPats.stderr
- + testsuite/tests/polykinds/T13882.hs
- testsuite/tests/polykinds/T6068.stdout
- testsuite/tests/polykinds/all.T
- testsuite/tests/quantified-constraints/T15316A.stderr
- testsuite/tests/quantified-constraints/T15359.hs
- testsuite/tests/quantified-constraints/T17267.stderr
- testsuite/tests/quantified-constraints/T17267a.stderr
- testsuite/tests/quantified-constraints/T17267b.stderr
- testsuite/tests/quantified-constraints/T17267c.stderr
- testsuite/tests/quantified-constraints/T17267e.stderr
- testsuite/tests/quantified-constraints/T17458.stderr
- testsuite/tests/regalloc/regalloc_unit_tests.hs
- + testsuite/tests/rename/should_compile/T12488b.hs
- + testsuite/tests/rename/should_compile/T12488f.hs
- + testsuite/tests/rename/should_compile/T25901_exp_1.hs
- + testsuite/tests/rename/should_compile/T25901_exp_1_helper.hs
- + testsuite/tests/rename/should_compile/T25901_exp_2.hs
- + testsuite/tests/rename/should_compile/T25901_exp_2_helper.hs
- + testsuite/tests/rename/should_compile/T25901_imp_hq.hs
- + testsuite/tests/rename/should_compile/T25901_imp_hu.hs
- + testsuite/tests/rename/should_compile/T25901_imp_sq.hs
- + testsuite/tests/rename/should_compile/T25901_imp_su.hs
- + testsuite/tests/rename/should_compile/T25901_sub_e.hs
- + testsuite/tests/rename/should_compile/T25901_sub_f.hs
- + testsuite/tests/rename/should_compile/T25901_sub_f.stderr
- + testsuite/tests/rename/should_compile/T25901_sub_g.hs
- + testsuite/tests/rename/should_compile/T25901_sub_g.stderr
- + testsuite/tests/rename/should_compile/T25901_sub_g_helper.hs
- testsuite/tests/rename/should_compile/all.T
- + testsuite/tests/rename/should_fail/T12488a.hs
- + testsuite/tests/rename/should_fail/T12488a.stderr
- + testsuite/tests/rename/should_fail/T12488a_foo.hs
- + testsuite/tests/rename/should_fail/T12488a_foo.stderr
- + testsuite/tests/rename/should_fail/T12488e.hs
- + testsuite/tests/rename/should_fail/T12488e.stderr
- + testsuite/tests/rename/should_fail/T12488g.hs
- + testsuite/tests/rename/should_fail/T12488g.stderr
- testsuite/tests/rename/should_fail/T19843h.stderr
- testsuite/tests/rename/should_fail/T23570b.stderr
- testsuite/tests/rename/should_fail/T25899e2.stderr
- + testsuite/tests/rename/should_fail/T25901_exp_fail_1.hs
- + testsuite/tests/rename/should_fail/T25901_exp_fail_1.stderr
- + testsuite/tests/rename/should_fail/T25901_exp_fail_1_helper.hs
- + testsuite/tests/rename/should_fail/T25901_exp_fail_2.hs
- + testsuite/tests/rename/should_fail/T25901_exp_fail_2.stderr
- + testsuite/tests/rename/should_fail/T25901_exp_fail_2_helper.hs
- + testsuite/tests/rename/should_fail/T25901_imp_hq_fail_5.hs
- + testsuite/tests/rename/should_fail/T25901_imp_hq_fail_5.stderr
- + testsuite/tests/rename/should_fail/T25901_imp_hq_fail_6.hs
- + testsuite/tests/rename/should_fail/T25901_imp_hq_fail_6.stderr
- + testsuite/tests/rename/should_fail/T25901_imp_hu_fail_4.hs
- + testsuite/tests/rename/should_fail/T25901_imp_hu_fail_4.stderr
- + testsuite/tests/rename/should_fail/T25901_imp_sq_fail_2.hs
- + testsuite/tests/rename/should_fail/T25901_imp_sq_fail_2.stderr
- + testsuite/tests/rename/should_fail/T25901_imp_sq_fail_3.hs
- + testsuite/tests/rename/should_fail/T25901_imp_sq_fail_3.stderr
- + testsuite/tests/rename/should_fail/T25901_imp_su_fail_1.hs
- + testsuite/tests/rename/should_fail/T25901_imp_su_fail_1.stderr
- + testsuite/tests/rename/should_fail/T25901_sub_a.hs
- + testsuite/tests/rename/should_fail/T25901_sub_a.stderr
- + testsuite/tests/rename/should_fail/T25901_sub_b.hs
- + testsuite/tests/rename/should_fail/T25901_sub_b.stderr
- + testsuite/tests/rename/should_fail/T25901_sub_c.hs
- + testsuite/tests/rename/should_fail/T25901_sub_c.stderr
- + testsuite/tests/rename/should_fail/T25901_sub_c_helper.hs
- + testsuite/tests/rename/should_fail/T25901_sub_d.hs
- + testsuite/tests/rename/should_fail/T25901_sub_d.stderr
- + testsuite/tests/rename/should_fail/T25901_sub_d_helper.hs
- + testsuite/tests/rename/should_fail/T25901_sub_w.hs
- + testsuite/tests/rename/should_fail/T25901_sub_w.stderr
- testsuite/tests/rename/should_fail/all.T
- testsuite/tests/rename/should_fail/rnfail055.stderr
- testsuite/tests/rep-poly/RepPolyCase1.stderr
- − testsuite/tests/rep-poly/RepPolyCase2.stderr
- testsuite/tests/rep-poly/RepPolyNPlusK.stderr
- testsuite/tests/rep-poly/RepPolyRightSection.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/T19709b.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/T23903.stderr
- + testsuite/tests/rep-poly/T26072.hs
- + testsuite/tests/rep-poly/T26072b.hs
- + testsuite/tests/rep-poly/T26528.hs
- testsuite/tests/rep-poly/UnliftedNewtypesLevityBinder.stderr
- testsuite/tests/rep-poly/all.T
- testsuite/tests/roles/should_compile/Roles13.stderr
- testsuite/tests/rts/KeepCafsBase.hs
- testsuite/tests/rts/T22859.hs
- 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/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/T26411.hs
- + testsuite/tests/simd/should_run/T26411.stdout
- + testsuite/tests/simd/should_run/T26411b.hs
- + testsuite/tests/simd/should_run/T26411b.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/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/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/T26349.hs
- + testsuite/tests/simplCore/should_compile/T26349.stderr
- + testsuite/tests/simplCore/should_compile/T26588.hs
- + testsuite/tests/simplCore/should_compile/T26589.hs
- + testsuite/tests/simplCore/should_compile/T26681.hs
- testsuite/tests/simplCore/should_compile/T4201.stdout
- testsuite/tests/simplCore/should_compile/T8331.stderr
- testsuite/tests/simplCore/should_compile/all.T
- testsuite/tests/simplCore/should_compile/rule2.stderr
- testsuite/tests/simplStg/should_compile/T22840.stderr
- testsuite/tests/simplStg/should_compile/all.T
- + testsuite/tests/splice-imports/SI07.stderr-ext-interp
- testsuite/tests/th/T15321.stderr
- + testsuite/tests/th/T26099.hs
- + testsuite/tests/th/T26099.stderr
- + testsuite/tests/th/T26568.hs
- + testsuite/tests/th/T26568.stderr
- testsuite/tests/th/T8761.stderr
- testsuite/tests/th/all.T
- testsuite/tests/typecheck/T16127/T16127.stderr
- testsuite/tests/typecheck/no_skolem_info/T13499.stderr
- testsuite/tests/typecheck/no_skolem_info/T20232.stderr
- testsuite/tests/typecheck/should_compile/T13050.stderr
- testsuite/tests/typecheck/should_compile/T13651.hs
- − testsuite/tests/typecheck/should_compile/T13651.stderr
- testsuite/tests/typecheck/should_compile/T14273.stderr
- testsuite/tests/typecheck/should_compile/T14590.stderr
- + testsuite/tests/typecheck/should_compile/T14745.hs
- testsuite/tests/typecheck/should_compile/T16188.hs
- + testsuite/tests/typecheck/should_compile/T17705.hs
- testsuite/tests/typecheck/should_compile/T22560d.stdout
- testsuite/tests/typecheck/should_compile/T25180.stderr
- + testsuite/tests/typecheck/should_compile/T26451.hs
- + testsuite/tests/typecheck/should_compile/T26582.hs
- testsuite/tests/typecheck/should_compile/abstract_refinement_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_compile/constraint_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/free_monad_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/hole_constraints.stderr
- testsuite/tests/typecheck/should_compile/hole_constraints_nested.stderr
- testsuite/tests/typecheck/should_compile/holes.stderr
- testsuite/tests/typecheck/should_compile/holes2.stderr
- testsuite/tests/typecheck/should_compile/holes3.stderr
- testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/subsumption_sort_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/tc126.hs
- testsuite/tests/typecheck/should_compile/type_in_type_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/valid_hole_fits_interactions.stderr
- testsuite/tests/typecheck/should_fail/AmbigFDs.hs
- − testsuite/tests/typecheck/should_fail/AmbigFDs.stderr
- testsuite/tests/typecheck/should_fail/ContextStack1.stderr
- testsuite/tests/typecheck/should_fail/FD3.stderr
- testsuite/tests/typecheck/should_fail/FDsFromGivens2.stderr
- testsuite/tests/typecheck/should_fail/FunDepOrigin1b.stderr
- testsuite/tests/typecheck/should_fail/T11672.stderr
- testsuite/tests/typecheck/should_fail/T12373.stderr
- testsuite/tests/typecheck/should_fail/T13506.stderr
- testsuite/tests/typecheck/should_fail/T14884.stderr
- testsuite/tests/typecheck/should_fail/T15629.stderr
- testsuite/tests/typecheck/should_fail/T15767.stderr
- testsuite/tests/typecheck/should_fail/T15807.stderr
- testsuite/tests/typecheck/should_fail/T15883e.stderr
- testsuite/tests/typecheck/should_fail/T16074.stderr
- testsuite/tests/typecheck/should_fail/T16512a.stderr
- testsuite/tests/typecheck/should_fail/T18357a.stderr
- testsuite/tests/typecheck/should_fail/T18851b.hs
- − testsuite/tests/typecheck/should_fail/T18851b.stderr
- testsuite/tests/typecheck/should_fail/T18851c.hs
- − testsuite/tests/typecheck/should_fail/T18851c.stderr
- testsuite/tests/typecheck/should_fail/T19415.stderr
- testsuite/tests/typecheck/should_fail/T19415b.stderr
- testsuite/tests/typecheck/should_fail/T19627.stderr
- testsuite/tests/typecheck/should_fail/T20241b.stderr
- testsuite/tests/typecheck/should_fail/T21530a.stderr
- testsuite/tests/typecheck/should_fail/T22684.stderr
- testsuite/tests/typecheck/should_fail/T22924b.stderr
- + testsuite/tests/typecheck/should_fail/T23162a.hs
- + testsuite/tests/typecheck/should_fail/T23162a.stderr
- + testsuite/tests/typecheck/should_fail/T23162b.hs
- + testsuite/tests/typecheck/should_fail/T23162b.stderr
- + testsuite/tests/typecheck/should_fail/T23162c.hs
- + testsuite/tests/typecheck/should_fail/T23162d.hs
- testsuite/tests/typecheck/should_fail/T2414.stderr
- testsuite/tests/typecheck/should_fail/T24279.hs
- − testsuite/tests/typecheck/should_fail/T24279.stderr
- testsuite/tests/typecheck/should_fail/T25325.stderr
- testsuite/tests/typecheck/should_fail/T2534.stderr
- testsuite/tests/typecheck/should_fail/T5236.stderr
- testsuite/tests/typecheck/should_fail/T5246.stderr
- testsuite/tests/typecheck/should_fail/T5978.stderr
- testsuite/tests/typecheck/should_fail/T7264.stderr
- testsuite/tests/typecheck/should_fail/T7368a.stderr
- testsuite/tests/typecheck/should_fail/T7696.stderr
- testsuite/tests/typecheck/should_fail/T8603.stderr
- testsuite/tests/typecheck/should_fail/T9612.stderr
- testsuite/tests/typecheck/should_fail/TcCoercibleFail.stderr
- testsuite/tests/typecheck/should_fail/TcStaticPointersFail03.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/tcfail122.stderr
- testsuite/tests/typecheck/should_fail/tcfail143.stderr
- testsuite/tests/unboxedsums/UbxSumUnpackedSize.hs
- + testsuite/tests/warnings/should_compile/DodgyExports02.hs
- + testsuite/tests/warnings/should_compile/DodgyExports02.stderr
- + testsuite/tests/warnings/should_compile/DodgyExports03.hs
- + testsuite/tests/warnings/should_compile/DodgyExports03.stderr
- testsuite/tests/warnings/should_compile/DodgyImports.stderr
- + testsuite/tests/warnings/should_compile/DodgyImports02.hs
- + testsuite/tests/warnings/should_compile/DodgyImports02.stderr
- + testsuite/tests/warnings/should_compile/DodgyImports03.hs
- + testsuite/tests/warnings/should_compile/DodgyImports03.stderr
- + testsuite/tests/warnings/should_compile/DodgyImports03_helper.hs
- + testsuite/tests/warnings/should_compile/DodgyImports04.hs
- + testsuite/tests/warnings/should_compile/DodgyImports04.stderr
- testsuite/tests/warnings/should_compile/DodgyImports_hiding.stderr
- + testsuite/tests/warnings/should_compile/DuplicateModExport.hs
- + testsuite/tests/warnings/should_compile/DuplicateModExport.stderr
- + testsuite/tests/warnings/should_compile/EmptyModExport.hs
- + testsuite/tests/warnings/should_compile/EmptyModExport.stderr
- + testsuite/tests/warnings/should_compile/T25901_exp_dodgy.hs
- + testsuite/tests/warnings/should_compile/T25901_exp_dodgy.stderr
- + testsuite/tests/warnings/should_compile/T25901_exp_dup_wc_1.hs
- + testsuite/tests/warnings/should_compile/T25901_exp_dup_wc_1.stderr
- + testsuite/tests/warnings/should_compile/T25901_exp_dup_wc_2.hs
- + testsuite/tests/warnings/should_compile/T25901_exp_dup_wc_2.stderr
- + testsuite/tests/warnings/should_compile/T25901_exp_dup_wc_3.hs
- + testsuite/tests/warnings/should_compile/T25901_exp_dup_wc_3.stderr
- + testsuite/tests/warnings/should_compile/T25901_exp_dup_wc_4.hs
- + testsuite/tests/warnings/should_compile/T25901_exp_dup_wc_4.stderr
- + testsuite/tests/warnings/should_compile/T25901_helper_1.hs
- + testsuite/tests/warnings/should_compile/T25901_helper_2.hs
- + testsuite/tests/warnings/should_compile/T25901_helper_3.hs
- + testsuite/tests/warnings/should_compile/T25901_imp_dodgy_1.hs
- + testsuite/tests/warnings/should_compile/T25901_imp_dodgy_1.stderr
- + testsuite/tests/warnings/should_compile/T25901_imp_dodgy_2.hs
- + testsuite/tests/warnings/should_compile/T25901_imp_dodgy_2.stderr
- + testsuite/tests/warnings/should_compile/T25901_imp_unused_1.hs
- + testsuite/tests/warnings/should_compile/T25901_imp_unused_1.stderr
- + testsuite/tests/warnings/should_compile/T25901_imp_unused_2.hs
- + testsuite/tests/warnings/should_compile/T25901_imp_unused_2.stderr
- + testsuite/tests/warnings/should_compile/T25901_imp_unused_3.hs
- + testsuite/tests/warnings/should_compile/T25901_imp_unused_3.stderr
- + testsuite/tests/warnings/should_compile/T25901_imp_unused_4.hs
- + testsuite/tests/warnings/should_compile/T25901_imp_unused_4.stderr
- testsuite/tests/warnings/should_compile/all.T
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Main.hs
- utils/check-exact/Parsers.hs
- utils/check-exact/Preprocess.hs
- utils/check-exact/Transform.hs
- utils/check-exact/Utils.hs
- utils/deriveConstants/Main.hs
- utils/genapply/Main.hs
- utils/genprimopcode/genprimopcode.cabal
- utils/ghc-pkg/Main.hs
- utils/ghc-toolchain/ghc-toolchain.cabal
- utils/ghc-toolchain/src/GHC/Toolchain/CheckArm.hs
- + utils/ghc-toolchain/src/GHC/Toolchain/CheckPower.hs
- utils/ghc-toolchain/src/GHC/Toolchain/ParseTriple.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/MergeObjs.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Utils.hs
- utils/haddock/cabal.project
- utils/haddock/haddock-api/haddock-api.cabal
- − utils/haddock/haddock-api/src/Haddock/Backends/HaddockDB.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.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/LaTeX.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Names.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Themes.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Utils.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/Doc.hs
- utils/haddock/haddock-api/src/Haddock/GhcUtils.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Create.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs
- utils/haddock/haddock-api/src/Haddock/Utils.hs
- utils/haddock/haddock-library/src/Documentation/Haddock/Parser.hs
- utils/haddock/haddock-test/src/Test/Haddock.hs
- utils/haddock/html-test/ref/Bug1004.html
- utils/haddock/html-test/ref/Bug1050.html
- utils/haddock/html-test/ref/Bug26.html
- + utils/haddock/html-test/ref/Bug26246.html
- utils/haddock/html-test/ref/Bug298.html
- utils/haddock/html-test/ref/Bug458.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/Nesting.html
- utils/haddock/html-test/ref/PatternSyns.html
- + utils/haddock/html-test/ref/PatternSyns2.html
- utils/haddock/html-test/ref/PromotedTypes.html
- utils/haddock/html-test/ref/TitledPicture.html
- utils/haddock/html-test/ref/TypeOperators.html
- utils/haddock/html-test/ref/Unicode.html
- utils/haddock/html-test/ref/Unicode2.html
- + utils/haddock/html-test/src/Bug26246.hs
- + utils/haddock/html-test/src/PatternSyns2.hs
- utils/haddock/hypsrc-test/ref/src/Classes.html
- utils/haddock/hypsrc-test/ref/src/Quasiquoter.html
- utils/haddock/latex-test/ref/LinearTypes/LinearTypes.tex
- utils/hpc
- utils/hsc2hs
- − utils/iserv/cbits/iservmain.c
- utils/iserv/iserv.cabal.in
- 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/6c07295a064dcb495bdbd17f36a0ed…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6c07295a064dcb495bdbd17f36a0ed…
You're receiving this email because of your account on gitlab.haskell.org.
1
0