[Git][ghc/ghc][wip/backports-9.14] 2 commits: Bump exceptions to 0.10.11
by Zubin (@wz1000) 31 Oct '25
by Zubin (@wz1000) 31 Oct '25
31 Oct '25
Zubin pushed to branch wip/backports-9.14 at Glasgow Haskell Compiler / GHC
Commits:
b213fd91 by Ben Gamari at 2025-10-31T17:37:45+05:30
Bump exceptions to 0.10.11
- - - - -
5e30da3a by Ben Gamari at 2025-10-31T17:37:45+05:30
Bump os-string to 2.0.8
- - - - -
3 changed files:
- libraries/exceptions
- libraries/os-string
- testsuite/tests/ghc-e/should_fail/T9930fail.stderr
Changes:
=====================================
libraries/exceptions
=====================================
@@ -1 +1 @@
-Subproject commit b6c4290124eb1138358bf04ad9f33e67f6c5c1d8
+Subproject commit 81bfd6e0ca631f315658201ae02e30046678f056
=====================================
libraries/os-string
=====================================
@@ -1 +1 @@
-Subproject commit 2e693aad07540173a0169971b27c9acac28eeff1
+Subproject commit c08666bf7bf528e607fc1eacc20032ec59e69df3
=====================================
testsuite/tests/ghc-e/should_fail/T9930fail.stderr
=====================================
@@ -7,5 +7,6 @@ While handling default output name would overwrite the input file; must specify
| Usage: For basic information, try the `--help' option.
HasCallStack backtrace:
- bracket, called at compiler/GHC/Driver/MakeAction.hs:2955:3 in ghc-9.13-inplace:GHC.Driver.MakeAction
-
+ throwIO, called at libraries/exceptions/src/Control/Monad/Catch.hs:1:1 in <package-id>:Control.Monad.Catch
+ throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:1:1 in <package-id>:Control.Monad.Catch
+ onException, called at compiler/GHC/Driver/MakeAction.hs:1:1 in <package-id>:GHC.Driver.MakeAction
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fa0cb6b48d0cb635e9d6b22a52fcf2…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fa0cb6b48d0cb635e9d6b22a52fcf2…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/9.12.3-backports] 6 commits: Fix EmptyCase panic in tcMatches (#25960)
by Zubin (@wz1000) 31 Oct '25
by Zubin (@wz1000) 31 Oct '25
31 Oct '25
Zubin pushed to branch wip/9.12.3-backports at Glasgow Haskell Compiler / GHC
Commits:
a8ce2f00 by Vladislav Zavialov at 2025-10-22T12:39:41+05:30
Fix EmptyCase panic in tcMatches (#25960)
Due to faulty reasoning in Note [Pattern types for EmptyCase],
tcMatches was too keen to panic.
* Old (incorrect) assumption: pat_tys is a singleton list.
This does not hold when \case{} is checked against a function type
preceded by invisible forall. See the new T25960 test case.
* New (hopefully correct) assumption: vis_pat_tys is a singleton list.
This should follow from:
checkArgCounts :: MatchGroup GhcRn ... -> TcM VisArity
checkArgCounts (MG { mg_alts = L _ [] })
= return 1
...
(cherry picked from commit b34890c7d4803041caff060391eec298e2b0a098)
- - - - -
72e32447 by Ben Gamari at 2025-10-22T12:42:06+05:30
StgToByteCode: Don't assume that data con workers are nullary
Previously StgToByteCode assumed that all data-con workers were of a
nullary representation. This is not a valid assumption, as seen
in #23210, where an unsaturated application of a unary data
constructor's worker resulted in invalid bytecode. Sadly, I have not yet
been able to reduce a minimal testcase for this.
Fixes #23210.
(cherry picked from commit d1d9e39ec293cd1d2b539b8246a349b539c6a61a)
- - - - -
dc9e7c4e by Ben Gamari at 2025-10-22T12:42:20+05:30
testsuite: Mark T23146* as unbroken
(cherry picked from commit 3eeecd508ef80812bc8ee84ab83f496f5030d59b)
- - - - -
08179480 by sheaf at 2025-10-22T12:42:31+05:30
Add test for #26216
(cherry picked from commit 2e73f3426ab6e3cf1938b53831005593f3fd351c)
- - - - -
38d49c64 by Brandon Chinn at 2025-10-22T12:43:24+05:30
Fix tabs in string gaps (#26415)
Tabs in string gaps were broken in bb030d0d because previously, string gaps were manually parsed, but now it's lexed by the usual Alex grammar and post-processed after successful lexing.
It broke because of a discrepancy between GHC's lexer grammar and the Haskell Report. The Haskell Report includes tabs in whitechar:
whitechar → newline | vertab | space | tab | uniWhite
$whitechar used to include tabs until 18 years ago, when it was removed in order to exclude tabs from $white_no_nl in order to warn on tabs: 6e202120. In this MR, I'm adding \t back into $whitechar, and explicitly excluding \t from the $white_no_nl+ rule ignoring all whitespace in source code, which more accurately colocates the "ignore all whitespace except tabs, which is handled in the next line" logic.
As a side effect of this MR, tabs are now allowed in pragmas; currently, a pragma written as {-# \t LANGUAGE ... #-} is interpreted as the tab character being the pragma name, and GHC warns "Unrecognized pragma". With this change, tabs are ignored as whitespace, which more closely matches the Report anyway.
(cherry picked from commit e9c5e46ffdb3cd8725e2ffdc2c440ea57af97bac)
- - - - -
10a82889 by Ben Gamari at 2025-10-23T17:35:29+05:30
rts: Dynamically initialize built-in closures
To resolve #26166 we need to eliminate references to undefined symbols
in the runtime system. One such source of these is the runtime's
static references to `I#` and `C#` due the `stg_INTLIKE` and
`stg_CHARLIKE` arrays.
To avoid this we make these dynamic, initializing them during RTS
start-up.
(cherry picked from commit 39eaaaba5356e3fc9218d8e27375d6de24778cbc)
- - - - -
26 changed files:
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/Lexer/String.x
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/Tc/Gen/Match.hs
- + rts/BuiltinClosures.c
- + rts/BuiltinClosures.h
- rts/Interpreter.c
- rts/RtsStartup.c
- rts/StgMiscClosures.cmm
- rts/include/rts/Constants.h
- rts/include/stg/MiscClosures.h
- rts/rts.cabal
- + testsuite/tests/bytecode/T26216.hs
- + testsuite/tests/bytecode/T26216.script
- + testsuite/tests/bytecode/T26216.stdout
- + testsuite/tests/bytecode/T26216_aux.hs
- testsuite/tests/bytecode/all.T
- testsuite/tests/codeGen/should_run/T23146/all.T
- + testsuite/tests/parser/should_run/T26415.hs
- + testsuite/tests/parser/should_run/T26415.stdout
- testsuite/tests/parser/should_run/all.T
- + testsuite/tests/typecheck/should_compile/T25960.hs
- testsuite/tests/typecheck/should_compile/all.T
- + testsuite/tests/typecheck/should_fail/T25004k.hs
- + testsuite/tests/typecheck/should_fail/T25004k.stderr
- testsuite/tests/typecheck/should_fail/all.T
Changes:
=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -145,7 +145,7 @@ import GHC.Parser.String
$unispace = \x05 -- Trick Alex into handling Unicode. See Note [Unicode in Alex].
$nl = [\n\r\f]
$space = [\ $unispace]
-$whitechar = [$nl \v $space]
+$whitechar = [$nl \t \v $space]
$white_no_nl = $whitechar # \n -- TODO #8424
$tab = \t
@@ -248,7 +248,7 @@ haskell :-
-- Alex "Rules"
-- everywhere: skip whitespace
-$white_no_nl+ ;
+($white_no_nl # \t)+ ;
$tab { warnTab }
-- Everywhere: deal with nested comments. We explicitly rule out
=====================================
compiler/GHC/Parser/Lexer/String.x
=====================================
@@ -25,7 +25,7 @@ import GHC.Utils.Panic (panic)
$unispace = \x05 -- Trick Alex into handling Unicode. See Note [Unicode in Alex].
$nl = [\n\r\f]
$space = [\ $unispace]
-$whitechar = [$nl \v $space]
+$whitechar = [$nl \t \v $space]
$tab = \t
$ascdigit = 0-9
=====================================
compiler/GHC/StgToByteCode.hs
=====================================
@@ -1930,11 +1930,12 @@ pushAtom d p (StgVarArg var)
-- PUSH_G doesn't tag constructors. So we use PACK here
-- if we are dealing with nullary constructor.
case isDataConWorkId_maybe var of
- Just con -> do
- massert (isNullaryRepDataCon con)
- return (unitOL (PACK con 0), szb)
+ Just con
+ -- See Note [LFInfo of DataCon workers and wrappers] in GHC.Types.Id.Make.
+ | isNullaryRepDataCon con ->
+ return (unitOL (PACK con 0), szb)
- Nothing
+ _
-- see Note [Generating code for top-level string literal bindings]
| isUnliftedType (idType var) -> do
massert (idType var `eqType` addrPrimTy)
=====================================
compiler/GHC/Tc/Gen/Match.hs
=====================================
@@ -240,7 +240,9 @@ tcMatches ctxt tc_body pat_tys rhs_ty (MG { mg_alts = L l matches
-- when in inference mode, so we must do it ourselves,
-- here, using expTypeToType
= do { tcEmitBindingUsage bottomUE
- ; pat_ty <- case pat_tys of -- See Note [Pattern types for EmptyCase]
+ -- See Note [Pattern types for EmptyCase]
+ ; let vis_pat_tys = filter isVisibleExpPatType pat_tys
+ ; pat_ty <- case vis_pat_tys of
[ExpFunPatTy t] -> scaledExpTypeToType t
[ExpForAllPatTy tvb] -> failWithTc $ TcRnEmptyCase ctxt (EmptyCaseForall tvb)
[] -> panic "tcMatches: no arguments in EmptyCase"
@@ -275,8 +277,15 @@ tcMatches ctxt tc_body pat_tys rhs_ty (MG { mg_alts = L l matches
In tcMatches, we might encounter an empty list of matches if the user wrote
`case x of {}` or `\case {}`.
-* First of all, both `case x of {}` and `\case {}` match on exactly one
- argument, so we expect pat_tys to be a singleton list [pat_ty] and panic otherwise.
+* First of all, both `case x of {}` and `\case {}` match on exactly one visible
+ argument, which follows from
+
+ checkArgCounts :: MatchGroup GhcRn ... -> TcM VisArity
+ checkArgCounts (MG { mg_alts = L _ [] })
+ = return 1
+ ...
+
+ So we expect vis_pat_tys to be a singleton list [pat_ty] and panic otherwise.
Multi-case `\cases {}` can't violate this assumption in `tcMatches` because it
must have been rejected earlier in `rnMatchGroup`.
@@ -293,7 +302,7 @@ In tcMatches, we might encounter an empty list of matches if the user wrote
This is not valid and it used to trigger a panic in pmcMatches (#25004).
We reject it by inspecting the expected pattern type:
- ; pat_ty <- case pat_tys of
+ ; pat_ty <- case vis_pat_tys of
[ExpFunPatTy t] -> ... -- value argument, ok
[ExpForAllPatTy tvb] -> ... -- type argument, error!
=====================================
rts/BuiltinClosures.c
=====================================
@@ -0,0 +1,30 @@
+#include "Rts.h"
+#include "Prelude.h"
+#include "BuiltinClosures.h"
+
+/*
+ * Note [CHARLIKE and INTLIKE closures]
+ * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+ * These are static representations of Chars and small Ints, so that
+ * we can remove dynamic Chars and Ints during garbage collection and
+ * replace them with references to the static objects.
+ */
+
+StgIntCharlikeClosure stg_INTLIKE_closure[MAX_INTLIKE - MIN_INTLIKE + 1];
+StgIntCharlikeClosure stg_CHARLIKE_closure[MAX_CHARLIKE - MIN_CHARLIKE + 1];
+
+void initBuiltinClosures(void) {
+ // INTLIKE closures
+ for (int i = MIN_INTLIKE; i <= MAX_INTLIKE; i++) {
+ StgIntCharlikeClosure *c = &stg_INTLIKE_closure[i - MIN_INTLIKE];
+ SET_HDR((StgClosure* ) c, Izh_con_info, CCS_SYSTEM_OR_NULL);
+ c->data = i;
+ }
+
+ // CHARLIKE closures
+ for (int i = MIN_CHARLIKE; i <= MAX_CHARLIKE; i++) {
+ StgIntCharlikeClosure *c = &stg_CHARLIKE_closure[i - MIN_CHARLIKE];
+ SET_HDR((StgClosure* ) c, Czh_con_info, CCS_SYSTEM_OR_NULL);
+ c->data = i;
+ }
+}
=====================================
rts/BuiltinClosures.h
=====================================
@@ -0,0 +1,14 @@
+/*
+ * (c) The GHC Team, 2025-2026
+ *
+ * RTS/ghc-internal interface
+ *
+ */
+
+#pragma once
+
+#include "BeginPrivate.h"
+
+void initBuiltinClosures(void);
+
+#include "EndPrivate.h"
=====================================
rts/Interpreter.c
=====================================
@@ -1874,7 +1874,6 @@ run_BCO:
// n_nptrs=1, n_ptrs=0.
ASSERT(n_ptrs + n_nptrs == n_words || (n_nptrs == 1 && n_ptrs == 0));
ASSERT(n_ptrs + n_nptrs > 0);
- //ASSERT(n_words > 0); // We shouldn't ever need to allocate nullary constructors
for (W_ i = 0; i < n_words; i++) {
con->payload[i] = (StgClosure*)ReadSpW(i);
}
=====================================
rts/RtsStartup.c
=====================================
@@ -14,6 +14,7 @@
#include "linker/MMap.h"
#include "RtsFlags.h"
#include "RtsUtils.h"
+#include "BuiltinClosures.h"
#include "Prelude.h"
#include "Printer.h" /* DEBUG_LoadSymbols */
#include "Schedule.h" /* initScheduler */
@@ -378,6 +379,9 @@ hs_init_ghc(int *argc, char **argv[], RtsConfig rts_config)
traceInitEvent(traceOSProcessInfo);
flushTrace();
+ /* initialize INTLIKE and CHARLIKE closures */
+ initBuiltinClosures();
+
/* initialize the storage manager */
initStorage();
=====================================
rts/StgMiscClosures.cmm
=====================================
@@ -13,8 +13,6 @@
#include "Cmm.h"
import pthread_mutex_lock;
-import ghczmprim_GHCziTypes_Czh_info;
-import ghczmprim_GHCziTypes_Izh_info;
import AcquireSRWLockExclusive;
import ReleaseSRWLockExclusive;
@@ -968,571 +966,6 @@ INFO_TABLE( stg_COMPACT_NFDATA_DIRTY, 0, 9, COMPACT_NFDATA, "COMPACT_NFDATA", "C
()
{ foreign "C" barf("COMPACT_NFDATA_DIRTY object (%p) entered!", R1) never returns; }
-/* ----------------------------------------------------------------------------
- Note [CHARLIKE and INTLIKE closures]
- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
- These are static representations of Chars and small Ints, so that
- we can remove dynamic Chars and Ints during garbage collection and
- replace them with references to the static objects.
------------------------------------------------------------------------- */
-#if defined(COMPILING_WINDOWS_DLL)
-/*
- * When sticking the RTS in a Windows DLL, we delay populating the
- * Charlike and Intlike tables until load-time, which is only
- * when we've got the real addresses to the C# and I# closures.
- *
- * -- this is currently broken BL 2009/11/14.
- * we don't rewrite to static closures at all with Windows DLLs.
- */
-// #warning Is this correct? _imp is a pointer!
-#define Char_hash_con_info _imp__ghczmprim_GHCziTypes_Czh_con_info
-#define Int_hash_con_info _imp__ghczmprim_GHCziTypes_Izh_con_info
-#else
-#define Char_hash_con_info ghczmprim_GHCziTypes_Czh_con_info
-#define Int_hash_con_info ghczmprim_GHCziTypes_Izh_con_info
-#endif
-
-
-#define CHARLIKE_HDR(n) CLOSURE(Char_hash_con_info, n)
-#define INTLIKE_HDR(n) CLOSURE(Int_hash_con_info, n)
-
-#if !(defined(COMPILING_WINDOWS_DLL))
-section "data" {
- stg_CHARLIKE_closure:
- CHARLIKE_HDR(0)
- CHARLIKE_HDR(1)
- CHARLIKE_HDR(2)
- CHARLIKE_HDR(3)
- CHARLIKE_HDR(4)
- CHARLIKE_HDR(5)
- CHARLIKE_HDR(6)
- CHARLIKE_HDR(7)
- CHARLIKE_HDR(8)
- CHARLIKE_HDR(9)
- CHARLIKE_HDR(10)
- CHARLIKE_HDR(11)
- CHARLIKE_HDR(12)
- CHARLIKE_HDR(13)
- CHARLIKE_HDR(14)
- CHARLIKE_HDR(15)
- CHARLIKE_HDR(16)
- CHARLIKE_HDR(17)
- CHARLIKE_HDR(18)
- CHARLIKE_HDR(19)
- CHARLIKE_HDR(20)
- CHARLIKE_HDR(21)
- CHARLIKE_HDR(22)
- CHARLIKE_HDR(23)
- CHARLIKE_HDR(24)
- CHARLIKE_HDR(25)
- CHARLIKE_HDR(26)
- CHARLIKE_HDR(27)
- CHARLIKE_HDR(28)
- CHARLIKE_HDR(29)
- CHARLIKE_HDR(30)
- CHARLIKE_HDR(31)
- CHARLIKE_HDR(32)
- CHARLIKE_HDR(33)
- CHARLIKE_HDR(34)
- CHARLIKE_HDR(35)
- CHARLIKE_HDR(36)
- CHARLIKE_HDR(37)
- CHARLIKE_HDR(38)
- CHARLIKE_HDR(39)
- CHARLIKE_HDR(40)
- CHARLIKE_HDR(41)
- CHARLIKE_HDR(42)
- CHARLIKE_HDR(43)
- CHARLIKE_HDR(44)
- CHARLIKE_HDR(45)
- CHARLIKE_HDR(46)
- CHARLIKE_HDR(47)
- CHARLIKE_HDR(48)
- CHARLIKE_HDR(49)
- CHARLIKE_HDR(50)
- CHARLIKE_HDR(51)
- CHARLIKE_HDR(52)
- CHARLIKE_HDR(53)
- CHARLIKE_HDR(54)
- CHARLIKE_HDR(55)
- CHARLIKE_HDR(56)
- CHARLIKE_HDR(57)
- CHARLIKE_HDR(58)
- CHARLIKE_HDR(59)
- CHARLIKE_HDR(60)
- CHARLIKE_HDR(61)
- CHARLIKE_HDR(62)
- CHARLIKE_HDR(63)
- CHARLIKE_HDR(64)
- CHARLIKE_HDR(65)
- CHARLIKE_HDR(66)
- CHARLIKE_HDR(67)
- CHARLIKE_HDR(68)
- CHARLIKE_HDR(69)
- CHARLIKE_HDR(70)
- CHARLIKE_HDR(71)
- CHARLIKE_HDR(72)
- CHARLIKE_HDR(73)
- CHARLIKE_HDR(74)
- CHARLIKE_HDR(75)
- CHARLIKE_HDR(76)
- CHARLIKE_HDR(77)
- CHARLIKE_HDR(78)
- CHARLIKE_HDR(79)
- CHARLIKE_HDR(80)
- CHARLIKE_HDR(81)
- CHARLIKE_HDR(82)
- CHARLIKE_HDR(83)
- CHARLIKE_HDR(84)
- CHARLIKE_HDR(85)
- CHARLIKE_HDR(86)
- CHARLIKE_HDR(87)
- CHARLIKE_HDR(88)
- CHARLIKE_HDR(89)
- CHARLIKE_HDR(90)
- CHARLIKE_HDR(91)
- CHARLIKE_HDR(92)
- CHARLIKE_HDR(93)
- CHARLIKE_HDR(94)
- CHARLIKE_HDR(95)
- CHARLIKE_HDR(96)
- CHARLIKE_HDR(97)
- CHARLIKE_HDR(98)
- CHARLIKE_HDR(99)
- CHARLIKE_HDR(100)
- CHARLIKE_HDR(101)
- CHARLIKE_HDR(102)
- CHARLIKE_HDR(103)
- CHARLIKE_HDR(104)
- CHARLIKE_HDR(105)
- CHARLIKE_HDR(106)
- CHARLIKE_HDR(107)
- CHARLIKE_HDR(108)
- CHARLIKE_HDR(109)
- CHARLIKE_HDR(110)
- CHARLIKE_HDR(111)
- CHARLIKE_HDR(112)
- CHARLIKE_HDR(113)
- CHARLIKE_HDR(114)
- CHARLIKE_HDR(115)
- CHARLIKE_HDR(116)
- CHARLIKE_HDR(117)
- CHARLIKE_HDR(118)
- CHARLIKE_HDR(119)
- CHARLIKE_HDR(120)
- CHARLIKE_HDR(121)
- CHARLIKE_HDR(122)
- CHARLIKE_HDR(123)
- CHARLIKE_HDR(124)
- CHARLIKE_HDR(125)
- CHARLIKE_HDR(126)
- CHARLIKE_HDR(127)
- CHARLIKE_HDR(128)
- CHARLIKE_HDR(129)
- CHARLIKE_HDR(130)
- CHARLIKE_HDR(131)
- CHARLIKE_HDR(132)
- CHARLIKE_HDR(133)
- CHARLIKE_HDR(134)
- CHARLIKE_HDR(135)
- CHARLIKE_HDR(136)
- CHARLIKE_HDR(137)
- CHARLIKE_HDR(138)
- CHARLIKE_HDR(139)
- CHARLIKE_HDR(140)
- CHARLIKE_HDR(141)
- CHARLIKE_HDR(142)
- CHARLIKE_HDR(143)
- CHARLIKE_HDR(144)
- CHARLIKE_HDR(145)
- CHARLIKE_HDR(146)
- CHARLIKE_HDR(147)
- CHARLIKE_HDR(148)
- CHARLIKE_HDR(149)
- CHARLIKE_HDR(150)
- CHARLIKE_HDR(151)
- CHARLIKE_HDR(152)
- CHARLIKE_HDR(153)
- CHARLIKE_HDR(154)
- CHARLIKE_HDR(155)
- CHARLIKE_HDR(156)
- CHARLIKE_HDR(157)
- CHARLIKE_HDR(158)
- CHARLIKE_HDR(159)
- CHARLIKE_HDR(160)
- CHARLIKE_HDR(161)
- CHARLIKE_HDR(162)
- CHARLIKE_HDR(163)
- CHARLIKE_HDR(164)
- CHARLIKE_HDR(165)
- CHARLIKE_HDR(166)
- CHARLIKE_HDR(167)
- CHARLIKE_HDR(168)
- CHARLIKE_HDR(169)
- CHARLIKE_HDR(170)
- CHARLIKE_HDR(171)
- CHARLIKE_HDR(172)
- CHARLIKE_HDR(173)
- CHARLIKE_HDR(174)
- CHARLIKE_HDR(175)
- CHARLIKE_HDR(176)
- CHARLIKE_HDR(177)
- CHARLIKE_HDR(178)
- CHARLIKE_HDR(179)
- CHARLIKE_HDR(180)
- CHARLIKE_HDR(181)
- CHARLIKE_HDR(182)
- CHARLIKE_HDR(183)
- CHARLIKE_HDR(184)
- CHARLIKE_HDR(185)
- CHARLIKE_HDR(186)
- CHARLIKE_HDR(187)
- CHARLIKE_HDR(188)
- CHARLIKE_HDR(189)
- CHARLIKE_HDR(190)
- CHARLIKE_HDR(191)
- CHARLIKE_HDR(192)
- CHARLIKE_HDR(193)
- CHARLIKE_HDR(194)
- CHARLIKE_HDR(195)
- CHARLIKE_HDR(196)
- CHARLIKE_HDR(197)
- CHARLIKE_HDR(198)
- CHARLIKE_HDR(199)
- CHARLIKE_HDR(200)
- CHARLIKE_HDR(201)
- CHARLIKE_HDR(202)
- CHARLIKE_HDR(203)
- CHARLIKE_HDR(204)
- CHARLIKE_HDR(205)
- CHARLIKE_HDR(206)
- CHARLIKE_HDR(207)
- CHARLIKE_HDR(208)
- CHARLIKE_HDR(209)
- CHARLIKE_HDR(210)
- CHARLIKE_HDR(211)
- CHARLIKE_HDR(212)
- CHARLIKE_HDR(213)
- CHARLIKE_HDR(214)
- CHARLIKE_HDR(215)
- CHARLIKE_HDR(216)
- CHARLIKE_HDR(217)
- CHARLIKE_HDR(218)
- CHARLIKE_HDR(219)
- CHARLIKE_HDR(220)
- CHARLIKE_HDR(221)
- CHARLIKE_HDR(222)
- CHARLIKE_HDR(223)
- CHARLIKE_HDR(224)
- CHARLIKE_HDR(225)
- CHARLIKE_HDR(226)
- CHARLIKE_HDR(227)
- CHARLIKE_HDR(228)
- CHARLIKE_HDR(229)
- CHARLIKE_HDR(230)
- CHARLIKE_HDR(231)
- CHARLIKE_HDR(232)
- CHARLIKE_HDR(233)
- CHARLIKE_HDR(234)
- CHARLIKE_HDR(235)
- CHARLIKE_HDR(236)
- CHARLIKE_HDR(237)
- CHARLIKE_HDR(238)
- CHARLIKE_HDR(239)
- CHARLIKE_HDR(240)
- CHARLIKE_HDR(241)
- CHARLIKE_HDR(242)
- CHARLIKE_HDR(243)
- CHARLIKE_HDR(244)
- CHARLIKE_HDR(245)
- CHARLIKE_HDR(246)
- CHARLIKE_HDR(247)
- CHARLIKE_HDR(248)
- CHARLIKE_HDR(249)
- CHARLIKE_HDR(250)
- CHARLIKE_HDR(251)
- CHARLIKE_HDR(252)
- CHARLIKE_HDR(253)
- CHARLIKE_HDR(254)
- CHARLIKE_HDR(255)
-}
-
-section "data" {
- stg_INTLIKE_closure:
- INTLIKE_HDR(-16) /* MIN_INTLIKE == -16 */
- INTLIKE_HDR(-15)
- INTLIKE_HDR(-14)
- INTLIKE_HDR(-13)
- INTLIKE_HDR(-12)
- INTLIKE_HDR(-11)
- INTLIKE_HDR(-10)
- INTLIKE_HDR(-9)
- INTLIKE_HDR(-8)
- INTLIKE_HDR(-7)
- INTLIKE_HDR(-6)
- INTLIKE_HDR(-5)
- INTLIKE_HDR(-4)
- INTLIKE_HDR(-3)
- INTLIKE_HDR(-2)
- INTLIKE_HDR(-1)
- INTLIKE_HDR(0)
- INTLIKE_HDR(1)
- INTLIKE_HDR(2)
- INTLIKE_HDR(3)
- INTLIKE_HDR(4)
- INTLIKE_HDR(5)
- INTLIKE_HDR(6)
- INTLIKE_HDR(7)
- INTLIKE_HDR(8)
- INTLIKE_HDR(9)
- INTLIKE_HDR(10)
- INTLIKE_HDR(11)
- INTLIKE_HDR(12)
- INTLIKE_HDR(13)
- INTLIKE_HDR(14)
- INTLIKE_HDR(15)
- INTLIKE_HDR(16)
- INTLIKE_HDR(17)
- INTLIKE_HDR(18)
- INTLIKE_HDR(19)
- INTLIKE_HDR(20)
- INTLIKE_HDR(21)
- INTLIKE_HDR(22)
- INTLIKE_HDR(23)
- INTLIKE_HDR(24)
- INTLIKE_HDR(25)
- INTLIKE_HDR(26)
- INTLIKE_HDR(27)
- INTLIKE_HDR(28)
- INTLIKE_HDR(29)
- INTLIKE_HDR(30)
- INTLIKE_HDR(31)
- INTLIKE_HDR(32)
- INTLIKE_HDR(33)
- INTLIKE_HDR(34)
- INTLIKE_HDR(35)
- INTLIKE_HDR(36)
- INTLIKE_HDR(37)
- INTLIKE_HDR(38)
- INTLIKE_HDR(39)
- INTLIKE_HDR(40)
- INTLIKE_HDR(41)
- INTLIKE_HDR(42)
- INTLIKE_HDR(43)
- INTLIKE_HDR(44)
- INTLIKE_HDR(45)
- INTLIKE_HDR(46)
- INTLIKE_HDR(47)
- INTLIKE_HDR(48)
- INTLIKE_HDR(49)
- INTLIKE_HDR(50)
- INTLIKE_HDR(51)
- INTLIKE_HDR(52)
- INTLIKE_HDR(53)
- INTLIKE_HDR(54)
- INTLIKE_HDR(55)
- INTLIKE_HDR(56)
- INTLIKE_HDR(57)
- INTLIKE_HDR(58)
- INTLIKE_HDR(59)
- INTLIKE_HDR(60)
- INTLIKE_HDR(61)
- INTLIKE_HDR(62)
- INTLIKE_HDR(63)
- INTLIKE_HDR(64)
- INTLIKE_HDR(65)
- INTLIKE_HDR(66)
- INTLIKE_HDR(67)
- INTLIKE_HDR(68)
- INTLIKE_HDR(69)
- INTLIKE_HDR(70)
- INTLIKE_HDR(71)
- INTLIKE_HDR(72)
- INTLIKE_HDR(73)
- INTLIKE_HDR(74)
- INTLIKE_HDR(75)
- INTLIKE_HDR(76)
- INTLIKE_HDR(77)
- INTLIKE_HDR(78)
- INTLIKE_HDR(79)
- INTLIKE_HDR(80)
- INTLIKE_HDR(81)
- INTLIKE_HDR(82)
- INTLIKE_HDR(83)
- INTLIKE_HDR(84)
- INTLIKE_HDR(85)
- INTLIKE_HDR(86)
- INTLIKE_HDR(87)
- INTLIKE_HDR(88)
- INTLIKE_HDR(89)
- INTLIKE_HDR(90)
- INTLIKE_HDR(91)
- INTLIKE_HDR(92)
- INTLIKE_HDR(93)
- INTLIKE_HDR(94)
- INTLIKE_HDR(95)
- INTLIKE_HDR(96)
- INTLIKE_HDR(97)
- INTLIKE_HDR(98)
- INTLIKE_HDR(99)
- INTLIKE_HDR(100)
- INTLIKE_HDR(101)
- INTLIKE_HDR(102)
- INTLIKE_HDR(103)
- INTLIKE_HDR(104)
- INTLIKE_HDR(105)
- INTLIKE_HDR(106)
- INTLIKE_HDR(107)
- INTLIKE_HDR(108)
- INTLIKE_HDR(109)
- INTLIKE_HDR(110)
- INTLIKE_HDR(111)
- INTLIKE_HDR(112)
- INTLIKE_HDR(113)
- INTLIKE_HDR(114)
- INTLIKE_HDR(115)
- INTLIKE_HDR(116)
- INTLIKE_HDR(117)
- INTLIKE_HDR(118)
- INTLIKE_HDR(119)
- INTLIKE_HDR(120)
- INTLIKE_HDR(121)
- INTLIKE_HDR(122)
- INTLIKE_HDR(123)
- INTLIKE_HDR(124)
- INTLIKE_HDR(125)
- INTLIKE_HDR(126)
- INTLIKE_HDR(127)
- INTLIKE_HDR(128)
- INTLIKE_HDR(129)
- INTLIKE_HDR(130)
- INTLIKE_HDR(131)
- INTLIKE_HDR(132)
- INTLIKE_HDR(133)
- INTLIKE_HDR(134)
- INTLIKE_HDR(135)
- INTLIKE_HDR(136)
- INTLIKE_HDR(137)
- INTLIKE_HDR(138)
- INTLIKE_HDR(139)
- INTLIKE_HDR(140)
- INTLIKE_HDR(141)
- INTLIKE_HDR(142)
- INTLIKE_HDR(143)
- INTLIKE_HDR(144)
- INTLIKE_HDR(145)
- INTLIKE_HDR(146)
- INTLIKE_HDR(147)
- INTLIKE_HDR(148)
- INTLIKE_HDR(149)
- INTLIKE_HDR(150)
- INTLIKE_HDR(151)
- INTLIKE_HDR(152)
- INTLIKE_HDR(153)
- INTLIKE_HDR(154)
- INTLIKE_HDR(155)
- INTLIKE_HDR(156)
- INTLIKE_HDR(157)
- INTLIKE_HDR(158)
- INTLIKE_HDR(159)
- INTLIKE_HDR(160)
- INTLIKE_HDR(161)
- INTLIKE_HDR(162)
- INTLIKE_HDR(163)
- INTLIKE_HDR(164)
- INTLIKE_HDR(165)
- INTLIKE_HDR(166)
- INTLIKE_HDR(167)
- INTLIKE_HDR(168)
- INTLIKE_HDR(169)
- INTLIKE_HDR(170)
- INTLIKE_HDR(171)
- INTLIKE_HDR(172)
- INTLIKE_HDR(173)
- INTLIKE_HDR(174)
- INTLIKE_HDR(175)
- INTLIKE_HDR(176)
- INTLIKE_HDR(177)
- INTLIKE_HDR(178)
- INTLIKE_HDR(179)
- INTLIKE_HDR(180)
- INTLIKE_HDR(181)
- INTLIKE_HDR(182)
- INTLIKE_HDR(183)
- INTLIKE_HDR(184)
- INTLIKE_HDR(185)
- INTLIKE_HDR(186)
- INTLIKE_HDR(187)
- INTLIKE_HDR(188)
- INTLIKE_HDR(189)
- INTLIKE_HDR(190)
- INTLIKE_HDR(191)
- INTLIKE_HDR(192)
- INTLIKE_HDR(193)
- INTLIKE_HDR(194)
- INTLIKE_HDR(195)
- INTLIKE_HDR(196)
- INTLIKE_HDR(197)
- INTLIKE_HDR(198)
- INTLIKE_HDR(199)
- INTLIKE_HDR(200)
- INTLIKE_HDR(201)
- INTLIKE_HDR(202)
- INTLIKE_HDR(203)
- INTLIKE_HDR(204)
- INTLIKE_HDR(205)
- INTLIKE_HDR(206)
- INTLIKE_HDR(207)
- INTLIKE_HDR(208)
- INTLIKE_HDR(209)
- INTLIKE_HDR(210)
- INTLIKE_HDR(211)
- INTLIKE_HDR(212)
- INTLIKE_HDR(213)
- INTLIKE_HDR(214)
- INTLIKE_HDR(215)
- INTLIKE_HDR(216)
- INTLIKE_HDR(217)
- INTLIKE_HDR(218)
- INTLIKE_HDR(219)
- INTLIKE_HDR(220)
- INTLIKE_HDR(221)
- INTLIKE_HDR(222)
- INTLIKE_HDR(223)
- INTLIKE_HDR(224)
- INTLIKE_HDR(225)
- INTLIKE_HDR(226)
- INTLIKE_HDR(227)
- INTLIKE_HDR(228)
- INTLIKE_HDR(229)
- INTLIKE_HDR(230)
- INTLIKE_HDR(231)
- INTLIKE_HDR(232)
- INTLIKE_HDR(233)
- INTLIKE_HDR(234)
- INTLIKE_HDR(235)
- INTLIKE_HDR(236)
- INTLIKE_HDR(237)
- INTLIKE_HDR(238)
- INTLIKE_HDR(239)
- INTLIKE_HDR(240)
- INTLIKE_HDR(241)
- INTLIKE_HDR(242)
- INTLIKE_HDR(243)
- INTLIKE_HDR(244)
- INTLIKE_HDR(245)
- INTLIKE_HDR(246)
- INTLIKE_HDR(247)
- INTLIKE_HDR(248)
- INTLIKE_HDR(249)
- INTLIKE_HDR(250)
- INTLIKE_HDR(251)
- INTLIKE_HDR(252)
- INTLIKE_HDR(253)
- INTLIKE_HDR(254)
- INTLIKE_HDR(255) /* MAX_INTLIKE == 255
- See #16961 for why 255 */
-}
-
-#endif
+CLOSURE(stg_TIMEOUT_QUEUE_EMPTY_closure,stg_TIMEOUT_QUEUE_EMPTY);
=====================================
rts/include/rts/Constants.h
=====================================
@@ -57,11 +57,12 @@
#define MAX_SPEC_CONSTR_SIZE 2
/* Range of built-in table of static small int-like and char-like closures.
+ * Range is inclusive of both minimum and maximum.
*
* NB. This corresponds with the number of actual INTLIKE/CHARLIKE
* closures defined in rts/StgMiscClosures.cmm.
*/
-#define MAX_INTLIKE 255
+#define MAX_INTLIKE 255 /* See #16961 for why 255 */
#define MIN_INTLIKE (-16)
#define MAX_CHARLIKE 255
=====================================
rts/include/stg/MiscClosures.h
=====================================
@@ -268,8 +268,8 @@ RTS_ENTRY(stg_NO_FINALIZER);
extern DLL_IMPORT_RTS StgWordArray stg_CHARLIKE_closure;
extern DLL_IMPORT_RTS StgWordArray stg_INTLIKE_closure;
#else
-extern DLL_IMPORT_RTS StgIntCharlikeClosure stg_CHARLIKE_closure[];
-extern DLL_IMPORT_RTS StgIntCharlikeClosure stg_INTLIKE_closure[];
+extern DLL_IMPORT_RTS StgIntCharlikeClosure stg_CHARLIKE_closure[MAX_CHARLIKE - MIN_CHARLIKE + 1];
+extern DLL_IMPORT_RTS StgIntCharlikeClosure stg_INTLIKE_closure[MAX_INTLIKE - MIN_INTLIKE + 1];
#endif
/* StgStartup */
=====================================
rts/rts.cabal
=====================================
@@ -381,6 +381,7 @@ library
adjustor/AdjustorPool.c
ExecPage.c
Arena.c
+ BuiltinClosures.c
Capability.c
CheckUnload.c
CheckVectorSupport.c
=====================================
testsuite/tests/bytecode/T26216.hs
=====================================
@@ -0,0 +1,28 @@
+{-# LANGUAGE GHC2024, BlockArguments, MagicHash #-}
+
+module T26216 (main) where
+
+import Data.Kind (Type, Constraint)
+import GHC.TypeNats
+import GHC.Exts (proxy#)
+
+import T26216_aux
+
+getN :: forall (n :: Nat). SNat n -> Natural
+getN s = withKnownNat s (natVal s)
+
+type C :: forall {k}. (k -> Constraint) -> k -> Type
+data C c a where { C :: c a => C c a }
+
+know :: forall (n :: Nat). SNat n -> C KnownNat n
+know s = withKnownNat s C
+
+getC :: forall (n :: Nat). C KnownNat n -> Natural
+getC C = natVal' (proxy# @n)
+
+main :: IO ()
+main = do
+ let !s = mkSome $ natSing @42
+ !c = withSome s $ mkSome . know
+ print $ withSome s getN
+ print $ withSome c getC
=====================================
testsuite/tests/bytecode/T26216.script
=====================================
@@ -0,0 +1,2 @@
+:l T26216
+main
=====================================
testsuite/tests/bytecode/T26216.stdout
=====================================
@@ -0,0 +1,2 @@
+42
+42
=====================================
testsuite/tests/bytecode/T26216_aux.hs
=====================================
@@ -0,0 +1,25 @@
+{-# LANGUAGE GHC2024 #-}
+{-# LANGUAGE PatternSynonyms #-}
+{-# LANGUAGE PolyKinds #-}
+
+module T26216_aux (Some, data Some, mkSome, withSome) where
+import Data.Kind (Type)
+import GHC.Exts (Any)
+import Unsafe.Coerce (unsafeCoerce)
+
+type Some :: (k -> Type) -> Type
+newtype Some tag = UnsafeSome (tag Any)
+type role Some representational
+
+{-# COMPLETE Some #-}
+pattern Some :: tag a -> Some tag
+pattern Some x <- UnsafeSome x
+ where Some x = UnsafeSome ((unsafeCoerce :: tag a -> tag Any) x)
+
+-- | Constructor.
+mkSome :: tag a -> Some tag
+mkSome = \x -> UnsafeSome (unsafeCoerce x)
+
+-- | Eliminator.
+withSome :: Some tag -> (forall a. tag a -> b) -> b
+withSome (UnsafeSome thing) some = some (unsafeCoerce thing)
=====================================
testsuite/tests/bytecode/all.T
=====================================
@@ -5,3 +5,7 @@ test('T23068', ghci_dump_bcos + [filter_stdout_lines(r'.*bitmap: .*')], ghci_scr
test('T25975', extra_ways(ghci_ways), compile_and_run,
# Some of the examples work more robustly with these flags
['-fno-break-points -fno-full-laziness'])
+
+# Nullary data constructors
+test('T26216', extra_files(["T26216_aux.hs"]), ghci_script, ['T26216.script'])
+
=====================================
testsuite/tests/codeGen/should_run/T23146/all.T
=====================================
@@ -1,4 +1,4 @@
test('T23146', expect_broken_for(23060, ghci_ways), compile_and_run, [''])
test('T23146_lifted', normal, compile_and_run, [''])
-test('T23146_liftedeq', expect_broken_for(23060, ghci_ways), compile_and_run, [''])
+test('T23146_liftedeq', normal, compile_and_run, [''])
test('T23146_lifted_unlifted', normal, compile_and_run, [''])
=====================================
testsuite/tests/parser/should_run/T26415.hs
=====================================
@@ -0,0 +1,7 @@
+{-# LANGUAGE MultilineStrings #-}
+
+main :: IO ()
+main = do
+ -- The below strings contain the characters ['\\', '\t', '\\']
+ print "\ \"
+ print """\ \"""
=====================================
testsuite/tests/parser/should_run/T26415.stdout
=====================================
@@ -0,0 +1,2 @@
+""
+""
=====================================
testsuite/tests/parser/should_run/all.T
=====================================
@@ -27,6 +27,7 @@ test('RecordDotSyntax4', [extra_files(['RecordDotSyntaxA.hs'])], multimod_compil
test('RecordDotSyntax5', normal, compile_and_run, [''])
test('ListTuplePunsConstraints', extra_files(['ListTuplePunsConstraints.hs']), ghci_script, ['ListTuplePunsConstraints.script'])
test('T25937', normal, compile_and_run, [''])
+test('T26415', normal, compile_and_run, [''])
# Multiline strings
test('MultilineStrings', normal, compile_and_run, [''])
=====================================
testsuite/tests/typecheck/should_compile/T25960.hs
=====================================
@@ -0,0 +1,12 @@
+{-# LANGUAGE LambdaCase #-}
+
+module T25960 where
+
+import Data.Void (Void)
+
+f :: (forall a. Void -> a) -> (forall a. Void -> a)
+f g = g
+
+absurd :: Void -> a
+absurd = f (\case)
+
=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -935,4 +935,4 @@ test('T24845a', normal, compile, [''])
test('T23501a', normal, compile, [''])
test('T23501b', normal, compile, [''])
test('T25597', normal, compile, [''])
-test('T26256a', normal, compile, [''])
+test('T25960', normal, compile, [''])
=====================================
testsuite/tests/typecheck/should_fail/T25004k.hs
=====================================
@@ -0,0 +1,9 @@
+{-# LANGUAGE RequiredTypeArguments, EmptyCase, LambdaCase #-}
+{-# OPTIONS -Wincomplete-patterns #-}
+
+module T25004k where
+
+import Data.Kind
+
+f :: ((forall k. forall (xs :: k) -> ()) -> r) -> r
+f cont = cont (\case {})
=====================================
testsuite/tests/typecheck/should_fail/T25004k.stderr
=====================================
@@ -0,0 +1,7 @@
+T25004k.hs:9:16: error: [GHC-48010]
+ • Empty list of alternatives in \case expression
+ checked against a forall-type: forall (xs :: k) -> ...
+ • In the first argument of ‘cont’, namely ‘(\case)’
+ In the expression: cont (\case)
+ In an equation for ‘f’: f cont = cont (\case)
+
=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -733,3 +733,4 @@ test('T24868', normal, compile_fail, [''])
test('T24938', normal, compile_fail, [''])
test('T25325', normal, compile_fail, [''])
test('T25004', normal, compile_fail, [''])
+test('T25004k', normal, compile_fail, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e0050c9dd7a1c00098cdff641a925d…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e0050c9dd7a1c00098cdff641a925d…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Ben Gamari pushed new branch wip/backports-9.14 at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/backports-9.14
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Ben Gamari pushed new branch wip/T26538 at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T26538
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Ben Gamari pushed new branch wip/T26539 at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T26539
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Ben Gamari pushed new tag ghc-9.14.1-rc1 at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/ghc-9.14.1-rc1
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/ani/kill-popErrCtxt] pass in the location of the head of the application chain to addArgCtxt to...
by Apoorv Ingle (@ani) 31 Oct '25
by Apoorv Ingle (@ani) 31 Oct '25
31 Oct '25
Apoorv Ingle pushed to branch wip/ani/kill-popErrCtxt at Glasgow Haskell Compiler / GHC
Commits:
eb9ac0c9 by Apoorv Ingle at 2025-10-30T13:27:46-05:00
pass in the location of the head of the application chain to addArgCtxt to print better error messages
- - - - -
3 changed files:
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Do.hs
- compiler/GHC/Tc/Gen/Head.hs
Changes:
=====================================
compiler/GHC/Tc/Gen/App.hs
=====================================
@@ -175,6 +175,9 @@ Note [Instantiation variables are short lived]
-- CAUTION: Any changes to tcApp should be reflected here
-- cf. T19167. the head is an expanded expression applied to a type
-- TODO: Use runInfer for tcExprSigma?
+-- Caution: Currently we assume that the expression is compiler generated/expanded
+-- Becuase that is that T19167 testcase generates. This function can possibly
+-- take in the rn_expr and its location to pass into tcValArgs
tcExprSigma :: Bool -> HsExpr GhcRn -> TcM (HsExpr GhcTc, TcSigmaType)
tcExprSigma inst rn_expr
= do { (fun@(rn_fun,fun_ctxt), rn_args) <- splitHsApps rn_expr
@@ -183,7 +186,7 @@ tcExprSigma inst rn_expr
; code_orig <- getSrcCodeOrigin
; let fun_orig = srcCodeOriginCtOrigin rn_expr code_orig
; (inst_args, app_res_sigma) <- tcInstFun do_ql inst fun_orig (tc_fun, rn_fun, fun_ctxt) fun_sigma rn_args
- ; tc_args <- tcValArgs do_ql rn_fun inst_args
+ ; tc_args <- tcValArgs do_ql (rn_fun, generatedSrcSpan) inst_args
; let tc_expr = rebuildHsApps (tc_fun, fun_ctxt) tc_args
; return (tc_expr, app_res_sigma) }
@@ -396,18 +399,18 @@ tcApp :: HsExpr GhcRn
-- See Note [tcApp: typechecking applications]
tcApp rn_expr exp_res_ty
= do { -- Step 1: Split the application chain
- (fun@(rn_fun, fun_loc), rn_args) <- splitHsApps rn_expr
+ (fun@(rn_fun, fun_lspan), rn_args) <- splitHsApps rn_expr
; inGenCode <- inGeneratedCode
; traceTc "tcApp {" $
vcat [ text "generated? " <+> ppr inGenCode
, text "rn_expr:" <+> ppr rn_expr
, text "rn_fun:" <+> ppr rn_fun
- , text "fun_loc:" <+> ppr fun_loc
+ , text "fun_lspan:" <+> ppr fun_lspan
, text "rn_args:" <+> ppr rn_args ]
-- Step 2: Infer the type of `fun`, the head of the application
; (tc_fun, fun_sigma) <- tcInferAppHead fun
- ; let tc_head = (tc_fun, fun_loc)
+ ; let tc_head = (tc_fun, fun_lspan)
-- inst_final: top-instantiate the result type of the application,
-- EXCEPT if we are trying to infer a sigma-type
inst_final = case exp_res_ty of
@@ -438,7 +441,7 @@ tcApp rn_expr exp_res_ty
, text "fun_origin" <+> ppr fun_orig
, text "do_ql:" <+> ppr do_ql]
; (inst_args, app_res_rho)
- <- tcInstFun do_ql inst_final fun_orig (tc_fun, rn_fun, fun_loc) fun_sigma rn_args
+ <- tcInstFun do_ql inst_final fun_orig (tc_fun, rn_fun, fun_lspan) fun_sigma rn_args
-- See (TCAPP1) and (TCAPP2) in
-- Note [tcApp: typechecking applications]
@@ -451,7 +454,7 @@ tcApp rn_expr exp_res_ty
app_res_rho exp_res_ty
-- Step 4.2: typecheck the arguments
- ; tc_args <- tcValArgs NoQL rn_fun inst_args
+ ; tc_args <- tcValArgs NoQL (rn_fun, fun_lspan) inst_args
-- Step 4.3: wrap up
; finishApp tc_head tc_args app_res_rho res_wrap }
@@ -462,7 +465,7 @@ tcApp rn_expr exp_res_ty
-- Step 5.2: typecheck the arguments, and monomorphise
-- any un-unified instantiation variables
- ; tc_args <- tcValArgs DoQL rn_fun inst_args
+ ; tc_args <- tcValArgs DoQL (rn_fun, fun_lspan) inst_args
-- Step 5.3: zonk to expose the polymorphism hidden under
-- QuickLook instantiation variables in `app_res_rho`
; app_res_rho <- liftZonkM $ zonkTcType app_res_rho
@@ -549,16 +552,16 @@ checkResultTy rn_expr (tc_fun, fun_loc) inst_args app_res_rho (Check res_ty)
thing_inside
----------------
-tcValArgs :: QLFlag -> HsExpr GhcRn -> [HsExprArg 'TcpInst] -> TcM [HsExprArg 'TcpTc]
+tcValArgs :: QLFlag -> (HsExpr GhcRn, SrcSpan) -> [HsExprArg 'TcpInst] -> TcM [HsExprArg 'TcpTc]
-- Importantly, tcValArgs works left-to-right, so that by the time we
-- encounter an argument, we have monomorphised all the instantiation
-- variables that its type contains. All that is left to do is an ordinary
-- zonkTcType. See Note [Monomorphise instantiation variables].
-tcValArgs do_ql fun args = go do_ql 0 args
+tcValArgs do_ql (fun, fun_lspan) args = go do_ql 0 args
where
go _ _ [] = return []
go do_ql pos (arg : args) =
- do { arg' <- tcValArg do_ql pos' fun arg
+ do { arg' <- tcValArg do_ql pos' (fun, fun_lspan) arg
; args' <- go do_ql pos' args
; return (arg' : args') }
where
@@ -574,7 +577,7 @@ tcValArgs do_ql fun args = go do_ql 0 args
= pos
-tcValArg :: QLFlag -> Int -> HsExpr GhcRn -> HsExprArg 'TcpInst -- Actual argument
+tcValArg :: QLFlag -> Int -> (HsExpr GhcRn, SrcSpan) -> HsExprArg 'TcpInst -- Actual argument
-> TcM (HsExprArg 'TcpTc) -- Resulting argument
tcValArg _ _ _ (EPrag l p) = return (EPrag l (tcExprPrag p))
tcValArg _ _ _ (ETypeArg l hty ty) = return (ETypeArg l hty ty)
@@ -583,10 +586,10 @@ tcValArg do_ql _ _ (EWrap (EHsWrap w)) = do { whenQL do_ql $ qlMonoHsWrapper w
-- qlMonoHsWrapper: see Note [Monomorphise instantiation variables]
tcValArg _ _ _ (EWrap ew) = return (EWrap ew)
-tcValArg do_ql pos fun (EValArg { ea_loc_span = lspan
+tcValArg do_ql pos (fun, fun_lspan) (EValArg { ea_loc_span = lspan
, ea_arg = larg@(L arg_loc arg)
, ea_arg_ty = sc_arg_ty })
- = addArgCtxt pos fun larg $
+ = addArgCtxt pos (fun, fun_lspan) larg $
do { -- Crucial step: expose QL results before checking exp_arg_ty
-- So far as the paper is concerned, this step applies
-- the poly-substitution Theta, learned by QL, so that we
@@ -601,6 +604,7 @@ tcValArg do_ql pos fun (EValArg { ea_loc_span = lspan
NoQL -> return sc_arg_ty
; traceTc "tcValArg {" $
vcat [ text "lspan:" <+> ppr lspan
+ , text "fun_lspan" <+> ppr fun_lspan
, text "sigma_type" <+> ppr (mkCheckExpType exp_arg_ty)
, text "arg:" <+> ppr larg
]
@@ -615,7 +619,7 @@ tcValArg do_ql pos fun (EValArg { ea_loc_span = lspan
, ea_arg = L arg_loc arg'
, ea_arg_ty = noExtField }) }
-tcValArg _ pos fun (EValArgQL {
+tcValArg _ pos (fun, fun_lspan) (EValArgQL {
eaql_wanted = wanted
, eaql_loc_span = lspan
, eaql_arg_ty = sc_arg_ty
@@ -626,7 +630,7 @@ tcValArg _ pos fun (EValArgQL {
, eaql_args = inst_args
, eaql_encl = arg_influences_enclosing_call
, eaql_res_rho = app_res_rho })
- = addArgCtxt pos fun larg $
+ = addArgCtxt pos (fun, fun_lspan) larg $
do { -- Expose QL results to tcSkolemise, as in EValArg case
Scaled mult exp_arg_ty <- liftZonkM $ zonkScaledTcType sc_arg_ty
@@ -635,6 +639,8 @@ tcValArg _ pos fun (EValArgQL {
, text "args:" <+> ppr inst_args
, text "mult:" <+> ppr mult
, text "fun" <+> ppr fun
+ , text "app_lspan" <+> ppr lspan
+ , text "head_lspan" <+> ppr fun_lspan
, text "tc_head" <+> ppr tc_head])
; ds_flag <- getDeepSubsumptionFlag
@@ -653,7 +659,7 @@ tcValArg _ pos fun (EValArgQL {
; unless arg_influences_enclosing_call $ -- Don't repeat
qlUnify app_res_rho exp_arg_rho -- the qlUnify
- ; tc_args <- tcValArgs DoQL rn_fun inst_args
+ ; tc_args <- tcValArgs DoQL (rn_fun, snd tc_head) inst_args
; app_res_rho <- liftZonkM $ zonkTcType app_res_rho
; res_wrap <- checkResultTy rn_expr tc_head inst_args
app_res_rho (mkCheckExpType exp_arg_rho)
@@ -696,20 +702,20 @@ tcInstFun :: QLFlag
-- Generally speaking we pass in True; in Fig 5 of the paper
-- |-inst returns a rho-type
-> CtOrigin
- -> (HsExpr GhcTc, HsExpr GhcRn, SrcSpan)
+ -> (HsExpr GhcTc, HsExpr GhcRn, SrcSpan) -- ANI: TODO, move HsExpr GhcRn, SrcSpan to CtOrigin
-> TcSigmaType -> [HsExprArg 'TcpRn]
-> TcM ( [HsExprArg 'TcpInst]
, TcSigmaType ) -- Does not instantiate trailing invisible foralls
-- This crucial function implements the |-inst judgement in Fig 4, plus the
-- modification in Fig 5, of the QL paper:
-- "A quick look at impredicativity" (ICFP'20).
-tcInstFun do_ql inst_final fun_orig (tc_fun, rn_fun, fun_ctxt) fun_sigma rn_args
+tcInstFun do_ql inst_final fun_orig (tc_fun, rn_fun, fun_lspan) fun_sigma rn_args
= do { traceTc "tcInstFun" (vcat [ text "origin" <+> ppr fun_orig
, text "tc_fun" <+> ppr tc_fun
, text "fun_sigma" <+> ppr fun_sigma
, text "args:" <+> ppr rn_args
, text "do_ql" <+> ppr do_ql
- , text "ctx" <+> ppr fun_ctxt])
+ , text "ctx" <+> ppr fun_lspan])
; setQLInstLevel do_ql $ -- See (TCAPP1) and (TCAPP2) in
-- Note [tcApp: typechecking applications]
go 1 [] fun_sigma rn_args }
@@ -786,7 +792,7 @@ tcInstFun do_ql inst_final fun_orig (tc_fun, rn_fun, fun_ctxt) fun_sigma rn_args
= do { (_inst_tvs, wrap, fun_rho) <-
-- addHeadCtxt: important for the class constraints
-- that may be emitted from instantiating fun_sigma
- setSrcSpan fun_ctxt $
+ setSrcSpan fun_lspan $
instantiateSigma fun_orig fun_conc_tvs tvs theta body2
-- See Note [Representation-polymorphism checking built-ins]
-- in GHC.Tc.Utils.Concrete.
@@ -881,7 +887,7 @@ tcInstFun do_ql inst_final fun_orig (tc_fun, rn_fun, fun_ctxt) fun_sigma rn_args
(Just $ HsExprTcThing tc_fun)
(n_val_args, fun_sigma) fun_ty
- ; arg' <- quickLookArg do_ql pos ctxt rn_fun arg arg_ty
+ ; arg' <- quickLookArg do_ql pos ctxt (rn_fun, fun_lspan) arg arg_ty
; let acc' = arg' : addArgWrap wrap acc
; go (pos+1) acc' res_ty rest_args }
@@ -931,7 +937,7 @@ looks_like_type_arg EValArg{ ea_arg = L _ e } =
_ -> False
looks_like_type_arg _ = False
-addArgCtxt :: Int -> HsExpr GhcRn -> LHsExpr GhcRn
+addArgCtxt :: Int -> (HsExpr GhcRn, SrcSpan) -> LHsExpr GhcRn
-> TcM a -> TcM a
-- There are 2 cases:
-- 1. In the normal case, we add an informative context (<=> `inGeneratedCode` is `False`)
@@ -942,7 +948,7 @@ addArgCtxt :: Int -> HsExpr GhcRn -> LHsExpr GhcRn
-- (iii) if arg_loc is RealSrcLoc then update tcl_loc and add "In the expression: arg" to ErrCtxtStack
-- See Note [Rebindable syntax and XXExprGhcRn] in GHC.Hs.Expr
-- See Note [Expanding HsDo with XXExprGhcRn] in GHC.Tc.Gen.Do
-addArgCtxt arg_no fun (L arg_loc arg) thing_inside
+addArgCtxt arg_no (fun, fun_lspan) (L arg_loc arg) thing_inside
= do { in_generated_code <- inGeneratedCode
; err_ctx <- getErrCtxt
; env0 <- liftZonkM tcInitTidyEnv
@@ -951,12 +957,14 @@ addArgCtxt arg_no fun (L arg_loc arg) thing_inside
, text "arg: " <+> ppr (arg, arg_no)
, text "arg_loc:" <+> ppr arg_loc
, text "fun:" <+> ppr fun
- , text "err_ctx" <+> vcat (fmap (\ (x, y) -> case x of
- MkErrCtxt (ExpansionCodeCtxt{}) _ -> text "<EXPN>" <+> pprErrCtxtMsg y
- _ -> text "<USER>" <+> pprErrCtxtMsg y)
- (take 4 (zip err_ctx err_ctx_msg)))
+ , text "fun_lspan" <+> ppr fun_lspan
+ , text "err_ctx" <+> vcat (fmap (\ (x, y) ->
+ case x of
+ MkErrCtxt (ExpansionCodeCtxt{}) _ -> text "<EXPN>" <+> pprErrCtxtMsg y
+ _ -> text "<USER>" <+> pprErrCtxtMsg y)
+ (take 4 (zip err_ctx err_ctx_msg)))
])
- ; if in_generated_code
+ ; if in_generated_code && isGeneratedSrcSpan fun_lspan
then updCtxtForArg (L arg_loc arg) $
thing_inside
else do setSrcSpanA arg_loc $
@@ -1745,24 +1753,26 @@ This turned out to be more subtle than I expected. Wrinkles:
-}
-quickLookArg :: QLFlag -> Int -> SrcSpan -> HsExpr GhcRn
+quickLookArg :: QLFlag -> Int
+ -> SrcSpan -- ^ location span of the whole application
+ -> (HsExpr GhcRn, SrcSpan) -- ^ Head of the application chain and its source span
-> LHsExpr GhcRn -- ^ Argument
-> Scaled TcSigmaTypeFRR -- ^ Type expected by the function
-> TcM (HsExprArg 'TcpInst)
-- See Note [Quick Look at value arguments]
-quickLookArg NoQL _ ctxt _ larg orig_arg_ty
- = skipQuickLook ctxt larg orig_arg_ty
-quickLookArg DoQL pos ctxt fun larg orig_arg_ty
+quickLookArg NoQL _ app_lspan _ larg orig_arg_ty
+ = skipQuickLook app_lspan larg orig_arg_ty
+quickLookArg DoQL pos app_lspan fun_and_lspan larg orig_arg_ty
= do { is_rho <- tcIsDeepRho (scaledThing orig_arg_ty)
; traceTc "qla" (ppr orig_arg_ty $$ ppr is_rho)
; if not is_rho
- then skipQuickLook ctxt larg orig_arg_ty
- else quickLookArg1 pos ctxt fun larg orig_arg_ty }
+ then skipQuickLook app_lspan larg orig_arg_ty
+ else quickLookArg1 pos app_lspan fun_and_lspan larg orig_arg_ty }
skipQuickLook :: SrcSpan -> LHsExpr GhcRn -> Scaled TcRhoType
-> TcM (HsExprArg 'TcpInst)
-skipQuickLook ctxt larg arg_ty
- = return (EValArg { ea_loc_span = ctxt
+skipQuickLook app_lspan larg arg_ty
+ = return (EValArg { ea_loc_span = app_lspan
, ea_arg = larg
, ea_arg_ty = arg_ty })
@@ -1800,14 +1810,14 @@ isGuardedTy ty
| Just {} <- tcSplitAppTy_maybe ty = True
| otherwise = False
-quickLookArg1 :: Int -> SrcSpan -> HsExpr GhcRn -> LHsExpr GhcRn
+quickLookArg1 :: Int -> SrcSpan -> (HsExpr GhcRn, SrcSpan) -> LHsExpr GhcRn
-> Scaled TcRhoType -- Deeply skolemised
-> TcM (HsExprArg 'TcpInst)
-- quickLookArg1 implements the "QL Argument" judgement in Fig 5 of the paper
-quickLookArg1 pos ctxt fun larg@(L _ arg) sc_arg_ty@(Scaled _ orig_arg_rho)
- = addArgCtxt pos fun larg $ -- Context needed for constraints
+quickLookArg1 pos app_lspan (fun, fun_lspan) larg@(L _ arg) sc_arg_ty@(Scaled _ orig_arg_rho)
+ = addArgCtxt pos (fun, fun_lspan) larg $ -- Context needed for constraints
-- generated by calls in arg
- do { ((rn_fun, fun_ctxt), rn_args) <- splitHsApps arg
+ do { ((rn_fun, fun_lspan), rn_args) <- splitHsApps arg
-- Step 1: get the type of the head of the argument
; (fun_ue, mb_fun_ty) <- tcCollectingUsage $ tcInferAppHead_maybe rn_fun
@@ -1823,15 +1833,15 @@ quickLookArg1 pos ctxt fun larg@(L _ arg) sc_arg_ty@(Scaled _ orig_arg_rho)
, text "args:" <+> ppr rn_args ]
; case mb_fun_ty of {
- Nothing -> skipQuickLook ctxt larg sc_arg_ty ; -- fun is too complicated
+ Nothing -> skipQuickLook app_lspan larg sc_arg_ty ; -- fun is too complicated
Just (tc_fun, fun_sigma) ->
-- step 2: use |-inst to instantiate the head applied to the arguments
- do { let tc_head = (tc_fun, fun_ctxt)
+ do { let tc_head = (tc_fun, fun_lspan)
; do_ql <- wantQuickLook rn_fun
; ((inst_args, app_res_rho), wanted)
<- captureConstraints $
- tcInstFun do_ql True (exprCtOrigin arg) (tc_fun, rn_fun, fun_ctxt) fun_sigma rn_args
+ tcInstFun do_ql True (exprCtOrigin arg) (tc_fun, rn_fun, fun_lspan) fun_sigma rn_args
-- We must capture type-class and equality constraints here, but
-- not equality constraints. See (QLA6) in Note [Quick Look at
-- value arguments]
@@ -1863,7 +1873,7 @@ quickLookArg1 pos ctxt fun larg@(L _ arg) sc_arg_ty@(Scaled _ orig_arg_rho)
; traceTc "quickLookArg done }" (ppr rn_fun)
- ; return (EValArgQL { eaql_loc_span = ctxt
+ ; return (EValArgQL { eaql_loc_span = app_lspan
, eaql_arg_ty = sc_arg_ty
, eaql_larg = larg
, eaql_tc_fun = tc_head
=====================================
compiler/GHC/Tc/Gen/Do.hs
=====================================
@@ -81,7 +81,7 @@ expand_do_stmts flav [stmt@(L sloc (LastStmt _ body@(L body_loc _) _ ret_expr))]
-- See `checkLastStmt` and `Syntax.Expr.StmtLR.LastStmt`
| NoSyntaxExprRn <- ret_expr
-- Last statement is just body if we are not in ListComp context. See Syntax.Expr.LastStmt
- = return $ L sloc (mkExpandedLastStmt (HsPar noExtField body))
+ = return $ L sloc (mkExpandedStmt stmt flav (HsPar noExtField body))
| SyntaxExprRn ret <- ret_expr -- We have unfortunately lost the location on the return function :(
--
@@ -89,7 +89,7 @@ expand_do_stmts flav [stmt@(L sloc (LastStmt _ body@(L body_loc _) _ ret_expr))]
-- return e ~~> return e
-- to make T18324 work
= do let expansion = L body_loc (genHsApp ret body)
- return $ L sloc (mkExpandedLastStmt (HsPar noExtField expansion))
+ return $ L sloc (mkExpandedStmt stmt flav (HsPar noExtField expansion))
expand_do_stmts doFlavour (stmt@(L loc (LetStmt _ bs)) : lstmts) =
-- See Note [Expanding HsDo with XXExprGhcRn] Equation (3) below
@@ -118,7 +118,7 @@ expand_do_stmts doFlavour (stmt@(L loc (BindStmt xbsrn pat e)): lstmts)
| otherwise
= pprPanic "expand_do_stmts: The impossible happened, missing bind operator from renamer" (text "stmt" <+> ppr stmt)
-expand_do_stmts doFlavour (stmt@(L loc (BodyStmt _ e (SyntaxExprRn then_op) _)) : lstmts) =
+expand_do_stmts doFlavour (stmt@(L loc (BodyStmt _ (L e_lspan e) (SyntaxExprRn then_op) _)) : lstmts) =
-- See Note [BodyStmt] in Language.Haskell.Syntax.Expr
-- See Note [Expanding HsDo with XXExprGhcRn] Equation (1) below
-- stmts ~~> stmts'
@@ -126,7 +126,7 @@ expand_do_stmts doFlavour (stmt@(L loc (BodyStmt _ e (SyntaxExprRn then_op) _))
-- e ; stmts ~~> (>>) e stmts'
do expand_stmts_expr <- expand_do_stmts doFlavour lstmts
let expansion = genHsExpApps then_op -- (>>)
- [ e
+ [ L e_lspan (mkExpandedStmt stmt doFlavour e)
, expand_stmts_expr ]
return $ L loc (mkExpandedStmt stmt doFlavour expansion)
@@ -486,3 +486,6 @@ It stores the original statement (with location) and the expanded expression
mkExpandedPatRn :: Pat GhcRn -> HsExpr GhcRn -> HsExpr GhcRn
mkExpandedPatRn pat e = XExpr (ExpandedThingRn (OrigPat pat) e)
+
+mkPopErrCtxtExprRn :: HsExpr GhcRn -> HsExpr GhcRn
+mkPopErrCtxtExprRn e = XExpr (ExpandedThingRn PopErrCtxt e)
=====================================
compiler/GHC/Tc/Gen/Head.hs
=====================================
@@ -175,7 +175,7 @@ data HsExprArg (p :: TcPass) where -- See Note [HsExprArg]
, eaql_larg :: LHsExpr GhcRn -- Original application, for
-- location and error msgs
, eaql_rn_fun :: HsExpr GhcRn -- Head of the argument if it is an application
- , eaql_tc_fun :: (HsExpr GhcTc, SrcSpan) -- Typechecked head
+ , eaql_tc_fun :: (HsExpr GhcTc, SrcSpan) -- Typechecked head and its location span
, eaql_fun_ue :: UsageEnv -- Usage environment of the typechecked head (QLA5)
, eaql_args :: [HsExprArg 'TcpInst] -- Args: instantiated, not typechecked
, eaql_wanted :: WantedConstraints
@@ -456,8 +456,8 @@ tcInferAppHead :: (HsExpr GhcRn, SrcSpan)
-- cases are dealt with by splitHsApps.
--
-- See Note [tcApp: typechecking applications] in GHC.Tc.Gen.App
-tcInferAppHead (fun,fun_loc)
- = setSrcSpan fun_loc $
+tcInferAppHead (fun,fun_lspan)
+ = setSrcSpan fun_lspan $
do { mb_tc_fun <- tcInferAppHead_maybe fun
; case mb_tc_fun of
Just (fun', fun_sigma) -> return (fun', fun_sigma)
@@ -471,7 +471,8 @@ tcInferAppHead_maybe fun =
case fun of
HsVar _ nm -> Just <$> tcInferId nm
XExpr (HsRecSelRn f) -> Just <$> tcInferRecSelId f
- XExpr (ExpandedThingRn o e) -> Just <$> (addExpansionErrCtxt o (srcCodeOriginErrCtxMsg o) $ -- We do not want to instantiate c.f. T19167
+ XExpr (ExpandedThingRn o e) -> Just <$> (addExpansionErrCtxt o (srcCodeOriginErrCtxMsg o) $
+ -- We do not want to instantiate c.f. T19167
tcExprSigma False e)
ExprWithTySig _ e hs_ty -> Just <$> tcExprWithSig e hs_ty
HsOverLit _ lit -> Just <$> tcInferOverLit lit
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/eb9ac0c913c9c4218eb868081aab64e…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/eb9ac0c913c9c4218eb868081aab64e…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T26425] 22 commits: Handle implications between x86 feature flags
by Simon Peyton Jones (@simonpj) 31 Oct '25
by Simon Peyton Jones (@simonpj) 31 Oct '25
31 Oct '25
Simon Peyton Jones pushed to branch wip/T26425 at Glasgow Haskell Compiler / GHC
Commits:
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`.
- - - - -
68b987fa by Simon Peyton Jones at 2025-10-30T16:55:03+00:00
Experimental occ-anal patch
... needs documenation...
- - - - -
0f087284 by Simon Peyton Jones at 2025-10-30T16:55:03+00:00
Wibble
- - - - -
a0566bf0 by Simon Peyton Jones at 2025-10-30T16:55:03+00:00
Fix buglet that led to non-termination!
- - - - -
193bf312 by Simon Peyton Jones at 2025-10-30T17:09:24+00:00
Fixes
- - - - -
143 changed files:
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/Cmm/MachOp.hs
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/Config.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/CodeGen.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/HsToCore/Foreign/Wasm.hs
- compiler/GHC/HsToCore/Pmc/Utils.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Platform.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Rename/Unbound.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/StgToJS/Prim.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Deriv/Generics.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Validity.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/Hint.hs
- compiler/GHC/Types/Hint/Ppr.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Types/Unique/FM.hs
- compiler/GHC/Types/Unique/Set.hs
- compiler/GHC/Types/Var/Env.hs
- compiler/Language/Haskell/Syntax/Expr.hs
- docs/users_guide/9.16.1-notes.rst
- docs/users_guide/using.rst
- hadrian/src/Rules/Gmp.hs
- hadrian/src/Rules/Libffi.hs
- hadrian/src/Settings/Builders/Cabal.hs
- hadrian/src/Settings/Builders/Common.hs
- hadrian/src/Settings/Builders/DeriveConstants.hs
- hadrian/src/Settings/Builders/Hsc2Hs.hs
- libraries/base/src/GHC/Base.hs
- libraries/base/src/GHC/Exts.hs
- libraries/ghc-experimental/CHANGELOG.md
- libraries/ghc-internal/cbits/Stack_c.c
- libraries/ghc-internal/ghc-internal.cabal.in
- + libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc
- libraries/ghc-internal/src/GHC/Internal/Stack/Decode.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
- m4/fp_check_pthreads.m4
- rts/configure.ac
- + rts/rts.buildinfo.in
- rts/rts.cabal
- 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/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/linters/all.T
- testsuite/tests/module/mod4.stderr
- + testsuite/tests/overloadedrecflds/should_fail/T26480.hs
- + testsuite/tests/overloadedrecflds/should_fail/T26480.stderr
- + testsuite/tests/overloadedrecflds/should_fail/T26480_aux1.hs
- + testsuite/tests/overloadedrecflds/should_fail/T26480_aux2.hs
- + testsuite/tests/overloadedrecflds/should_fail/T26480b.hs
- + testsuite/tests/overloadedrecflds/should_fail/T26480b.stderr
- testsuite/tests/overloadedrecflds/should_fail/all.T
- testsuite/tests/overloadedrecflds/should_fail/hasfieldfail01.stderr
- testsuite/tests/overloadedrecflds/should_fail/hasfieldfail02.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail11.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/all.T
- + testsuite/tests/perf/compiler/T26425.hs
- testsuite/tests/perf/compiler/all.T
- + testsuite/tests/rename/should_compile/T12488b.hs
- + testsuite/tests/rename/should_compile/T12488f.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/T25899e2.stderr
- testsuite/tests/rename/should_fail/all.T
- 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/typecheck/should_compile/T17705.hs
- testsuite/tests/typecheck/should_compile/all.T
- utils/check-exact/ExactPrint.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs
- 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/0675a96cd150475fb8f0a6ac303cfe…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0675a96cd150475fb8f0a6ac303cfe…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T23162-spj] 14 commits: Add a perf test for #26425
by Simon Peyton Jones (@simonpj) 31 Oct '25
by Simon Peyton Jones (@simonpj) 31 Oct '25
31 Oct '25
Simon Peyton Jones pushed to branch wip/T23162-spj at Glasgow Haskell Compiler / GHC
Commits:
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`.
- - - - -
2cc9924e by Richard Eisenberg at 2025-10-30T17:08:32+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
- - - - -
072466a4 by Simon Peyton Jones at 2025-10-30T17:08:32+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.
- - - - -
0c9e957c by Simon Peyton Jones at 2025-10-30T17:08:32+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.
- - - - -
fbb2a831 by Simon Peyton Jones at 2025-10-30T17:08:32+00:00
Comments about defaulting representation equalities
- - - - -
b59a8713 by Simon Peyton Jones at 2025-10-30T17:08:32+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`
- - - - -
02de4352 by Simon Peyton Jones at 2025-10-30T17:08:32+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.
- - - - -
27b3b406 by Simon Peyton Jones at 2025-10-30T17:08:32+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.
- - - - -
49a558ed by Simon Peyton Jones at 2025-10-30T17:08:32+00:00
Update debug-tracing in CallArity
No effect on behaviour, and commented out anyway
- - - - -
c35ab399 by Simon Peyton Jones at 2025-10-30T17:08:33+00:00
Comments only -- remove dangling Note references
- - - - -
eaf505bd by Simon Peyton Jones at 2025-10-30T17:08:33+00:00
Accept error message wibbles
- - - - -
09161c1f by Simon Peyton Jones at 2025-10-30T17:08:33+00:00
Comments only
- - - - -
125 changed files:
- compiler/GHC/Core/Opt/CallArity.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/TyCo/FVs.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Iface/Tidy/StaticPtrTable.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Tc/Instance/FunDeps.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/Types.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Concrete.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/Zonk/TcType.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/Types/Basic.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/Hint.hs
- compiler/GHC/Types/Hint/Ppr.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Types/Unique/DSM.hs
- compiler/GHC/Types/Unique/FM.hs
- compiler/GHC/Types/Var/Env.hs
- + compiler/GHC/Utils/EndoOS.hs
- compiler/ghc.cabal.in
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- testsuite/tests/default/default-fail05.stderr
- testsuite/tests/dependent/should_fail/T13135_simple.stderr
- testsuite/tests/deriving/should_fail/T3621.stderr
- testsuite/tests/indexed-types/should_fail/T14369.stderr
- testsuite/tests/indexed-types/should_fail/T1897b.stderr
- testsuite/tests/linters/notes.stdout
- testsuite/tests/module/mod4.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail10.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail13.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/perf/compiler/T26425.hs
- testsuite/tests/perf/compiler/all.T
- testsuite/tests/polykinds/T6068.stdout
- testsuite/tests/quantified-constraints/T15359.hs
- + testsuite/tests/rename/should_compile/T12488b.hs
- + testsuite/tests/rename/should_compile/T12488f.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/T25899e2.stderr
- testsuite/tests/rename/should_fail/all.T
- testsuite/tests/rep-poly/RepPolyNPlusK.stderr
- testsuite/tests/rep-poly/RepPolyRightSection.stderr
- testsuite/tests/rep-poly/T13233.stderr
- testsuite/tests/rep-poly/T19709b.stderr
- testsuite/tests/rep-poly/T23903.stderr
- testsuite/tests/typecheck/no_skolem_info/T13499.stderr
- testsuite/tests/typecheck/should_compile/T13651.hs
- − testsuite/tests/typecheck/should_compile/T13651.stderr
- + testsuite/tests/typecheck/should_compile/T14745.hs
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_compile/hole_constraints_nested.stderr
- testsuite/tests/typecheck/should_compile/tc126.hs
- testsuite/tests/typecheck/should_fail/AmbigFDs.hs
- − testsuite/tests/typecheck/should_fail/AmbigFDs.stderr
- testsuite/tests/typecheck/should_fail/FD3.stderr
- testsuite/tests/typecheck/should_fail/FDsFromGivens2.stderr
- testsuite/tests/typecheck/should_fail/T13506.stderr
- testsuite/tests/typecheck/should_fail/T16512a.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/T22684.stderr
- + testsuite/tests/typecheck/should_fail/T23162a.hs
- + testsuite/tests/typecheck/should_fail/T23162a.stderr
- testsuite/tests/typecheck/should_fail/T25325.stderr
- testsuite/tests/typecheck/should_fail/T5246.stderr
- testsuite/tests/typecheck/should_fail/T5978.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/TcStaticPointersFail03.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/typecheck/should_fail/tcfail122.stderr
- testsuite/tests/typecheck/should_fail/tcfail143.stderr
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/040919fec6783a2b2e0b9c4b54fbc0…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/040919fec6783a2b2e0b9c4b54fbc0…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T26349] 10 commits: Skip uniques test if sources are not available
by Simon Peyton Jones (@simonpj) 31 Oct '25
by Simon Peyton Jones (@simonpj) 31 Oct '25
31 Oct '25
Simon Peyton Jones pushed to branch wip/T26349 at Glasgow Haskell Compiler / GHC
Commits:
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`.
- - - - -
ce0773a7 by Simon Peyton Jones at 2025-10-30T17:02:14+00:00
Add a HsWrapper optimiser
This is an experimental MR. The big change is adding
`GHC.Tc.Types.Evidence.optHsWrapper
Addresses #26349
A bit more
Working, I think
Remove silly trace
Better now
Added WpSubType
Remove trace
better
More
Comments and one test wibble
- - - - -
9f6aee01 by Simon Peyton Jones at 2025-10-30T17:02:14+00: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.
- - - - -
f4f71579 by Simon Peyton Jones at 2025-10-30T17:02:14+00:00
Comments only
- - - - -
82 changed files:
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Hs.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Foreign/Wasm.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Deriv/Generics.hs
- compiler/GHC/Tc/Errors/Hole.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Concrete.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Tc/Validity.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/Hint.hs
- compiler/GHC/Types/Hint/Ppr.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Types/Unique/FM.hs
- compiler/GHC/Types/Var/Env.hs
- m4/fp_check_pthreads.m4
- rts/configure.ac
- + rts/rts.buildinfo.in
- rts/rts.cabal
- testsuite/tests/linters/all.T
- testsuite/tests/module/mod4.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/all.T
- + testsuite/tests/perf/compiler/T26425.hs
- testsuite/tests/perf/compiler/all.T
- + testsuite/tests/rename/should_compile/T12488b.hs
- + testsuite/tests/rename/should_compile/T12488f.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/T25899e2.stderr
- testsuite/tests/rename/should_fail/all.T
- + testsuite/tests/simplCore/should_compile/T26349.hs
- + testsuite/tests/simplCore/should_compile/T26349.stderr
- testsuite/tests/simplCore/should_compile/all.T
- testsuite/tests/simplCore/should_compile/rule2.stderr
- + testsuite/tests/typecheck/should_compile/T17705.hs
- testsuite/tests/typecheck/should_compile/all.T
- utils/check-exact/ExactPrint.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6676d34dab1bc325de619605b2d8ea…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6676d34dab1bc325de619605b2d8ea…
You're receiving this email because of your account on gitlab.haskell.org.
1
0