
[Git][ghc/ghc][wip/symbolizer] 3 commits: compiler: fix closure C type in SPT init code
by Cheng Shao (@TerrorJack) 16 Aug '25
by Cheng Shao (@TerrorJack) 16 Aug '25
16 Aug '25
Cheng Shao pushed to branch wip/symbolizer at Glasgow Haskell Compiler / GHC
Commits:
f38fcd9b by Cheng Shao at 2025-08-16T13:57:20+02:00
compiler: fix closure C type in SPT init code
This patch fixes the closure C type in SPT init code to StgClosure,
instead of the previously incorrect StgPtr. Having an incorrect C type
makes SPT init code not compatible with other foreign stub generation
logic, which may also emit their own extern declarations for the same
closure symbols and thus will clash with the incorrect prototypes in
SPT init code.
- - - - -
107feea4 by Cheng Shao at 2025-08-16T13:57:20+02:00
rts: remove libbfd logic
- - - - -
fd415c7a by Cheng Shao at 2025-08-16T13:57:20+02:00
compiler/rts: add debug symbolizer
- - - - -
18 changed files:
- + compiler/GHC/Cmm/GenerateDebugSymbolStub.hs
- compiler/GHC/Driver/CodeOutput.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Iface/Tidy/StaticPtrTable.hs
- compiler/ghc.cabal.in
- configure.ac
- hadrian/cfg/system.config.in
- hadrian/src/Oracles/Flag.hs
- hadrian/src/Settings/Packages.hs
- − m4/fp_bfd_support.m4
- rts/Printer.c
- rts/Printer.h
- rts/RtsStartup.c
- rts/configure.ac
- rts/include/Rts.h
- rts/include/rts/Config.h
- + rts/include/rts/Debug.h
- rts/rts.cabal
Changes:
=====================================
compiler/GHC/Cmm/GenerateDebugSymbolStub.hs
=====================================
@@ -0,0 +1,138 @@
+{-# LANGUAGE MultiWayIf #-}
+{-# LANGUAGE Strict #-}
+
+module GHC.Cmm.GenerateDebugSymbolStub
+ ( generateDebugSymbolStub,
+ )
+where
+
+import Control.Monad
+import Control.Monad.IO.Class
+import Data.Foldable
+import Data.Functor
+import Data.IORef
+import Data.List (isSuffixOf)
+import Data.Map.Strict qualified as Map
+import Data.Maybe
+import GHC.Cmm
+import GHC.Cmm.CLabel
+import GHC.Cmm.Dataflow.Label qualified as H
+import GHC.Data.FastString
+import GHC.Data.Stream (Stream)
+import GHC.Data.Stream qualified as Stream
+import GHC.Platform
+import GHC.Prelude
+import GHC.Types.ForeignStubs
+import GHC.Unit.Types
+import GHC.Utils.Outputable
+
+generateDebugSymbolStub ::
+ (MonadIO m) =>
+ Platform ->
+ Module ->
+ Stream m RawCmmGroup r ->
+ Stream m RawCmmGroup (r, CStub)
+generateDebugSymbolStub platform this_mod rawcmms0 = do
+ (lbls_ref, per_group) <- liftIO $ do
+ lbls_ref <- newIORef Map.empty
+ let per_group decls = for_ decls per_decl $> decls
+ per_decl (CmmData _ (CmmStaticsRaw lbl _)) =
+ liftIO
+ $ when (externallyVisibleCLabel lbl)
+ $ modifyIORef' lbls_ref
+ $ Map.insert lbl (data_label_type lbl)
+ per_decl (CmmProc h lbl _ _) = case H.mapToList h of
+ [] ->
+ liftIO
+ $ when (externallyVisibleCLabel lbl)
+ $ modifyIORef' lbls_ref
+ $ Map.insert lbl (proc_label_type lbl)
+ hs -> for_ hs $ \(_, CmmStaticsRaw lbl _) ->
+ liftIO
+ $ when (externallyVisibleCLabel lbl)
+ $ modifyIORef' lbls_ref
+ $ Map.insert lbl (data_label_type lbl)
+ data_label_type lbl
+ | "_closure"
+ `isSuffixOf` str
+ && not
+ (str `elem` ["stg_CHARLIKE_closure", "stg_INTLIKE_closure"]) =
+ Just ("extern StgClosure ", "")
+ | "_str" `isSuffixOf` str =
+ Just ("EB_(", ")")
+ | str
+ `elem` [ "stg_arg_bitmaps",
+ "stg_ap_stack_entries",
+ "stg_stack_save_entries"
+ ] =
+ Just ("ERO_(", ")")
+ | str
+ `elem` [ "no_break_on_exception",
+ "stg_scheduler_loop_epoch",
+ "stg_scheduler_loop_tid"
+ ] =
+ Just ("ERW_(", ")")
+ | str
+ `elem` [ "stg_gc_prim_p_ll_info",
+ "stg_gc_prim_pp_ll_info",
+ "stg_JSVAL_info",
+ "stg_scheduler_loop_info"
+ ] =
+ Just ("extern const StgInfoTable ", "")
+ | not $ needsCDecl lbl =
+ Nothing
+ | "_cc" `isSuffixOf` str =
+ Just ("extern CostCentre ", "[]")
+ | "_ccs" `isSuffixOf` str =
+ Just ("extern CostCentreStack ", "[]")
+ | "_ipe_buf" `isSuffixOf` str =
+ Just ("extern IpeBufferListNode ", "")
+ | otherwise =
+ Just ("ERW_(", ")")
+ where
+ str =
+ showSDocOneLine defaultSDocContext {sdocStyle = PprCode}
+ $ pprCLabel platform lbl
+ proc_label_type _ = Just ("EF_(", ")")
+ pure (lbls_ref, per_group)
+ r <- Stream.mapM per_group rawcmms0
+ liftIO $ do
+ lbls <- Map.toList <$> readIORef lbls_ref
+ let ctor_lbl = mkInitializerStubLabel this_mod $ fsLit "symbolizer"
+ entries_lbl =
+ mkInitializerStubLabel this_mod $ fsLit "symbolizer_entries"
+ ctor_decls =
+ vcat
+ [ text lbl_type_l
+ <> pprCLabel platform lbl
+ <> text lbl_type_r
+ <> semi
+ | (lbl, maybe_lbl_type) <- lbls,
+ (lbl_type_l, lbl_type_r) <- maybeToList maybe_lbl_type
+ ]
+ <> text "static const DebugSymbolEntry "
+ <> pprCLabel platform entries_lbl
+ <> text "[] = "
+ <> braces
+ ( hsep
+ $ punctuate
+ comma
+ [ braces
+ $ text ".addr = (void*)&"
+ <> pprCLabel platform lbl
+ <> comma
+ <> text ".sym = "
+ <> doubleQuotes (pprCLabel platform lbl)
+ | (lbl, _) <- lbls
+ ]
+ )
+ <> semi
+ ctor_body =
+ text "registerDebugSymbol"
+ <> parens
+ (pprCLabel platform entries_lbl <> comma <> int (length lbls))
+ <> semi
+ cstub = case lbls of
+ [] -> mempty
+ _ -> initializerCStub platform ctor_lbl ctor_decls ctor_body
+ pure (r, cstub)
=====================================
compiler/GHC/Driver/CodeOutput.hs
=====================================
@@ -26,6 +26,7 @@ import GHC.CmmToC ( cmmToC )
import GHC.Cmm.Lint ( cmmLint )
import GHC.Cmm
import GHC.Cmm.CLabel
+import GHC.Cmm.GenerateDebugSymbolStub
import GHC.StgToCmm.CgUtils (CgStream)
@@ -76,7 +77,8 @@ import qualified Data.Set as Set
codeOutput
:: forall a.
- Logger
+ Platform
+ -> Logger
-> TmpFs
-> LlvmConfigCache
-> DynFlags
@@ -95,7 +97,7 @@ codeOutput
(Bool{-stub_h_exists-}, Maybe FilePath{-stub_c_exists-}),
[(ForeignSrcLang, FilePath)]{-foreign_fps-},
a)
-codeOutput logger tmpfs llvm_config dflags unit_state this_mod filenm location genForeignStubs foreign_fps pkg_deps dus0
+codeOutput platform logger tmpfs llvm_config dflags unit_state this_mod filenm location genForeignStubs foreign_fps pkg_deps dus0
cmm_stream
=
do {
@@ -119,10 +121,12 @@ codeOutput logger tmpfs llvm_config dflags unit_state this_mod filenm location g
; return cmm
}
+ debug_cmm_stream = generateDebugSymbolStub platform this_mod linted_cmm_stream
+
; let final_stream :: CgStream RawCmmGroup (ForeignStubs, a)
final_stream = do
- { a <- linted_cmm_stream
- ; let stubs = genForeignStubs a
+ { (a, debug_cstub) <- debug_cmm_stream
+ ; let stubs = genForeignStubs a `appendStubC` debug_cstub
; emitInitializerDecls this_mod stubs
; return (stubs, a) }
=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -2094,7 +2094,7 @@ hscGenHardCode hsc_env cgguts mod_loc output_filename = do
(output_filename, (_stub_h_exists, stub_c_exists), foreign_fps, cmm_cg_infos)
<- {-# SCC "codeOutput" #-}
- codeOutput logger tmpfs llvm_config dflags (hsc_units hsc_env) this_mod output_filename mod_loc
+ codeOutput platform logger tmpfs llvm_config dflags (hsc_units hsc_env) this_mod output_filename mod_loc
foreign_stubs foreign_files dependencies (initDUniqSupply 'n' 0) rawcmms1
return ( output_filename, stub_c_exists, foreign_fps
, Just stg_cg_infos, Just cmm_cg_infos)
@@ -2248,7 +2248,7 @@ hscCompileCmmFile hsc_env original_filename filename output_filename = runHsc hs
in NoStubs `appendStubC` ip_init
| otherwise = NoStubs
(_output_filename, (_stub_h_exists, stub_c_exists), _foreign_fps, _caf_infos)
- <- codeOutput logger tmpfs llvm_config dflags (hsc_units hsc_env) cmm_mod output_filename no_loc foreign_stubs [] S.empty
+ <- codeOutput platform logger tmpfs llvm_config dflags (hsc_units hsc_env) cmm_mod output_filename no_loc foreign_stubs [] S.empty
dus1 rawCmms
return stub_c_exists
where
=====================================
compiler/GHC/Iface/Tidy/StaticPtrTable.hs
=====================================
@@ -17,18 +17,18 @@
-- > static void hs_hpc_init_Main(void) {
-- >
-- > static StgWord64 k0[2] = {16252233372134256ULL,7370534374096082ULL};
--- > extern StgPtr Main_r2wb_closure;
+-- > extern StgClosure Main_r2wb_closure;
-- > hs_spt_insert(k0, &Main_r2wb_closure);
-- >
-- > static StgWord64 k1[2] = {12545634534567898ULL,5409674567544151ULL};
--- > extern StgPtr Main_r2wc_closure;
+-- > extern StgClosure Main_r2wc_closure;
-- > hs_spt_insert(k1, &Main_r2wc_closure);
-- >
-- > }
--
-- where the constants are fingerprints produced from the static forms.
--
--- The linker must find the definitions matching the @extern StgPtr <name>@
+-- The linker must find the definitions matching the @extern StgClosure <name>@
-- declarations. For this to work, the identifiers of static pointers need to be
-- exported. This is done in 'GHC.Core.Opt.SetLevels.newLvlVar'.
--
@@ -256,7 +256,7 @@ sptModuleInitCode platform this_mod entries
init_fn_body = vcat
[ text "static StgWord64 k" <> int i <> text "[2] = "
<> pprFingerprint fp <> semi
- $$ text "extern StgPtr "
+ $$ text "extern StgClosure "
<> (pprCLabel platform $ mkClosureLabel (idName n) (idCafInfo n)) <> semi
$$ text "hs_spt_insert" <> parens
(hcat $ punctuate comma
=====================================
compiler/ghc.cabal.in
=====================================
@@ -242,6 +242,7 @@ Library
GHC.Cmm.Dataflow.Label
GHC.Cmm.DebugBlock
GHC.Cmm.Expr
+ GHC.Cmm.GenerateDebugSymbolStub
GHC.Cmm.GenericOpt
GHC.Cmm.Graph
GHC.Cmm.Info
=====================================
configure.ac
=====================================
@@ -876,9 +876,6 @@ AC_SUBST([UseLibm])
TargetHasLibm=$UseLibm
AC_SUBST(TargetHasLibm)
-FP_BFD_FLAG
-AC_SUBST([UseLibbfd])
-
dnl ################################################################
dnl Check for libraries
dnl ################################################################
=====================================
hadrian/cfg/system.config.in
=====================================
@@ -120,7 +120,6 @@ use-lib-numa = @UseLibNuma@
use-lib-m = @UseLibm@
use-lib-rt = @UseLibrt@
use-lib-dl = @UseLibdl@
-use-lib-bfd = @UseLibbfd@
use-lib-pthread = @UseLibpthread@
need-libatomic = @NeedLibatomic@
=====================================
hadrian/src/Oracles/Flag.hs
=====================================
@@ -36,7 +36,6 @@ data Flag = CrossCompiling
| UseLibm
| UseLibrt
| UseLibdl
- | UseLibbfd
| UseLibpthread
| NeedLibatomic
| UseGhcToolchain
@@ -60,7 +59,6 @@ flag f = do
UseLibm -> "use-lib-m"
UseLibrt -> "use-lib-rt"
UseLibdl -> "use-lib-dl"
- UseLibbfd -> "use-lib-bfd"
UseLibpthread -> "use-lib-pthread"
NeedLibatomic -> "need-libatomic"
UseGhcToolchain -> "use-ghc-toolchain"
=====================================
hadrian/src/Settings/Packages.hs
=====================================
@@ -442,7 +442,6 @@ rtsPackageArgs = package rts ? do
, useSystemFfi `cabalFlag` "use-system-libffi"
, useLibffiForAdjustors `cabalFlag` "libffi-adjustors"
, flag UseLibpthread `cabalFlag` "need-pthread"
- , flag UseLibbfd `cabalFlag` "libbfd"
, flag NeedLibatomic `cabalFlag` "need-atomic"
, flag UseLibdw `cabalFlag` "libdw"
, flag UseLibnuma `cabalFlag` "libnuma"
=====================================
m4/fp_bfd_support.m4 deleted
=====================================
@@ -1,59 +0,0 @@
-# FP_BFD_SUPPORT()
-# ----------------------
-# Whether to use libbfd for debugging RTS
-#
-# Sets:
-# UseLibbfd: [YES|NO]
-AC_DEFUN([FP_BFD_FLAG], [
- UseLibbfd=NO
- AC_ARG_ENABLE(bfd-debug,
- [AS_HELP_STRING([--enable-bfd-debug],
- [Enable symbol resolution for -debug rts ('+RTS -Di') via binutils' libbfd [default=no]])],
- [UseLibbfd=YES],
- [UseLibbfd=NO])
-])
-
-# FP_WHEN_ENABLED_BFD
-# ----------------------
-# Checks for libraries in the default way, which will define various
-# `HAVE_*` macros.
-AC_DEFUN([FP_WHEN_ENABLED_BFD], [
- # don't pollute general LIBS environment
- save_LIBS="$LIBS"
- AC_CHECK_HEADERS([bfd.h])
- dnl ** check whether this machine has BFD and libiberty installed (used for debugging)
- dnl the order of these tests matters: bfd needs libiberty
- AC_CHECK_LIB(iberty, xmalloc)
- dnl 'bfd_init' is a rare non-macro in libbfd
- AC_CHECK_LIB(bfd, bfd_init)
-
- AC_LINK_IFELSE(
- [AC_LANG_PROGRAM(
- [[#include <bfd.h>]],
- [[
- /* mimic our rts/Printer.c */
- bfd* abfd;
- const char * name;
- char **matching;
-
- name = "some.executable";
- bfd_init();
- abfd = bfd_openr(name, "default");
- bfd_check_format_matches (abfd, bfd_object, &matching);
- {
- long storage_needed;
- storage_needed = bfd_get_symtab_upper_bound (abfd);
- }
- {
- asymbol **symbol_table;
- long number_of_symbols;
- symbol_info info;
-
- number_of_symbols = bfd_canonicalize_symtab (abfd, symbol_table);
- bfd_get_symbol_info(abfd,symbol_table[0],&info);
- }
- ]])],
- [], dnl bfd seems to work
- [AC_MSG_ERROR([can't use 'bfd' library])])
- LIBS="$save_LIBS"
-])
=====================================
rts/Printer.c
=====================================
@@ -43,13 +43,20 @@ static void printStdObjPayload( const StgClosure *obj );
void printPtr( StgPtr p )
{
const char *raw;
- raw = lookupGHCName(p);
+ raw = lookupDebugSymbol(p);
if (raw != NULL) {
- debugBelch("<%s>", raw);
- debugBelch("[%p]", p);
- } else {
- debugBelch("%p", p);
+ debugBelch("<%s>[%p]", raw, p);
+ return;
}
+
+ StgPtr p0 = (StgPtr)UNTAG_CLOSURE((StgClosure *)p);
+ raw = lookupDebugSymbol(p0);
+ if (raw != NULL) {
+ debugBelch("<%s>[%p+%td]", raw, p0, p - p0);
+ return;
+ }
+
+ debugBelch("%p", p);
}
void printObj( StgClosure *obj )
@@ -853,129 +860,6 @@ void printLargeAndPinnedObjects(void)
* Uses symbol table in (unstripped executable)
* ------------------------------------------------------------------------*/
-/* --------------------------------------------------------------------------
- * Simple lookup table
- * address -> function name
- * ------------------------------------------------------------------------*/
-
-static HashTable * add_to_fname_table = NULL;
-
-const char *lookupGHCName( void *addr )
-{
- if (add_to_fname_table == NULL)
- return NULL;
-
- return lookupHashTable(add_to_fname_table, (StgWord)addr);
-}
-
-/* --------------------------------------------------------------------------
- * Symbol table loading
- * ------------------------------------------------------------------------*/
-
-/* Causing linking trouble on Win32 plats, so I'm
- disabling this for now.
-*/
-#if defined(USING_LIBBFD)
-# define PACKAGE 1
-# define PACKAGE_VERSION 1
-/* Those PACKAGE_* defines are workarounds for bfd:
- * https://sourceware.org/bugzilla/show_bug.cgi?id=14243
- * ghc's build system filter PACKAGE_* values out specifically to avoid clashes
- * with user's autoconf-based Cabal packages.
- * It's a shame <bfd.h> checks for unrelated fields instead of actually used
- * macros.
- */
-# include <bfd.h>
-
-/* Fairly ad-hoc piece of code that seems to filter out a lot of
- * rubbish like the obj-splitting symbols
- */
-
-static bool isReal( flagword flags STG_UNUSED, const char *name )
-{
-#if 0
- /* ToDo: make this work on BFD */
- int tp = type & N_TYPE;
- if (tp == N_TEXT || tp == N_DATA) {
- return (name[0] == '_' && name[1] != '_');
- } else {
- return false;
- }
-#else
- if (*name == '\0' ||
- (name[0] == 'g' && name[1] == 'c' && name[2] == 'c') ||
- (name[0] == 'c' && name[1] == 'c' && name[2] == '.')) {
- return false;
- }
- return true;
-#endif
-}
-
-extern void DEBUG_LoadSymbols( const char *name )
-{
- bfd* abfd;
- char **matching;
-
- bfd_init();
- abfd = bfd_openr(name, "default");
- if (abfd == NULL) {
- barf("can't open executable %s to get symbol table", name);
- }
- if (!bfd_check_format_matches (abfd, bfd_object, &matching)) {
- barf("mismatch");
- }
-
- {
- long storage_needed;
- asymbol **symbol_table;
- long number_of_symbols;
- long num_real_syms = 0;
- long i;
-
- storage_needed = bfd_get_symtab_upper_bound (abfd);
-
- if (storage_needed < 0) {
- barf("can't read symbol table");
- }
- symbol_table = (asymbol **) stgMallocBytes(storage_needed,"DEBUG_LoadSymbols");
-
- number_of_symbols = bfd_canonicalize_symtab (abfd, symbol_table);
-
- if (number_of_symbols < 0) {
- barf("can't canonicalise symbol table");
- }
-
- if (add_to_fname_table == NULL)
- add_to_fname_table = allocHashTable();
-
- for( i = 0; i != number_of_symbols; ++i ) {
- symbol_info info;
- bfd_get_symbol_info(abfd,symbol_table[i],&info);
- if (isReal(info.type, info.name)) {
- insertHashTable(add_to_fname_table,
- info.value, (void*)info.name);
- num_real_syms += 1;
- }
- }
-
- IF_DEBUG(interpreter,
- debugBelch("Loaded %ld symbols. Of which %ld are real symbols\n",
- number_of_symbols, num_real_syms)
- );
-
- stgFree(symbol_table);
- }
-}
-
-#else /* USING_LIBBFD */
-
-extern void DEBUG_LoadSymbols( const char *name STG_UNUSED )
-{
- /* nothing, yet */
-}
-
-#endif /* USING_LIBBFD */
-
void findPtr(P_ p, int); /* keep gcc -Wall happy */
int searched = 0;
@@ -1080,6 +964,31 @@ void printObj( StgClosure *obj )
#endif /* DEBUG */
+/* --------------------------------------------------------------------------
+ * Simple lookup table
+ * address -> function name
+ * ------------------------------------------------------------------------*/
+
+static HashTable * add_to_fname_table = NULL;
+
+void registerDebugSymbol( const DebugSymbolEntry entries[], int len ) {
+ if (add_to_fname_table == NULL) {
+ add_to_fname_table = allocHashTable();
+ }
+
+ for (int i = 0; i < len; ++i) {
+ insertHashTable(add_to_fname_table, (StgWord)entries[i].addr, entries[i].sym);
+ }
+}
+
+const char *lookupDebugSymbol( void *addr )
+{
+ if (add_to_fname_table == NULL)
+ return NULL;
+
+ return lookupHashTable(add_to_fname_table, (StgWord)addr);
+}
+
/* -----------------------------------------------------------------------------
Closure types
=====================================
rts/Printer.h
=====================================
@@ -30,11 +30,9 @@ extern void printStaticObjects ( StgClosure *obj );
extern void printWeakLists ( void );
extern void printLargeAndPinnedObjects ( void );
-extern void DEBUG_LoadSymbols( const char *name );
-
-extern const char *lookupGHCName( void *addr );
-
extern const char *what_next_strs[];
#endif
+extern const char *lookupDebugSymbol( void *addr );
+
#include "EndPrivate.h"
=====================================
rts/RtsStartup.c
=====================================
@@ -15,7 +15,6 @@
#include "RtsFlags.h"
#include "RtsUtils.h"
#include "Prelude.h"
-#include "Printer.h" /* DEBUG_LoadSymbols */
#include "Schedule.h" /* initScheduler */
#include "Stats.h" /* initStats */
#include "STM.h" /* initSTM */
@@ -326,11 +325,6 @@ hs_init_ghc(int *argc, char **argv[], RtsConfig rts_config)
} else {
setFullProgArgv(*argc,*argv);
setupRtsFlags(argc, *argv, rts_config);
-
-#if defined(DEBUG)
- /* load debugging symbols for current binary */
- DEBUG_LoadSymbols((*argv)[0]);
-#endif /* DEBUG */
}
/* Based on the RTS flags, decide which I/O manager to use. */
=====================================
rts/configure.ac
=====================================
@@ -171,8 +171,6 @@ AS_IF(
[test "$CABAL_FLAG_libm" = 1],
[AC_DEFINE([HAVE_LIBM], [1], [Define to 1 if you need to link with libm])])
-AS_IF([test "$CABAL_FLAG_libbfd" = 1], [FP_WHEN_ENABLED_BFD])
-
dnl ################################################################
dnl Check for libraries
dnl ################################################################
=====================================
rts/include/Rts.h
=====================================
@@ -283,6 +283,7 @@ void _warnFail(const char *filename, unsigned int linenum);
#include "rts/StaticPtrTable.h"
#include "rts/Libdw.h"
#include "rts/LibdwPool.h"
+#include "rts/Debug.h"
/* Misc stuff without a home */
DLL_IMPORT_RTS extern char **prog_argv; /* so we can get at these from Haskell */
=====================================
rts/include/rts/Config.h
=====================================
@@ -19,13 +19,6 @@
#error TICKY_TICKY is incompatible with THREADED_RTS
#endif
-/*
- * Whether the runtime system will use libbfd for debugging purposes.
- */
-#if defined(DEBUG) && defined(HAVE_BFD_H) && defined(HAVE_LIBBFD) && !defined(_WIN32)
-#define USING_LIBBFD 1
-#endif
-
/*
* We previously only offer the eventlog in a subset of RTS ways; we now
* enable it unconditionally to simplify packaging. See #18948.
@@ -101,4 +94,3 @@ code.
#else
#define CACHELINE_SIZE 64
#endif
-
=====================================
rts/include/rts/Debug.h
=====================================
@@ -0,0 +1,18 @@
+/* -----------------------------------------------------------------------------
+ *
+ * (c) The GHC Team, 2017-2025
+ *
+ * Debug API
+ *
+ * Do not #include this file directly: #include "Rts.h" instead.
+ *
+ * To understand the structure of the RTS headers, see the wiki:
+ * https://gitlab.haskell.org/ghc/ghc/wikis/commentary/source-tree/includes
+ *
+ * -------------------------------------------------------------------------- */
+
+#pragma once
+
+typedef struct { void *addr; const char *sym; } DebugSymbolEntry;
+
+void registerDebugSymbol( const DebugSymbolEntry entries[], int len );
=====================================
rts/rts.cabal
=====================================
@@ -46,9 +46,6 @@ flag libffi-adjustors
flag need-pthread
default: False
manual: True
-flag libbfd
- default: False
- manual: True
flag need-atomic
default: False
manual: True
@@ -250,9 +247,6 @@ library
if flag(need-atomic)
-- for sub-word-sized atomic operations (#19119)
extra-libraries: atomic
- if flag(libbfd)
- -- for debugging
- extra-libraries: bfd iberty
if flag(libdw)
-- for backtraces
extra-libraries: elf dw
@@ -286,6 +280,7 @@ library
rts/Bytecodes.h
rts/Config.h
rts/Constants.h
+ rts/Debug.h
rts/EventLogFormat.h
rts/EventLogWriter.h
rts/FileLock.h
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2924dad40c01ccde7278a75207ca7d…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2924dad40c01ccde7278a75207ca7d…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/T21730-import] 2 commits: Rename implicit => generated
by Brandon Chinn (@brandonchinn178) 15 Aug '25
by Brandon Chinn (@brandonchinn178) 15 Aug '25
15 Aug '25
Brandon Chinn pushed to branch wip/T21730-import at Glasgow Haskell Compiler / GHC
Commits:
4ac945d9 by Brandon Chinn at 2025-08-15T20:25:18-07:00
Rename implicit => generated
- - - - -
17b879b3 by Brandon Chinn at 2025-08-15T20:52:09-07:00
Generated imports beat user imports for minimal imports
- - - - -
8 changed files:
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Types/Name/Reader.hs
- ghc/GHCi/UI.hs
- testsuite/tests/parser/should_compile/T7476/T7476.stdout
Changes:
=====================================
compiler/GHC/Driver/Backpack.hs
=====================================
@@ -878,14 +878,14 @@ hsModuleToModSummary home_keys pn hsc_src modname
let (src_idecls, ord_idecls) = partition ((== IsBoot) . ideclSource . unLoc) imps
implicit_prelude = xopt LangExt.ImplicitPrelude dflags
- implicit_imports = mkPrelImports modname implicit_prelude imps
+ generated_imports = mkPrelImports modname implicit_prelude imps
rn_pkg_qual = renameRawPkgQual (hsc_unit_env hsc_env) modname
convImport (L _ i) = (convImportLevel (ideclLevelSpec i), rn_pkg_qual (ideclPkgQual i), reLoc $ ideclName i)
extra_sig_imports <- liftIO $ findExtraSigImports hsc_env hsc_src modname
- let normal_imports = map convImport (implicit_imports ++ ord_idecls)
+ let normal_imports = map convImport (generated_imports ++ ord_idecls)
(implicit_sigs, inst_deps) <- liftIO $ implicitRequirementsShallow hsc_env normal_imports
-- So that Finder can find it, even though it doesn't exist...
=====================================
compiler/GHC/Hs/ImpExp.hs
=====================================
@@ -80,16 +80,18 @@ type instance XCImportDecl GhcTc = DataConCantHappen
data XImportDeclPass = XImportDeclPass
{ ideclAnn :: EpAnn EpAnnImportDecl
, ideclSourceText :: SourceText -- Note [Pragma source text] in "GHC.Types.SourceText"
- , ideclImplicit :: Bool -- ^ See Note [Implicit imports]
+ , ideclGenerated :: Bool -- ^ See Note [Generated imports]
}
deriving (Data)
-{- Note [Implicit imports]
-~~~~~~~~~~~~~~~~~~~~~~~~~~
+{- Note [Generated imports]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~
GHC generates an `ImportDecl` to represent the invisible `import Prelude`
that appears in any file that omits `import Prelude`, setting
this field to indicate that the import doesn't appear in the
-original source. True => implicit import (of Prelude)
+original source.
+
+Plugins may also introduce generated imports.
-}
type instance XXImportDecl (GhcPass _) = DataConCantHappen
@@ -165,8 +167,8 @@ instance (OutputableBndrId p
where
pp_implicit ext =
let implicit = case ghcPass @p of
- GhcPs | XImportDeclPass { ideclImplicit = implicit } <- ext -> implicit
- GhcRn | XImportDeclPass { ideclImplicit = implicit } <- ext -> implicit
+ GhcPs | XImportDeclPass { ideclGenerated = implicit } <- ext -> implicit
+ GhcRn | XImportDeclPass { ideclGenerated = implicit } <- ext -> implicit
GhcTc -> dataConCantHappen ext
in if implicit then text "(implicit)"
else empty
=====================================
compiler/GHC/Iface/Ext/Ast.hs
=====================================
@@ -348,7 +348,7 @@ enrichHie ts (hsGrp, imports, exports, docs, modName) ev_bs insts tcs tte =
modName <- toHie (IEC Export <$> modName)
tasts <- toHie $ fmap (BC RegularBind ModuleScope) ts
rasts <- processGrp hsGrp
- imps <- toHie $ filter (not . ideclImplicit . ideclExt . unLoc) imports
+ imps <- toHie $ filter (not . ideclGenerated . ideclExt . unLoc) imports
exps <- toHie $ fmap (map $ IEC Export . fst) exports
docs <- toHie docs
-- Add Instance bindings
=====================================
compiler/GHC/Parser/Header.hs
=====================================
@@ -100,12 +100,12 @@ getImports popts implicit_prelude buf filename source_filename = do
mod = mb_mod `orElse` L (noAnnSrcSpan main_loc) mAIN_NAME
(src_idecls, ord_idecls) = partition ((== IsBoot) . ideclSource . unLoc) imps
- implicit_imports = mkPrelImports (unLoc mod) implicit_prelude imps
+ generated_imports = mkPrelImports (unLoc mod) implicit_prelude imps
convImport (L _ (i :: ImportDecl GhcPs)) = (convImportLevel (ideclLevelSpec i), ideclPkgQual i, reLoc $ ideclName i)
convImport_src (L _ (i :: ImportDecl GhcPs)) = (reLoc $ ideclName i)
in
return (map convImport_src src_idecls
- , map convImport (implicit_imports ++ ord_idecls)
+ , map convImport (generated_imports ++ ord_idecls)
, reLoc mod)
@@ -146,7 +146,7 @@ mkPrelImports this_mod implicit_prelude import_decls
= L loc $ ImportDecl { ideclExt = XImportDeclPass
{ ideclAnn = noAnn
, ideclSourceText = NoSourceText
- , ideclImplicit = True -- Implicit!
+ , ideclGenerated = True -- Generated!
},
ideclName = L loc pRELUDE_NAME,
ideclPkgQual = NoRawPkgQual,
=====================================
compiler/GHC/Rename/Names.hs
=====================================
@@ -317,7 +317,7 @@ rnImportDecl this_mod
, ideclSafe = mod_safe
, ideclLevelSpec = import_level
, ideclQualified = qual_style
- , ideclExt = XImportDeclPass { ideclImplicit = implicit }
+ , ideclExt = XImportDeclPass { ideclGenerated = implicit }
, ideclAs = as_mod, ideclImportList = imp_details }), import_reason)
= setSrcSpanA loc $ do
@@ -1922,25 +1922,27 @@ type ImportDeclUsage
warnUnusedImportDecls :: TcGblEnv -> HscSource -> RnM ()
warnUnusedImportDecls gbl_env hsc_src
= do { uses <- readMutVar (tcg_used_gres gbl_env)
- ; let user_imports = filterOut
- (ideclImplicit . ideclExt . unLoc)
- (tcg_rn_imports gbl_env)
- -- This whole function deals only with *user* imports
- -- both for warning about unnecessary ones, and for
- -- deciding the minimal ones
+ ; let imports = tcg_rn_imports gbl_env
rdr_env = tcg_rdr_env gbl_env
- ; let usage :: [ImportDeclUsage]
- usage = findImportUsage user_imports uses
+ -- We should only warn for unnecessary *user* imports, but deciding
+ -- minimal imports should take generated imports into account
+ ; let usageUserImports = findImportUsage (excludeGenerated imports) uses
+ usageAllImports = findImportUsage imports uses
; traceRn "warnUnusedImportDecls" $
(vcat [ text "Uses:" <+> ppr uses
- , text "Import usage" <+> ppr usage])
+ , text "Usage all user imports: " <+> ppr usageUserImports
+ , text "Usage all imports: " <+> ppr usageAllImports])
- ; mapM_ (warnUnusedImport rdr_env) usage
+ ; mapM_ (warnUnusedImport rdr_env) usageUserImports
; whenGOptM Opt_D_dump_minimal_imports $
- printMinimalImports hsc_src usage }
+ printMinimalImports hsc_src usageAllImports }
+
+-- | Exclude generated imports
+excludeGenerated :: [LImportDecl GhcRn] -> [LImportDecl GhcRn]
+excludeGenerated = filterOut (ideclGenerated . ideclExt . unLoc)
findImportUsage :: [LImportDecl GhcRn]
-> [GlobalRdrElt]
@@ -2208,8 +2210,10 @@ x,y to avoid name-shadowing warnings. Example (#9061)
Note [Printing minimal imports]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-To print the minimal imports we walk over the user-supplied import
-decls, and simply trim their import lists. NB that
+To print the minimal imports we walk over all import decls (both user-supplied
+and generated), trim their import lists, then filter out generated decls.
+
+NB that
* We do *not* change the 'qualified' or 'as' parts!
@@ -2301,7 +2305,7 @@ classifyGREs = partition (not . isRecFldGRE)
printMinimalImports :: HscSource -> [ImportDeclUsage] -> RnM ()
-- See Note [Printing minimal imports]
printMinimalImports hsc_src imports_w_usage
- = do { imports' <- getMinimalImports imports_w_usage
+ = do { imports' <- excludeGenerated <$> getMinimalImports imports_w_usage
; this_mod <- getModule
; dflags <- getDynFlags
; liftIO $ withFile (mkFilename dflags this_mod) WriteMode $ \h ->
=====================================
compiler/GHC/Types/Name/Reader.hs
=====================================
@@ -2041,10 +2041,13 @@ bestImport iss = NE.head $ NE.sortBy best iss
-- Less means better
-- Unqualified always wins over qualified; then
-- import-all wins over import-some; then
+ -- generated wins over user-specified; then
-- earlier declaration wins over later
best (ImpSpec { is_item = item1, is_decl = d1 })
(ImpSpec { is_item = item2, is_decl = d2 })
- = (is_qual d1 `compare` is_qual d2) S.<> best_item item1 item2 S.<>
+ = (is_qual d1 `compare` is_qual d2) S.<>
+ best_item item1 item2 S.<>
+ compareGenerated (is_dloc d1) (is_dloc d2) S.<>
SrcLoc.leftmost_smallest (is_dloc d1) (is_dloc d2)
best_item :: ImpItemSpec -> ImpItemSpec -> Ordering
@@ -2055,6 +2058,11 @@ bestImport iss = NE.head $ NE.sortBy best iss
(ImpSome { is_explicit = e2 }) = e1 `compare` e2
-- False < True, so if e1 is explicit and e2 is not, we get GT
+ compareGenerated UnhelpfulSpan{} UnhelpfulSpan{} = EQ
+ compareGenerated UnhelpfulSpan{} RealSrcSpan{} = LT
+ compareGenerated RealSrcSpan{} UnhelpfulSpan{} = GT
+ compareGenerated RealSrcSpan{} RealSrcSpan{} = EQ
+
{- Note [Choosing the best import declaration]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
When reporting unused import declarations we use the following rules.
=====================================
ghc/GHCi/UI.hs
=====================================
@@ -527,7 +527,7 @@ interactiveUI config srcs maybe_exprs = do
let prelude_import =
case simpleImportDecl preludeModuleName of
-- Set to True because Prelude is implicitly imported.
- impDecl@ImportDecl{ideclExt=ext} -> impDecl{ideclExt = ext{ideclImplicit=True}}
+ impDecl@ImportDecl{ideclExt=ext} -> impDecl{ideclExt = ext{ideclGenerated=True}}
empty_cache <- liftIO newIfaceCache
startGHCi (runGHCi srcs maybe_exprs)
GHCiState{ progname = default_progname,
=====================================
testsuite/tests/parser/should_compile/T7476/T7476.stdout
=====================================
@@ -1 +1 @@
-import Control.Applicative ( Applicative(pure), (<**>) )
+import Control.Applicative ( (<**>) )
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bc29a798654f3452a23ce5ea019b88…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bc29a798654f3452a23ce5ea019b88…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

15 Aug '25
Bodigrim pushed to branch wip/warning-for-last-and-init at Glasgow Haskell Compiler / GHC
Commits:
510f8466 by Andrew Lelechenko at 2025-08-16T00:33:37+01:00
Revert ghc-boot-th
- - - - -
1 changed file:
- libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs
Changes:
=====================================
libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs
=====================================
@@ -1,5 +1,6 @@
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE LambdaCase #-}
+{-# OPTIONS_GHC -Wno-x-partial #-}
-- | contains a prettyprinter for the
-- Template Haskell datatypes
@@ -13,7 +14,7 @@ import GHC.Boot.TH.PprLib
import GHC.Boot.TH.Syntax
import Data.Word ( Word8 )
import Data.Char ( toLower, chr )
-import Data.List ( intersperse, unsnoc )
+import Data.List ( intersperse )
import GHC.Show ( showMultiLineString )
import GHC.Lexeme( isVarSymChar )
import Data.Ratio ( numerator, denominator )
@@ -214,10 +215,9 @@ pprExp i (MDoE m ss_) = parensIf (i > noPrec) $
pprStms [s] = ppr s
pprStms ss = braces (semiSep ss)
+pprExp _ (CompE []) = text "<<Empty CompExp>>"
-- This will probably break with fixity declarations - would need a ';'
-pprExp _ (CompE ss) = case unsnoc ss of
- Nothing -> text "<<Empty CompExp>>"
- Just (ss', s) ->
+pprExp _ (CompE ss) =
if null ss'
-- If there are no statements in a list comprehension besides the last
-- one, we simply treat it like a normal list.
@@ -226,6 +226,8 @@ pprExp _ (CompE ss) = case unsnoc ss of
<+> bar
<+> commaSep ss'
<> text "]"
+ where s = last ss
+ ss' = init ss
pprExp _ (ArithSeqE d) = ppr d
pprExp _ (ListE es) = brackets (commaSep es)
pprExp i (SigE e t) = parensIf (i > noPrec) $ pprExp sigPrec e
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/510f84664e4c9885eca683338ea7f72…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/510f84664e4c9885eca683338ea7f72…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Ben Gamari deleted branch wip/backports-9.14 at Glasgow Haskell Compiler / GHC
--
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][ghc-9.14] 28 commits: Bump time submodule to 1.15
by Ben Gamari (@bgamari) 15 Aug '25
by Ben Gamari (@bgamari) 15 Aug '25
15 Aug '25
Ben Gamari pushed to branch ghc-9.14 at Glasgow Haskell Compiler / GHC
Commits:
9efc1c85 by Ben Gamari at 2025-08-12T12:20:58-04:00
Bump time submodule to 1.15
Also required bumps of Cabal, directory, and hpc.
(cherry picked from commit 0434af813cd5aa629ef7566cd267d7cdefa42114)
- - - - -
cbfee32f by Andrew Lelechenko at 2025-08-12T12:27:19-04:00
hadrian: bump Stackage snapshot to LTS 24.2 / GHC 9.10.2
In line with #25693 we should use GHC 9.10 as a boot compiler,
while Hadrian stack.yaml was stuck on GHC 9.6.
(cherry picked from commit 57d3b4a82e97f379cc8f41d61675d8c3904f7572)
- - - - -
ad5ef2b6 by Andrew Lelechenko at 2025-08-12T12:27:51-04:00
Bump submodule text to 2.1.3
(cherry picked from commit 77df0ded670cffcc1e9bfd8d30f0bf0c0e54b3f7)
- - - - -
bbfead6c by Andreas Klebinger at 2025-08-12T12:29:01-04:00
rts: Support COFF BigObj files in archives.
(cherry picked from commit 01136779b1d4c1576c925ef673f55c81c45d8551)
- - - - -
7fb21569 by fendor at 2025-08-12T12:32:21-04:00
Revert "base: Expose Backtraces constructor and fields"
This reverts commit 17db44c5b32fff82ea988fa4f1a233d1a27bdf57.
(cherry picked from commit 4f6bc9cf2a5569e8ac3303a79f8a88fb23e2578b)
- - - - -
13f32328 by Simon Peyton Jones at 2025-08-12T12:33:03-04:00
In TcSShortCut, typechecker plugins should get empty Givens
Solving in TcShortCut mode means /ignoring the Givens/. So we
should not pass them to typechecker plugins!
Fixes #26258.
This is a fixup to the earlier MR:
commit 1bd12371feacc52394a0e660ef9349f9e8ee1c06
Author: Simon Peyton Jones <simon.peytonjones(a)gmail.com>
Date: Mon Jul 21 10:04:49 2025 +0100
Improve treatment of SPECIALISE pragmas -- again!
(cherry picked from commit 2860a9a5d657eacd711a7df4a231dc9fe81402c2)
- - - - -
712da356 by Sylvain Henry at 2025-08-12T12:33:43-04:00
STM: don't create a transaction in the rhs of catchRetry# (#26028)
We don't need to create a transaction for the rhs of (catchRetry#)
because contrary to the lhs we don't need to abort it on retry. Moreover
it is particularly harmful if we have code such as (#26028):
let cN = readTVar vN >> retry
tree = c1 `orElse` (c2 `orElse` (c3 `orElse` ...))
atomically tree
Because it will stack transactions for the rhss and the read-sets of all
the transactions will be iteratively merged in O(n^2) after the
execution of the most nested retry.
(cherry picked from commit 0a5836891ca29836a24c306d2a364c2e4b5377fd)
- - - - -
a52e0d45 by Zubin Duggal at 2025-08-12T12:33:54-04:00
haddock: Don't warn about missing link destinations for derived names.
Fixes #26114
(cherry picked from commit 5dabc718a04bfc4d277c5ff7f815ee3d6b9670cb)
- - - - -
9d73a535 by ARATA Mizuki at 2025-08-12T12:34:35-04:00
x86 NCG: Better lowering for shuffleFloatX4# and shuffleDoubleX2#
The new implementation
* make use of specialized instructions like (V)UNPCK{L,H}{PS,PD}, and
* do not require -mavx.
Close #26096
Co-authored-by: sheaf <sam.derbyshire(a)gmail.com>
(cherry picked from commit 7ee22fd53bea1c69780613c339feee9ae75525b2)
- - - - -
86a6ca1e by Duncan Coutts at 2025-08-12T12:34:59-04:00
base: Deprecate GHC.Weak.Finalize.runFinalizerBatch
https://github.com/haskell/core-libraries-committee/issues/342
(cherry picked from commit 360fa82cc0e06163c7d712a22e7a33cf30e6b852)
- - - - -
3be62b10 by Zubin Duggal at 2025-08-12T12:35:18-04:00
fetch_gitlab: Ensure we copy users_guide.pdf and Haddock.pdf to the release docs directory
Fixes #24093
(cherry picked from commit 9fa590a6e27545995cdcf419ed7a6504e6668b18)
- - - - -
3c02ae3c by Teo Camarasu at 2025-08-12T12:35:37-04:00
rts/nonmovingGC: remove n_free
We remove the nonmovingHeap.n_free variable.
We wanted this to track the length of nonmovingHeap.free.
But this isn't possible to do atomically.
When this isn't accurate we can get a segfault by going past the end of
the list.
Instead, we just count the length of the list when we grab it in
nonmovingPruneFreeSegment.
Resolves #26186
(cherry picked from commit 45efaf71d97355f76fe0db5af2fc5b4b67fddf47)
- - - - -
d96470b1 by Andreas Klebinger at 2025-08-12T12:35:58-04:00
Disable -fprof-late-overloaded-calls for join points.
Currently GHC considers cost centres as destructive to
join contexts. Or in other words this is not considered valid:
join f x = ...
in
... -> scc<tick> jmp
This makes the functionality of `-fprof-late-overloaded-calls` not feasible
for join points in general. We used to try to work around this by putting the
ticks on the rhs of the join point rather than around the jump. However beyond
the loss of accuracy this was broken for recursive join points as we ended up
with something like:
rec-join f x = scc<tick> ... jmp f x
Which similarly is not valid as the tick once again destroys the tail call.
One might think we could limit ourselves to non-recursive tail calls and do
something clever like:
join f x = scc<tick> ...
in ... jmp f x
And sometimes this works! But sometimes the full rhs would look something like:
join g x = ....
join f x = scc<tick> ... -> jmp g x
Which, would again no longer be valid. I believe in the long run we can make
cost centre ticks non-destructive to join points. Or we could keep track of
where we are/are not allowed to insert a cost centre. But in the short term I will
simply disable the annotation of join calls under this flag.
(cherry picked from commit 7da86e165612721c4e09f772a3fdaffc733e9293)
- - - - -
99e4eb40 by Rodrigo Mesquita at 2025-08-12T12:36:10-04:00
base: Export displayExceptionWithInfo
This function should be exposed from base following CLC#285
Approved change in CLC#344
Fixes #26058
(cherry picked from commit ef03d8b8851a1cace5f792fe5a91b6b227198aa2)
- - - - -
81de45dc by Sebastian Graf at 2025-08-12T12:36:29-04:00
CprAnal: Detect recursive newtypes (#25944)
While `cprTransformDataConWork` handles recursive data con workers, it
did not detect the case when a newtype is responsible for the recursion.
This is now detected in the `Cast` case of `cprAnal`.
The same reproducer made it clear that `isRecDataCon` lacked congruent
handling for `AppTy` and `CastTy`, now fixed.
Furthermore, the new repro case T25944 triggered this bug via an
infinite loop in `cprFix`, caused by the infelicity in `isRecDataCon`.
While it should be much less likely to trigger such an infinite loop now
that `isRecDataCon` has been fixed, I made sure to abort the loop after
10 iterations and emitting a warning instead.
Fixes #25944.
(cherry picked from commit 4bc78496406f7469640faaa46e2f311c05760124)
- - - - -
3d821e16 by Ben Gamari at 2025-08-12T12:36:43-04:00
configure: Allow override of CrossCompiling
As noted in #26236, the current inference logic is a bit simplistic. In
particular, there are many cases (e.g. building for a new libc) where
the target and host triples may differ yet we are still able to run the
produced artifacts as native code.
Closes #26236.
(cherry picked from commit 81577fe7c1913c53608bf03e48f84507be904620)
- - - - -
0061a178 by Matthew Pickering at 2025-08-12T12:37:37-04:00
level imports: Check the level of exported identifiers
The level imports specification states that exported identifiers have to
be at level 0. This patch adds the requird level checks that all
explicitly mentioned identifiers occur at level 0.
For implicit export specifications (T(..) and module B), only level 0
identifiers are selected for re-export.
ghc-proposal: https://github.com/ghc-proposals/ghc-proposals/pull/705
Fixes #26090
(cherry picked from commit 246b785367d8bf0059a641306fe662fecc3342af)
- - - - -
6576e711 by Ben Gamari at 2025-08-12T12:45:20-04:00
Kill IOPort#
This type is unnecessary, having been superceded by `MVar` and a rework
of WinIO's blocking logic.
See #20947.
See https://github.com/haskell/core-libraries-committee/issues/213.
(cherry picked from commit 34fc50c13b47842e0d1f9879285a68b06215c16b)
- - - - -
bf3a76e1 by Zubin Duggal at 2025-08-12T12:45:20-04:00
compiler: Export a version of `newNameCache` that is not prone to footguns.
`newNameCache` must be initialized with both a non-"reserved" unique tag, as well
as a list of known key names. Failing to do so results in hard to debug unique conflicts.
It is difficult for API users to tell which unique tags are safe to use. So instead of leaving
this up to the user to decide, we now export a version of `newNameCache` which uses a guaranteed
non-reserved unique tag. In fact, this is now the way the unique tag is initialized for all invocations
of the compiler.
The original version of `newNameCache` is now exported as `newNameCache'` for advanced users.
We also deprecate `initNameCache` as it is also prone to footguns and is completely subsumed in
functionality by `newNameCache` and `newNameCache'`.
Fixes #26135 and #26055
(cherry picked from commit bcdec6572a098f984efeb85bf45ff7c0b5d717af)
- - - - -
d832844a by Ben Gamari at 2025-08-12T12:45:20-04:00
testsuite/recomp015: Ignore stderr
This is necessary since ld.bfd complains
that we don't have a .note.GNU-stack section,
potentially resulting in an executable stack.
(cherry picked from commit 637bb53825b9414f7c7dbed4cc3e5cc1ed4d2329)
- - - - -
30ad189d by fendor at 2025-08-14T22:27:38-04:00
Bump GHC on darwin CI to 9.10.1
(cherry picked from commit 358bc4fc8324a0685f336142d0d608cbd51d54f9)
- - - - -
15d7ef64 by Zubin Duggal at 2025-08-14T22:27:38-04:00
ci: upgrade bootstrap compiler on windows to 9.10.1
(cherry picked from commit c8d76a2994b8620c54adc2069f4728135d6b5059)
- - - - -
0ad30b89 by Ben Gamari at 2025-08-14T22:27:38-04:00
Accept performance shifts
Metric Increase:
WWRec
- - - - -
bdf66b51 by Simon Peyton Jones at 2025-08-15T06:26:00-04:00
Treat tuple dictionaries uniformly; don't unbox them
See `Note [Do not unbox class dictionaries]` in DmdAnal.hs,
sep (DNB1).
This MR reverses the plan in #23398, which suggested a special case to
unbox tuple dictionaries in worker/wrapper. But:
- This was the cause of a pile of complexity in the specialiser (#26158)
- Even with that complexity, specialision was still bad, very bad
See https://gitlab.haskell.org/ghc/ghc/-/issues/19747#note_626297
And it's entirely unnecessary! Specialision works fine without
unboxing tuple dictionaries.
(cherry picked from commit ca7a9d421f602355822b674dd01fb48cd6291108)
- - - - -
5194ccbc by Simon Peyton Jones at 2025-08-15T09:07:30-04:00
Make injecting implicit bindings into its own pass
Previously we were injecting "impliicit bindings" (data constructor
worker and wrappers etc)
- both at the end of CoreTidy,
- and at the start of CorePrep
This is unpleasant and confusing. This patch puts it it its own pass,
addImplicitBinds, which runs between the two.
The function `GHC.CoreToStg.AddImplicitBinds.addImplicitBinds` now takes /all/
TyCons, not just the ones for algebraic data types. That change ripples
through to
- corePrepPgm
- doCodeGen
- byteCodeGen
All take [TyCon] which includes all TyCons
(cherry picked from commit fd811ded65bb9b19571ba525fb5eaf8f23a4533d)
- - - - -
779a7bc6 by Simon Peyton Jones at 2025-08-15T09:07:33-04:00
Implement unary classes
The big change is described exhaustively in
Note [Unary class magic] in GHC.Core.TyCon
Other changes
* We never unbox class dictionaries in worker/wrapper. This has been true for some
time now, but the logic is now centralised in functions in
GHC.Core.Opt.WorkWrap.Utils, namely `canUnboxTyCon`, and `canUnboxArg`
See Note [Do not unbox class dictionaries] in GHC.Core.Opt.WorkWrap.Utils.
* Refactored the `notWorthFloating` logic in GHc.Core.Opt.SetLevels.
I can't remember if I actually changed any behaviour here, but if so it's
only in a corner cases.
* Fixed a bug in `GHC.Core.TyCon.isEnumerationTyCon`, which was wrongly returning
True for (##).
* Remove redundant Role argument to `liftCoSubstWithEx`. It was always
Representational.
* I refactored evidence generation in the constraint solver:
* Made GHC.Tc.Types.Evidence contain better abstactions for evidence
generation.
* I deleted the file `GHC.Tc.Types.EvTerm` and merged its (small) contents
elsewhere. It wasn't paying its way.
* Made evidence for implicit parameters go via a proper abstraction.
* Fix inlineBoringOk; see (IB6) in Note [inlineBoringOk]
This fixes a slowdown in `countdownEffectfulDynLocal`
in the `effectful` library.
Smaller things
* Rename `isDataTyCon` to `isBoxedDataTyCon`.
* GHC.Core.Corecion.liftCoSubstWithEx was only called with Representational role,
so I baked that into the function and removed the argument.
* Get rid of `GHC.Core.TyCon.tyConSingleAlgDataCon_maybe` in favour of calling
`not isNewTyCon` at the call sites; more explicit.
* Refatored `GHC.Core.TyCon.isInjectiveTyCon`; but I don't think I changed its
behaviour
* Moved `decomposeIPPred` to GHC.Core.Predicate
Compile time performance changes:
geo. mean +0.1%
minimum -6.8%
maximum +14.4%
The +14% one is in T21839c, where it seems that a bit more inlining
is taking place. That seems acceptable; and the average change is small
Metric Decrease:
LargeRecord
T12227
T12707
T16577
T21839r
T5642
Metric Increase:
T15164
T21839c
T3294
T5321FD
T5321Fun
WWRec
(cherry picked from commit 9bd7fcc518111a1549c98720c222cdbabd32ed46)
- - - - -
e09e1443 by Simon Peyton Jones at 2025-08-15T12:25:41-04:00
Fix a long-standing assertion error in normSplitTyConApp_maybe
(cherry picked from commit 60db2c66b870bac28615d272936bef6905befdbb)
- - - - -
7b814248 by Simon Peyton Jones at 2025-08-15T12:25:50-04:00
Add comment to coercion optimiser
(cherry picked from commit b2b95dce34ce7f6a8f0acdd637cbe2cafc56c922)
- - - - -
205 changed files:
- .gitlab/darwin/toolchain.nix
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/InfoTable.hs
- compiler/GHC/CmmToAsm/X86/CodeGen.hs
- compiler/GHC/CmmToAsm/X86/Instr.hs
- compiler/GHC/CmmToAsm/X86/Ppr.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/FamInstEnv.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/SetLevels.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Unfold.hs
- compiler/GHC/Core/Unfold/Make.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToStg.hs
- + compiler/GHC/CoreToStg/AddImplicitBinds.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Foreign/Call.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Tidy.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToJS/Prim.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/Instance/Family.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.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/EvTerm.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Types/Demand.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Make.hs
- compiler/GHC/Types/Name/Cache.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Types/RepType.hs
- compiler/GHC/Types/TyThing.hs
- compiler/ghc.cabal.in
- configure.ac
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/profiling.rst
- ghc/ghc-bin.cabal.in
- hadrian/stack.yaml
- hadrian/stack.yaml.lock
- libraries/Cabal
- libraries/base/base.cabal.in
- libraries/base/changelog.md
- libraries/base/src/Control/Exception.hs
- libraries/base/src/Control/Exception/Backtrace.hs
- libraries/base/src/GHC/Exts.hs
- − libraries/base/src/GHC/IOPort.hs
- libraries/base/src/GHC/Weak/Finalize.hs
- libraries/directory
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
- libraries/ghc-internal/ghc-internal.cabal.in
- libraries/ghc-internal/src/GHC/Internal/Event/Windows.hsc
- libraries/ghc-internal/src/GHC/Internal/Event/Windows/Thread.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs
- libraries/ghc-internal/src/GHC/Internal/Exts.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Buffer.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Windows/Handle.hsc
- − libraries/ghc-internal/src/GHC/Internal/IOPort.hs
- libraries/ghc-internal/src/GHC/Internal/Prim/PtrEq.hs
- libraries/ghc-prim/changelog.md
- libraries/hpc
- libraries/text
- libraries/time
- libraries/unix
- rts/Prelude.h
- rts/PrimOps.cmm
- rts/RaiseAsync.c
- rts/RtsSymbols.c
- rts/STM.c
- rts/external-symbols.list.in
- rts/include/stg/MiscClosures.h
- rts/include/stg/SMP.h
- rts/linker/LoadArchive.c
- rts/sm/NonMoving.c
- rts/sm/NonMoving.h
- rts/sm/NonMovingAllocate.c
- rts/sm/Sanity.c
- rts/win32/AsyncWinIO.c
- rts/win32/libHSghc-internal.def
- testsuite/tests/core-to-stg/T24124.stderr
- + testsuite/tests/cpranal/sigs/T25944.hs
- + testsuite/tests/cpranal/sigs/T25944.stderr
- testsuite/tests/cpranal/sigs/all.T
- testsuite/tests/deSugar/should_compile/T2431.stderr
- testsuite/tests/dmdanal/should_compile/T16029.stdout
- testsuite/tests/dmdanal/should_compile/T23398.hs
- testsuite/tests/dmdanal/should_compile/T23398.stderr
- testsuite/tests/dmdanal/sigs/T21119.stderr
- testsuite/tests/dmdanal/sigs/T21888.stderr
- testsuite/tests/driver/recomp015/all.T
- testsuite/tests/ghci.debugger/scripts/break011.stdout
- testsuite/tests/ghci.debugger/scripts/break024.stdout
- testsuite/tests/haddock/haddock_testsuite/Makefile
- + testsuite/tests/haddock/haddock_testsuite/T26114.hs
- + testsuite/tests/haddock/haddock_testsuite/T26114.stdout
- testsuite/tests/haddock/haddock_testsuite/all.T
- testsuite/tests/hiefile/should_run/TestUtils.hs
- testsuite/tests/indexed-types/should_compile/T2238.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
- 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/lib/stm/T26028.hs
- + testsuite/tests/lib/stm/T26028.stdout
- + testsuite/tests/lib/stm/all.T
- testsuite/tests/numeric/should_compile/T15547.stderr
- testsuite/tests/numeric/should_compile/T23907.stderr
- testsuite/tests/primops/should_run/UnliftedIOPort.hs
- testsuite/tests/primops/should_run/all.T
- testsuite/tests/roles/should_compile/Roles14.stderr
- testsuite/tests/roles/should_compile/Roles3.stderr
- testsuite/tests/roles/should_compile/Roles4.stderr
- testsuite/tests/simd/should_run/all.T
- + testsuite/tests/simd/should_run/doublex2_shuffle.hs
- + testsuite/tests/simd/should_run/doublex2_shuffle.stdout
- + testsuite/tests/simd/should_run/doublex2_shuffle_baseline.hs
- + testsuite/tests/simd/should_run/doublex2_shuffle_baseline.stdout
- + testsuite/tests/simd/should_run/floatx4_shuffle.hs
- + testsuite/tests/simd/should_run/floatx4_shuffle.stdout
- + testsuite/tests/simd/should_run/floatx4_shuffle_baseline.hs
- + testsuite/tests/simd/should_run/floatx4_shuffle_baseline.stdout
- testsuite/tests/simplCore/should_compile/DataToTagFamilyScrut.stderr
- testsuite/tests/simplCore/should_compile/T15205.stderr
- testsuite/tests/simplCore/should_compile/T17366.stderr
- testsuite/tests/simplCore/should_compile/T17966.stderr
- testsuite/tests/simplCore/should_compile/T22309.stderr
- testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr
- testsuite/tests/simplCore/should_compile/T23307.stderr
- testsuite/tests/simplCore/should_compile/T23307a.stderr
- testsuite/tests/simplCore/should_compile/T25389.stderr
- testsuite/tests/simplCore/should_compile/T25713.stderr
- testsuite/tests/simplCore/should_compile/T7360.stderr
- testsuite/tests/simplStg/should_compile/T15226b.stderr
- + testsuite/tests/splice-imports/DodgyLevelExport.hs
- + testsuite/tests/splice-imports/DodgyLevelExport.stderr
- + testsuite/tests/splice-imports/DodgyLevelExportA.hs
- + testsuite/tests/splice-imports/LevelImportExports.hs
- + testsuite/tests/splice-imports/LevelImportExports.stdout
- + testsuite/tests/splice-imports/LevelImportExportsA.hs
- testsuite/tests/splice-imports/Makefile
- + testsuite/tests/splice-imports/ModuleExport.hs
- + testsuite/tests/splice-imports/ModuleExport.stderr
- + testsuite/tests/splice-imports/ModuleExportA.hs
- + testsuite/tests/splice-imports/ModuleExportB.hs
- + testsuite/tests/splice-imports/T26090.hs
- + testsuite/tests/splice-imports/T26090.stderr
- + testsuite/tests/splice-imports/T26090A.hs
- testsuite/tests/splice-imports/all.T
- testsuite/tests/tcplugins/CtIdPlugin.hs
- testsuite/tests/typecheck/should_compile/Makefile
- testsuite/tests/typecheck/should_compile/T12763.stderr
- testsuite/tests/typecheck/should_compile/T14774.stdout
- testsuite/tests/typecheck/should_compile/T18406b.stderr
- testsuite/tests/typecheck/should_compile/T18529.stderr
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/unboxedsums/unpack_sums_7.stdout
- testsuite/tests/wasm/should_run/control-flow/LoadCmmGroup.hs
- testsuite/tests/wasm/should_run/control-flow/RunWasm.hs
- utils/genprimopcode/Main.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/33331570de1b79286218fef976bc6d…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/33331570de1b79286218fef976bc6d…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

15 Aug '25
Simon Peyton Jones pushed to branch wip/T23162-spj at Glasgow Haskell Compiler / GHC
Commits:
164590b5 by Simon Peyton Jones at 2025-08-16T00:09:40+01:00
Wibble Outputable
- - - - -
1 changed file:
- compiler/GHC/Utils/Outputable.hs
Changes:
=====================================
compiler/GHC/Utils/Outputable.hs
=====================================
@@ -528,19 +528,22 @@ pprDeeperList f ds
| null ds = f []
| otherwise = SDoc work
where
- work ctx@SDC{ sdocStyle=PprUser _ (PartWay {}) _ }
- = let -- Only do this depth-limitation in User style
- -- when PartWay is on. Why not for DefaultDepth?
- -- I have no idea; seems like a bug to me.
- go _ [] = []
- go i (d:ds) | i >= default_depth = [text "...."]
- | otherwise = d : go (i+1) ds
- in runSDoc (f (go 0 ds)) ctx
- where
- default_depth = sdocDefaultDepth ctx
+ -- Trim the list to the length of the remaining depth count
+ work ctx@SDC{ sdocStyle=PprUser _ depth _ }
+ | Just list_elts_to_print
+ <- case depth of
+ DefaultDepth -> Just (sdocDefaultDepth ctx)
+ PartWay n -> Just n
+ AllTheWay -> Nothing
+ = runSDoc (f (trim list_elts_to_print ds)) ctx
work other_ctx = runSDoc (f ds) other_ctx
+trim :: Int -> [SDoc] -> [SDoc]
+trim _ [] = []
+trim 0 _ = [text "...."]
+trim n (d:ds) = d : trim (n-1) ds
+
pprSetDepth :: Depth -> SDoc -> SDoc
pprSetDepth depth doc = SDoc $ \ctx ->
case ctx of
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/164590b57b9bd0ff7f18bb0bef2ed53…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/164590b57b9bd0ff7f18bb0bef2ed53…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Simon Peyton Jones pushed new branch wip/T25992a at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T25992a
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/warning-for-last-and-init] 33 commits: Extend record-selector usage ticking to all binds using a record field
by Bodigrim (@Bodigrim) 15 Aug '25
by Bodigrim (@Bodigrim) 15 Aug '25
15 Aug '25
Bodigrim pushed to branch wip/warning-for-last-and-init at Glasgow Haskell Compiler / GHC
Commits:
62899117 by Florian Ragwitz at 2025-08-13T21:01:34-04:00
Extend record-selector usage ticking to all binds using a record field
This extends the previous handling of ticking for RecordWildCards and
NamedFieldPuns to all var bindings that involve record selectors.
Note that certain patterns such as `Foo{foo = 42}` will currently not tick the
`foo` selector, as ticking is triggered by `HsVar`s.
Closes #26191.
- - - - -
b37b3af7 by Florian Ragwitz at 2025-08-13T21:01:34-04:00
Add release notes for 9.16.1 and move description of latest HPC changes there.
- - - - -
a5e4b7d9 by Ben Gamari at 2025-08-13T21:02:18-04:00
rts: Clarify rationale for undefined atomic wrappers
Since c06e3f46d24ef69f3a3d794f5f604cb8c2a40cbc the RTS has declared
various atomic operation wrappers defined by ghc-internal as undefined.
While the rationale for this isn't clear from the commit message, I
believe that this is necessary due to the unregisterised backend.
Specifically, the code generator will reference these symbols when
compiling RTS Cmm sources.
- - - - -
50842f83 by Andreas Klebinger at 2025-08-13T21:03:01-04:00
Make unexpected LLVM versions a warning rather than an error.
Typically a newer LLVM version *will* work so erroring out if
a user uses a newer LLVM version is too aggressive.
Fixes #25915
- - - - -
c91e2650 by fendor at 2025-08-13T21:03:43-04:00
Store `StackTrace` and `StackSnapshot` in `Backtraces`
Instead of decoding the stack traces when collecting the `Backtraces`,
defer this decoding until actually showing the `Backtraces`.
This allows users to customise how `Backtraces` are displayed by
using a custom implementation of `displayExceptionWithInfo`, overwriting
the default implementation for `Backtraces` (`displayBacktraces`).
- - - - -
dee28cdd by fendor at 2025-08-13T21:03:43-04:00
Allow users to customise the collection of exception annotations
Add a global `CollectExceptionAnnotationMechanism` which determines how
`ExceptionAnnotation`s are collected upon throwing an `Exception`.
This API is exposed via `ghc-experimental`.
By overriding how we collect `Backtraces`, we can control how the
`Backtraces` are displayed to the user by newtyping `Backtraces` and
giving a different instance for `ExceptionAnnotation`.
A concrete use-case for this feature is allowing us to experiment with
alternative stack decoders, without having to modify `base`, which take
additional information from the stack frames.
This commit does not modify how `Backtraces` are currently
collected or displayed.
- - - - -
66024722 by fendor at 2025-08-13T21:03:43-04:00
Expose Backtraces internals from ghc-experimental
Additionally, expose the same API `base:Control.Exception.Backtrace`
to make it easier to use as a drop-in replacement.
- - - - -
a766286f by Reed Mullanix at 2025-08-13T21:04:36-04:00
ghc-internal: Fix naturalAndNot for NB/NS case
When the first argument to `naturalAndNot` is larger than a `Word` and the second is `Word`-sized, `naturalAndNot` will truncate the
result:
```
>>> naturalAndNot ((2 ^ 65) .|. (2 ^ 3)) (2 ^ 3)
0
```
In contrast, `naturalAndNot` does not truncate when both arguments are larger than a `Word`, so this appears to be a bug.
Luckily, the fix is pretty easy: we just need to call `bigNatAndNotWord#` instead of truncating.
Fixes #26230
- - - - -
3506fa7d by Simon Hengel at 2025-08-13T21:05:18-04:00
Report -pgms as a deprecated flag
(instead of reporting an unspecific warning)
Before:
on the commandline: warning:
Object splitting was removed in GHC 8.8
After:
on the commandline: warning: [GHC-53692] [-Wdeprecated-flags]
-pgms is deprecated: Object splitting was removed in GHC 8.8
- - - - -
51c701fe by Zubin Duggal at 2025-08-13T21:06:00-04:00
testsuite: Be more permissive when filtering out GNU_PROPERTY_TYPE linker warnings
The warning text is slightly different with ld.bfd.
Fixes #26249
- - - - -
dfe6f464 by Simon Hengel at 2025-08-13T21:06:43-04:00
Refactoring: Don't misuse `MCDiagnostic` for lint messages
`MCDiagnostic` is meant to be used for compiler diagnostics.
Any code that creates `MCDiagnostic` directly, without going through
`GHC.Driver.Errors.printMessage`, side steps `-fdiagnostics-as-json`
(see e.g. !14475, !14492 !14548).
To avoid this in the future I want to control more narrowly who creates
`MCDiagnostic` (see #24113).
Some parts of the compiler use `MCDiagnostic` purely for formatting
purposes, without creating any real compiler diagnostics. This change
introduces a helper function, `formatDiagnostic`, that can be used in
such cases instead of constructing `MCDiagnostic`.
- - - - -
a8b2fbae by Teo Camarasu at 2025-08-13T21:07:24-04:00
rts: ensure MessageBlackHole.link is always a valid closure
We turn a MessageBlackHole into an StgInd in wakeBlockingQueue().
Therefore it's important that the link field, which becomes the
indirection field, always points to a valid closure.
It's unclear whether it's currently possible for the previous behaviour
to lead to a crash, but it's good to be consistent about this invariant nonetheless.
Co-authored-by: Andreas Klebinger <klebinger.andreas(a)gmx.at>
- - - - -
4021181e by Teo Camarasu at 2025-08-13T21:07:24-04:00
rts: spin if we see a WHITEHOLE in messageBlackHole
When a BLACKHOLE gets cancelled in raiseAsync, we indirect to a THUNK.
GC can then shortcut this, replacing our BLACKHOLE with a fresh THUNK.
This THUNK is not guaranteed to have a valid indirectee field.
If at the same time, a message intended for the previous BLACKHOLE is
processed and concurrently we BLACKHOLE the THUNK, thus temporarily
turning it into a WHITEHOLE, we can get a segfault, since we look at the
undefined indirectee field of the THUNK
The fix is simple: spin if we see a WHITEHOLE, and it will soon be
replaced with a valid BLACKHOLE.
Resolves #26205
- - - - -
1107af89 by Oleg Grenrus at 2025-08-13T21:08:06-04:00
Allow defining HasField instances for naughty fields
Resolves #26295
... as HasField solver doesn't solve for fields with "naughty"
selectors, we could as well allow defining HasField instances for these
fields.
- - - - -
020e7587 by Sylvain Henry at 2025-08-13T21:09:00-04:00
Fix Data.List unqualified import warning
- - - - -
fd811ded by Simon Peyton Jones at 2025-08-14T17:56:47-04:00
Make injecting implicit bindings into its own pass
Previously we were injecting "impliicit bindings" (data constructor
worker and wrappers etc)
- both at the end of CoreTidy,
- and at the start of CorePrep
This is unpleasant and confusing. This patch puts it it its own pass,
addImplicitBinds, which runs between the two.
The function `GHC.CoreToStg.AddImplicitBinds.addImplicitBinds` now takes /all/
TyCons, not just the ones for algebraic data types. That change ripples
through to
- corePrepPgm
- doCodeGen
- byteCodeGen
All take [TyCon] which includes all TyCons
- - - - -
9bd7fcc5 by Simon Peyton Jones at 2025-08-14T17:56:47-04:00
Implement unary classes
The big change is described exhaustively in
Note [Unary class magic] in GHC.Core.TyCon
Other changes
* We never unbox class dictionaries in worker/wrapper. This has been true for some
time now, but the logic is now centralised in functions in
GHC.Core.Opt.WorkWrap.Utils, namely `canUnboxTyCon`, and `canUnboxArg`
See Note [Do not unbox class dictionaries] in GHC.Core.Opt.WorkWrap.Utils.
* Refactored the `notWorthFloating` logic in GHc.Core.Opt.SetLevels.
I can't remember if I actually changed any behaviour here, but if so it's
only in a corner cases.
* Fixed a bug in `GHC.Core.TyCon.isEnumerationTyCon`, which was wrongly returning
True for (##).
* Remove redundant Role argument to `liftCoSubstWithEx`. It was always
Representational.
* I refactored evidence generation in the constraint solver:
* Made GHC.Tc.Types.Evidence contain better abstactions for evidence
generation.
* I deleted the file `GHC.Tc.Types.EvTerm` and merged its (small) contents
elsewhere. It wasn't paying its way.
* Made evidence for implicit parameters go via a proper abstraction.
* Fix inlineBoringOk; see (IB6) in Note [inlineBoringOk]
This fixes a slowdown in `countdownEffectfulDynLocal`
in the `effectful` library.
Smaller things
* Rename `isDataTyCon` to `isBoxedDataTyCon`.
* GHC.Core.Corecion.liftCoSubstWithEx was only called with Representational role,
so I baked that into the function and removed the argument.
* Get rid of `GHC.Core.TyCon.tyConSingleAlgDataCon_maybe` in favour of calling
`not isNewTyCon` at the call sites; more explicit.
* Refatored `GHC.Core.TyCon.isInjectiveTyCon`; but I don't think I changed its
behaviour
* Moved `decomposeIPPred` to GHC.Core.Predicate
Compile time performance changes:
geo. mean +0.1%
minimum -6.8%
maximum +14.4%
The +14% one is in T21839c, where it seems that a bit more inlining
is taking place. That seems acceptable; and the average change is small
Metric Decrease:
LargeRecord
T12227
T12707
T16577
T21839r
T5642
Metric Increase:
T15164
T21839c
T3294
T5321FD
T5321Fun
WWRec
- - - - -
b4075d71 by Simon Peyton Jones at 2025-08-14T17:56:47-04:00
Slight improvement to pre/postInlineUnconditionally
Avoids an extra simplifier iteration
- - - - -
9e443596 by Simon Peyton Jones at 2025-08-14T17:56:47-04:00
Fix a long-standing assertion error in normSplitTyConApp_maybe
- - - - -
91310ad0 by Simon Peyton Jones at 2025-08-14T17:56:47-04:00
Add comment to coercion optimiser
- - - - -
5b841d82 by Teo Camarasu at 2025-08-14T17:57:56-04:00
template-haskell: move some identifiers from ghc-internal to template-haskell
These identifiers are not used internally by the compiler. Therefore we
have no reason for them to be in ghc-internal.
By moving them to template-haskell, we benefit from it being easier to
change them and we avoid having to build them in stage0.
Resolves #26048
- - - - -
33e2c7e5 by Teo Camarasu at 2025-08-14T17:57:56-04:00
template-haskell: transfer $infix note to public module
This Haddock note should be in the public facing module
- - - - -
2a411fc4 by Sylvain Henry at 2025-08-14T17:59:09-04:00
JS: export HEAP8 symbol (#26290)
Newer Emscripten requires this.
- - - - -
248f78ca by Ben Gamari at 2025-08-14T17:59:51-04:00
users-guide: Drop the THREAD_RUNNABLE event
As of f361281c89fbce42865d8b8b27b0957205366186 it is no longer emitted.
- - - - -
706d33e3 by Recursion Ninja at 2025-08-15T04:12:12-04:00
Resolving issues #20645 and #26109
Correctly sign extending and casting smaller bit width types for LLVM operations:
- bitReverse8#
- bitReverse16#
- bitReverse32#
- byteSwap16#
- byteSwap32#
- pdep8#
- pdep16#
- pext8#
- pext16#
- - - - -
1cdc6f46 by Cheng Shao at 2025-08-15T04:12:56-04:00
hadrian: enforce have_llvm=False for wasm32/js
This patch fixes hadrian to always pass have_llvm=False to the
testsuite driver for wasm32/js targets. These targets don't really
support the LLVM backend, and the optllvm test way doesn't work. We
used to special-case wasm32/js to avoid auto-adding optllvm way in
testsuite/config/ghc, but this is still problematic if someone writes
a new LLVM-related test and uses something like when(have_llvm(),
extra_ways(["optllvm"])). So better just enforce have_llvm=False for
these targets here.
- - - - -
869a90c0 by Mike Pilgrem at 2025-08-15T19:22:34+01: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-unrecognised-warning-flags` `-Wno-x-partial` to the `Cabal`, `filepath`, `hsc2hs`, `hpc`, `parsec`, `text` and `time` packages (outside GHC's repository).
Also bumps submodules.
- - - - -
81d591b3 by Andrew Lelechenko at 2025-08-15T19:22:34+01:00
Wibble
- - - - -
1cd09314 by Andrew Lelechenko at 2025-08-15T19:22:34+01:00
Wobble
- - - - -
d832a1bd by Andrew Lelechenko at 2025-08-15T19:22:34+01:00
Revert GHC.Internal.System.IO
- - - - -
33ce0807 by Andrew Lelechenko at 2025-08-15T19:22:34+01:00
Revert GHC.Core.Utils
- - - - -
22f5ab7e by Andrew Lelechenko at 2025-08-15T19:22:34+01:00
Revert template-haskell
- - - - -
6ed912bc by Andrew Lelechenko at 2025-08-15T19:22:34+01:00
Revert filepath
- - - - -
206 changed files:
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/InfoTable.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/FamInstEnv.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/SetLevels.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Unfold.hs
- compiler/GHC/Core/Unfold/Make.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToStg.hs
- + compiler/GHC/CoreToStg/AddImplicitBinds.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Driver/Session/Units.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Foreign/Call.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Tidy.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Prelude/Basic.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Stg/Lint.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/Instance/Family.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.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/EvTerm.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Validity.hs
- compiler/GHC/Types/Demand.hs
- compiler/GHC/Types/Error.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Make.hs
- compiler/GHC/Types/RepType.hs
- compiler/GHC/Types/TyThing.hs
- compiler/GHC/Utils/Error.hs
- compiler/ghc.cabal.in
- − docs/users_guide/9.14.1-notes.rst
- + docs/users_guide/9.16.1-notes.rst
- docs/users_guide/eventlog-formats.rst
- docs/users_guide/release-notes.rst
- ghc/GHCi/UI.hs
- ghc/Main.hs
- hadrian/src/Settings/Builders/RunTest.hs
- hadrian/src/Settings/Warnings.hs
- libraries/base/changelog.md
- libraries/filepath
- libraries/ghc-bignum/changelog.md
- libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs
- + libraries/ghc-experimental/src/GHC/Exception/Backtrace/Experimental.hs
- libraries/ghc-internal/cbits/pdep.c
- libraries/ghc-internal/cbits/pext.c
- libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs
- libraries/ghc-internal/src/GHC/Internal/Exception.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs-boot
- libraries/ghc-internal/src/GHC/Internal/Float.hs
- libraries/ghc-internal/src/GHC/Internal/List.hs
- libraries/ghc-internal/src/GHC/Internal/System/IO.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
- + libraries/ghc-internal/tests/Makefile
- + libraries/ghc-internal/tests/all.T
- + libraries/ghc-internal/tests/backtraces/Makefile
- + libraries/ghc-internal/tests/backtraces/T14532a.hs
- + libraries/ghc-internal/tests/backtraces/T14532a.stdout
- + libraries/ghc-internal/tests/backtraces/T14532b.hs
- + libraries/ghc-internal/tests/backtraces/T14532b.stdout
- + libraries/ghc-internal/tests/backtraces/all.T
- libraries/template-haskell/Language/Haskell/TH/Lib.hs
- libraries/template-haskell/Language/Haskell/TH/Quote.hs
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs
- libraries/template-haskell/tests/all.T
- libraries/template-haskell/vendored-filepath/System/FilePath/Posix.hs
- libraries/template-haskell/vendored-filepath/System/FilePath/Windows.hs
- rts/Messages.c
- rts/StgMiscClosures.cmm
- rts/Updates.h
- rts/external-symbols.list.in
- rts/js/mem.js
- rts/rts.cabal
- testsuite/config/ghc
- testsuite/driver/testlib.py
- testsuite/tests/arrows/should_compile/T21301.stderr
- testsuite/tests/core-to-stg/T24124.stderr
- testsuite/tests/deSugar/should_compile/T2431.stderr
- testsuite/tests/deSugar/should_fail/DsStrictFail.stderr
- testsuite/tests/deSugar/should_run/T20024.stderr
- testsuite/tests/deSugar/should_run/dsrun005.stderr
- testsuite/tests/deSugar/should_run/dsrun007.stderr
- testsuite/tests/deSugar/should_run/dsrun008.stderr
- testsuite/tests/deriving/should_run/T9576.stderr
- testsuite/tests/dmdanal/should_compile/T16029.stdout
- testsuite/tests/dmdanal/sigs/T21119.stderr
- testsuite/tests/dmdanal/sigs/T21888.stderr
- testsuite/tests/driver/j-space/jspace.hs
- testsuite/tests/ghci.debugger/scripts/break011.stdout
- testsuite/tests/ghci.debugger/scripts/break024.stdout
- testsuite/tests/ghci/scripts/Defer02.stderr
- testsuite/tests/ghci/scripts/T15325.stderr
- testsuite/tests/hpc/recsel/recsel.hs
- testsuite/tests/hpc/recsel/recsel.stdout
- testsuite/tests/indexed-types/should_compile/T2238.hs
- testsuite/tests/interface-stability/template-haskell-exports.stdout
- + testsuite/tests/llvm/should_run/T20645.hs
- + testsuite/tests/llvm/should_run/T20645.stdout
- testsuite/tests/llvm/should_run/all.T
- testsuite/tests/numeric/should_compile/T15547.stderr
- testsuite/tests/numeric/should_compile/T23907.stderr
- + testsuite/tests/numeric/should_run/T26230.hs
- + testsuite/tests/numeric/should_run/T26230.stdout
- testsuite/tests/numeric/should_run/all.T
- testsuite/tests/numeric/should_run/foundation.hs
- + testsuite/tests/overloadedrecflds/should_run/T26295.hs
- + testsuite/tests/overloadedrecflds/should_run/T26295.stdout
- testsuite/tests/overloadedrecflds/should_run/all.T
- testsuite/tests/patsyn/should_run/ghci.stderr
- testsuite/tests/quasiquotation/T4491/test.T
- testsuite/tests/quotes/LiftErrMsgDefer.stderr
- testsuite/tests/roles/should_compile/Roles14.stderr
- testsuite/tests/roles/should_compile/Roles3.stderr
- testsuite/tests/roles/should_compile/Roles4.stderr
- testsuite/tests/rts/KeepCafsBase.hs
- testsuite/tests/safeHaskell/safeLanguage/SafeLang15.stderr
- testsuite/tests/simplCore/should_compile/DataToTagFamilyScrut.stderr
- testsuite/tests/simplCore/should_compile/T15205.stderr
- testsuite/tests/simplCore/should_compile/T17366.stderr
- testsuite/tests/simplCore/should_compile/T17966.stderr
- testsuite/tests/simplCore/should_compile/T22309.stderr
- testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr
- testsuite/tests/simplCore/should_compile/T23307.stderr
- testsuite/tests/simplCore/should_compile/T23307a.stderr
- testsuite/tests/simplCore/should_compile/T25389.stderr
- testsuite/tests/simplCore/should_compile/T25713.stderr
- testsuite/tests/simplCore/should_compile/T7360.stderr
- testsuite/tests/simplStg/should_compile/T15226b.stderr
- testsuite/tests/tcplugins/CtIdPlugin.hs
- testsuite/tests/th/Makefile
- testsuite/tests/type-data/should_run/T22332a.stderr
- testsuite/tests/typecheck/should_compile/Makefile
- testsuite/tests/typecheck/should_compile/T12763.stderr
- testsuite/tests/typecheck/should_compile/T14774.stdout
- testsuite/tests/typecheck/should_compile/T18406b.stderr
- testsuite/tests/typecheck/should_compile/T18529.stderr
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_run/T10284.stderr
- testsuite/tests/typecheck/should_run/T13838.stderr
- testsuite/tests/typecheck/should_run/T9497a-run.stderr
- testsuite/tests/typecheck/should_run/T9497b-run.stderr
- testsuite/tests/typecheck/should_run/T9497c-run.stderr
- testsuite/tests/unboxedsums/unpack_sums_7.stdout
- testsuite/tests/unsatisfiable/T23816.stderr
- testsuite/tests/unsatisfiable/UnsatDefer.stderr
- testsuite/tests/wasm/should_run/control-flow/LoadCmmGroup.hs
- testsuite/tests/wasm/should_run/control-flow/RunWasm.hs
- utils/check-exact/Main.hs
- utils/check-exact/Transform.hs
- utils/check-exact/Utils.hs
- utils/genprimopcode/Lexer.x
- utils/genprimopcode/Main.hs
- utils/genprimopcode/Parser.y
- utils/genprimopcode/ParserM.hs
- utils/genprimopcode/Syntax.hs
- utils/ghc-pkg/Main.hs
- utils/ghc-toolchain/src/GHC/Toolchain/CheckArm.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml.hs
- utils/haddock/haddock-library/src/Documentation/Haddock/Parser.hs
- utils/hpc
- utils/hsc2hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3fa7314c859a76e8d976f3d9115eae…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3fa7314c859a76e8d976f3d9115eae…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/fix-26065] 27 commits: Extend record-selector usage ticking to all binds using a record field
by recursion-ninja (@recursion-ninja) 15 Aug '25
by recursion-ninja (@recursion-ninja) 15 Aug '25
15 Aug '25
recursion-ninja pushed to branch wip/fix-26065 at Glasgow Haskell Compiler / GHC
Commits:
62899117 by Florian Ragwitz at 2025-08-13T21:01:34-04:00
Extend record-selector usage ticking to all binds using a record field
This extends the previous handling of ticking for RecordWildCards and
NamedFieldPuns to all var bindings that involve record selectors.
Note that certain patterns such as `Foo{foo = 42}` will currently not tick the
`foo` selector, as ticking is triggered by `HsVar`s.
Closes #26191.
- - - - -
b37b3af7 by Florian Ragwitz at 2025-08-13T21:01:34-04:00
Add release notes for 9.16.1 and move description of latest HPC changes there.
- - - - -
a5e4b7d9 by Ben Gamari at 2025-08-13T21:02:18-04:00
rts: Clarify rationale for undefined atomic wrappers
Since c06e3f46d24ef69f3a3d794f5f604cb8c2a40cbc the RTS has declared
various atomic operation wrappers defined by ghc-internal as undefined.
While the rationale for this isn't clear from the commit message, I
believe that this is necessary due to the unregisterised backend.
Specifically, the code generator will reference these symbols when
compiling RTS Cmm sources.
- - - - -
50842f83 by Andreas Klebinger at 2025-08-13T21:03:01-04:00
Make unexpected LLVM versions a warning rather than an error.
Typically a newer LLVM version *will* work so erroring out if
a user uses a newer LLVM version is too aggressive.
Fixes #25915
- - - - -
c91e2650 by fendor at 2025-08-13T21:03:43-04:00
Store `StackTrace` and `StackSnapshot` in `Backtraces`
Instead of decoding the stack traces when collecting the `Backtraces`,
defer this decoding until actually showing the `Backtraces`.
This allows users to customise how `Backtraces` are displayed by
using a custom implementation of `displayExceptionWithInfo`, overwriting
the default implementation for `Backtraces` (`displayBacktraces`).
- - - - -
dee28cdd by fendor at 2025-08-13T21:03:43-04:00
Allow users to customise the collection of exception annotations
Add a global `CollectExceptionAnnotationMechanism` which determines how
`ExceptionAnnotation`s are collected upon throwing an `Exception`.
This API is exposed via `ghc-experimental`.
By overriding how we collect `Backtraces`, we can control how the
`Backtraces` are displayed to the user by newtyping `Backtraces` and
giving a different instance for `ExceptionAnnotation`.
A concrete use-case for this feature is allowing us to experiment with
alternative stack decoders, without having to modify `base`, which take
additional information from the stack frames.
This commit does not modify how `Backtraces` are currently
collected or displayed.
- - - - -
66024722 by fendor at 2025-08-13T21:03:43-04:00
Expose Backtraces internals from ghc-experimental
Additionally, expose the same API `base:Control.Exception.Backtrace`
to make it easier to use as a drop-in replacement.
- - - - -
a766286f by Reed Mullanix at 2025-08-13T21:04:36-04:00
ghc-internal: Fix naturalAndNot for NB/NS case
When the first argument to `naturalAndNot` is larger than a `Word` and the second is `Word`-sized, `naturalAndNot` will truncate the
result:
```
>>> naturalAndNot ((2 ^ 65) .|. (2 ^ 3)) (2 ^ 3)
0
```
In contrast, `naturalAndNot` does not truncate when both arguments are larger than a `Word`, so this appears to be a bug.
Luckily, the fix is pretty easy: we just need to call `bigNatAndNotWord#` instead of truncating.
Fixes #26230
- - - - -
3506fa7d by Simon Hengel at 2025-08-13T21:05:18-04:00
Report -pgms as a deprecated flag
(instead of reporting an unspecific warning)
Before:
on the commandline: warning:
Object splitting was removed in GHC 8.8
After:
on the commandline: warning: [GHC-53692] [-Wdeprecated-flags]
-pgms is deprecated: Object splitting was removed in GHC 8.8
- - - - -
51c701fe by Zubin Duggal at 2025-08-13T21:06:00-04:00
testsuite: Be more permissive when filtering out GNU_PROPERTY_TYPE linker warnings
The warning text is slightly different with ld.bfd.
Fixes #26249
- - - - -
dfe6f464 by Simon Hengel at 2025-08-13T21:06:43-04:00
Refactoring: Don't misuse `MCDiagnostic` for lint messages
`MCDiagnostic` is meant to be used for compiler diagnostics.
Any code that creates `MCDiagnostic` directly, without going through
`GHC.Driver.Errors.printMessage`, side steps `-fdiagnostics-as-json`
(see e.g. !14475, !14492 !14548).
To avoid this in the future I want to control more narrowly who creates
`MCDiagnostic` (see #24113).
Some parts of the compiler use `MCDiagnostic` purely for formatting
purposes, without creating any real compiler diagnostics. This change
introduces a helper function, `formatDiagnostic`, that can be used in
such cases instead of constructing `MCDiagnostic`.
- - - - -
a8b2fbae by Teo Camarasu at 2025-08-13T21:07:24-04:00
rts: ensure MessageBlackHole.link is always a valid closure
We turn a MessageBlackHole into an StgInd in wakeBlockingQueue().
Therefore it's important that the link field, which becomes the
indirection field, always points to a valid closure.
It's unclear whether it's currently possible for the previous behaviour
to lead to a crash, but it's good to be consistent about this invariant nonetheless.
Co-authored-by: Andreas Klebinger <klebinger.andreas(a)gmx.at>
- - - - -
4021181e by Teo Camarasu at 2025-08-13T21:07:24-04:00
rts: spin if we see a WHITEHOLE in messageBlackHole
When a BLACKHOLE gets cancelled in raiseAsync, we indirect to a THUNK.
GC can then shortcut this, replacing our BLACKHOLE with a fresh THUNK.
This THUNK is not guaranteed to have a valid indirectee field.
If at the same time, a message intended for the previous BLACKHOLE is
processed and concurrently we BLACKHOLE the THUNK, thus temporarily
turning it into a WHITEHOLE, we can get a segfault, since we look at the
undefined indirectee field of the THUNK
The fix is simple: spin if we see a WHITEHOLE, and it will soon be
replaced with a valid BLACKHOLE.
Resolves #26205
- - - - -
1107af89 by Oleg Grenrus at 2025-08-13T21:08:06-04:00
Allow defining HasField instances for naughty fields
Resolves #26295
... as HasField solver doesn't solve for fields with "naughty"
selectors, we could as well allow defining HasField instances for these
fields.
- - - - -
020e7587 by Sylvain Henry at 2025-08-13T21:09:00-04:00
Fix Data.List unqualified import warning
- - - - -
fd811ded by Simon Peyton Jones at 2025-08-14T17:56:47-04:00
Make injecting implicit bindings into its own pass
Previously we were injecting "impliicit bindings" (data constructor
worker and wrappers etc)
- both at the end of CoreTidy,
- and at the start of CorePrep
This is unpleasant and confusing. This patch puts it it its own pass,
addImplicitBinds, which runs between the two.
The function `GHC.CoreToStg.AddImplicitBinds.addImplicitBinds` now takes /all/
TyCons, not just the ones for algebraic data types. That change ripples
through to
- corePrepPgm
- doCodeGen
- byteCodeGen
All take [TyCon] which includes all TyCons
- - - - -
9bd7fcc5 by Simon Peyton Jones at 2025-08-14T17:56:47-04:00
Implement unary classes
The big change is described exhaustively in
Note [Unary class magic] in GHC.Core.TyCon
Other changes
* We never unbox class dictionaries in worker/wrapper. This has been true for some
time now, but the logic is now centralised in functions in
GHC.Core.Opt.WorkWrap.Utils, namely `canUnboxTyCon`, and `canUnboxArg`
See Note [Do not unbox class dictionaries] in GHC.Core.Opt.WorkWrap.Utils.
* Refactored the `notWorthFloating` logic in GHc.Core.Opt.SetLevels.
I can't remember if I actually changed any behaviour here, but if so it's
only in a corner cases.
* Fixed a bug in `GHC.Core.TyCon.isEnumerationTyCon`, which was wrongly returning
True for (##).
* Remove redundant Role argument to `liftCoSubstWithEx`. It was always
Representational.
* I refactored evidence generation in the constraint solver:
* Made GHC.Tc.Types.Evidence contain better abstactions for evidence
generation.
* I deleted the file `GHC.Tc.Types.EvTerm` and merged its (small) contents
elsewhere. It wasn't paying its way.
* Made evidence for implicit parameters go via a proper abstraction.
* Fix inlineBoringOk; see (IB6) in Note [inlineBoringOk]
This fixes a slowdown in `countdownEffectfulDynLocal`
in the `effectful` library.
Smaller things
* Rename `isDataTyCon` to `isBoxedDataTyCon`.
* GHC.Core.Corecion.liftCoSubstWithEx was only called with Representational role,
so I baked that into the function and removed the argument.
* Get rid of `GHC.Core.TyCon.tyConSingleAlgDataCon_maybe` in favour of calling
`not isNewTyCon` at the call sites; more explicit.
* Refatored `GHC.Core.TyCon.isInjectiveTyCon`; but I don't think I changed its
behaviour
* Moved `decomposeIPPred` to GHC.Core.Predicate
Compile time performance changes:
geo. mean +0.1%
minimum -6.8%
maximum +14.4%
The +14% one is in T21839c, where it seems that a bit more inlining
is taking place. That seems acceptable; and the average change is small
Metric Decrease:
LargeRecord
T12227
T12707
T16577
T21839r
T5642
Metric Increase:
T15164
T21839c
T3294
T5321FD
T5321Fun
WWRec
- - - - -
b4075d71 by Simon Peyton Jones at 2025-08-14T17:56:47-04:00
Slight improvement to pre/postInlineUnconditionally
Avoids an extra simplifier iteration
- - - - -
9e443596 by Simon Peyton Jones at 2025-08-14T17:56:47-04:00
Fix a long-standing assertion error in normSplitTyConApp_maybe
- - - - -
91310ad0 by Simon Peyton Jones at 2025-08-14T17:56:47-04:00
Add comment to coercion optimiser
- - - - -
5b841d82 by Teo Camarasu at 2025-08-14T17:57:56-04:00
template-haskell: move some identifiers from ghc-internal to template-haskell
These identifiers are not used internally by the compiler. Therefore we
have no reason for them to be in ghc-internal.
By moving them to template-haskell, we benefit from it being easier to
change them and we avoid having to build them in stage0.
Resolves #26048
- - - - -
33e2c7e5 by Teo Camarasu at 2025-08-14T17:57:56-04:00
template-haskell: transfer $infix note to public module
This Haddock note should be in the public facing module
- - - - -
2a411fc4 by Sylvain Henry at 2025-08-14T17:59:09-04:00
JS: export HEAP8 symbol (#26290)
Newer Emscripten requires this.
- - - - -
248f78ca by Ben Gamari at 2025-08-14T17:59:51-04:00
users-guide: Drop the THREAD_RUNNABLE event
As of f361281c89fbce42865d8b8b27b0957205366186 it is no longer emitted.
- - - - -
706d33e3 by Recursion Ninja at 2025-08-15T04:12:12-04:00
Resolving issues #20645 and #26109
Correctly sign extending and casting smaller bit width types for LLVM operations:
- bitReverse8#
- bitReverse16#
- bitReverse32#
- byteSwap16#
- byteSwap32#
- pdep8#
- pdep16#
- pext8#
- pext16#
- - - - -
1cdc6f46 by Cheng Shao at 2025-08-15T04:12:56-04:00
hadrian: enforce have_llvm=False for wasm32/js
This patch fixes hadrian to always pass have_llvm=False to the
testsuite driver for wasm32/js targets. These targets don't really
support the LLVM backend, and the optllvm test way doesn't work. We
used to special-case wasm32/js to avoid auto-adding optllvm way in
testsuite/config/ghc, but this is still problematic if someone writes
a new LLVM-related test and uses something like when(have_llvm(),
extra_ways(["optllvm"])). So better just enforce have_llvm=False for
these targets here.
- - - - -
553650d9 by Alex Washburn at 2025-08-15T13:26:04-04:00
Correcting LLVM linking of Intel BMI intrinsics pdep{8,16} and pext{8,16}.
This patch fixes #26045.
The LLVM interface does not expose bindings to:
- llvm.x86.bmi.pdep.8
- llvm.x86.bmi.pdep.16
- llvm.x86.bmi.pext.8
- llvm.x86.bmi.pext.16
So calls are instead made to llvm.x86.bmi.{pdep,pext}.32 in these cases,
with pre/post-operation truncation to constrain the logical value range.
- - - - -
185 changed files:
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/InfoTable.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/FamInstEnv.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/SetLevels.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Unfold.hs
- compiler/GHC/Core/Unfold/Make.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToStg.hs
- + compiler/GHC/CoreToStg/AddImplicitBinds.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Foreign/Call.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Tidy.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Stg/Lint.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/Instance/Family.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.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/EvTerm.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Validity.hs
- compiler/GHC/Types/Demand.hs
- compiler/GHC/Types/Error.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Make.hs
- compiler/GHC/Types/RepType.hs
- compiler/GHC/Types/TyThing.hs
- compiler/GHC/Utils/Error.hs
- compiler/ghc.cabal.in
- − docs/users_guide/9.14.1-notes.rst
- + docs/users_guide/9.16.1-notes.rst
- docs/users_guide/eventlog-formats.rst
- docs/users_guide/release-notes.rst
- hadrian/src/Settings/Builders/RunTest.hs
- libraries/base/changelog.md
- libraries/ghc-bignum/changelog.md
- + libraries/ghc-experimental/src/GHC/Exception/Backtrace/Experimental.hs
- libraries/ghc-internal/cbits/pdep.c
- libraries/ghc-internal/cbits/pext.c
- libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs
- libraries/ghc-internal/src/GHC/Internal/Exception.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs-boot
- libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
- + libraries/ghc-internal/tests/Makefile
- + libraries/ghc-internal/tests/all.T
- + libraries/ghc-internal/tests/backtraces/Makefile
- + libraries/ghc-internal/tests/backtraces/T14532a.hs
- + libraries/ghc-internal/tests/backtraces/T14532a.stdout
- + libraries/ghc-internal/tests/backtraces/T14532b.hs
- + libraries/ghc-internal/tests/backtraces/T14532b.stdout
- + libraries/ghc-internal/tests/backtraces/all.T
- libraries/template-haskell/Language/Haskell/TH/Lib.hs
- libraries/template-haskell/Language/Haskell/TH/Quote.hs
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs
- libraries/template-haskell/tests/all.T
- rts/Messages.c
- rts/StgMiscClosures.cmm
- rts/Updates.h
- rts/external-symbols.list.in
- rts/js/mem.js
- rts/rts.cabal
- testsuite/config/ghc
- testsuite/driver/testlib.py
- testsuite/tests/arrows/should_compile/T21301.stderr
- testsuite/tests/core-to-stg/T24124.stderr
- testsuite/tests/deSugar/should_compile/T2431.stderr
- testsuite/tests/deSugar/should_fail/DsStrictFail.stderr
- testsuite/tests/deSugar/should_run/T20024.stderr
- testsuite/tests/deSugar/should_run/dsrun005.stderr
- testsuite/tests/deSugar/should_run/dsrun007.stderr
- testsuite/tests/deSugar/should_run/dsrun008.stderr
- testsuite/tests/deriving/should_run/T9576.stderr
- testsuite/tests/dmdanal/should_compile/T16029.stdout
- testsuite/tests/dmdanal/sigs/T21119.stderr
- testsuite/tests/dmdanal/sigs/T21888.stderr
- testsuite/tests/ghci.debugger/scripts/break011.stdout
- testsuite/tests/ghci.debugger/scripts/break024.stdout
- testsuite/tests/ghci/scripts/Defer02.stderr
- testsuite/tests/ghci/scripts/T15325.stderr
- testsuite/tests/hpc/recsel/recsel.hs
- testsuite/tests/hpc/recsel/recsel.stdout
- testsuite/tests/indexed-types/should_compile/T2238.hs
- testsuite/tests/interface-stability/template-haskell-exports.stdout
- + testsuite/tests/llvm/should_run/T20645.hs
- + testsuite/tests/llvm/should_run/T20645.stdout
- + testsuite/tests/llvm/should_run/T26065.hs
- + testsuite/tests/llvm/should_run/T26065.stdout
- testsuite/tests/llvm/should_run/all.T
- testsuite/tests/numeric/should_compile/T15547.stderr
- testsuite/tests/numeric/should_compile/T23907.stderr
- + testsuite/tests/numeric/should_run/T26230.hs
- + testsuite/tests/numeric/should_run/T26230.stdout
- testsuite/tests/numeric/should_run/all.T
- testsuite/tests/numeric/should_run/foundation.hs
- + testsuite/tests/overloadedrecflds/should_run/T26295.hs
- + testsuite/tests/overloadedrecflds/should_run/T26295.stdout
- testsuite/tests/overloadedrecflds/should_run/all.T
- testsuite/tests/patsyn/should_run/ghci.stderr
- testsuite/tests/quasiquotation/T4491/test.T
- testsuite/tests/quotes/LiftErrMsgDefer.stderr
- testsuite/tests/roles/should_compile/Roles14.stderr
- testsuite/tests/roles/should_compile/Roles3.stderr
- testsuite/tests/roles/should_compile/Roles4.stderr
- testsuite/tests/safeHaskell/safeLanguage/SafeLang15.stderr
- testsuite/tests/simplCore/should_compile/DataToTagFamilyScrut.stderr
- testsuite/tests/simplCore/should_compile/T15205.stderr
- testsuite/tests/simplCore/should_compile/T17366.stderr
- testsuite/tests/simplCore/should_compile/T17966.stderr
- testsuite/tests/simplCore/should_compile/T22309.stderr
- testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr
- testsuite/tests/simplCore/should_compile/T23307.stderr
- testsuite/tests/simplCore/should_compile/T23307a.stderr
- testsuite/tests/simplCore/should_compile/T25389.stderr
- testsuite/tests/simplCore/should_compile/T25713.stderr
- testsuite/tests/simplCore/should_compile/T7360.stderr
- testsuite/tests/simplStg/should_compile/T15226b.stderr
- testsuite/tests/tcplugins/CtIdPlugin.hs
- testsuite/tests/th/Makefile
- testsuite/tests/type-data/should_run/T22332a.stderr
- testsuite/tests/typecheck/should_compile/Makefile
- testsuite/tests/typecheck/should_compile/T12763.stderr
- testsuite/tests/typecheck/should_compile/T14774.stdout
- testsuite/tests/typecheck/should_compile/T18406b.stderr
- testsuite/tests/typecheck/should_compile/T18529.stderr
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_run/T10284.stderr
- testsuite/tests/typecheck/should_run/T13838.stderr
- testsuite/tests/typecheck/should_run/T9497a-run.stderr
- testsuite/tests/typecheck/should_run/T9497b-run.stderr
- testsuite/tests/typecheck/should_run/T9497c-run.stderr
- testsuite/tests/unboxedsums/unpack_sums_7.stdout
- testsuite/tests/unsatisfiable/T23816.stderr
- testsuite/tests/unsatisfiable/UnsatDefer.stderr
- testsuite/tests/wasm/should_run/control-flow/LoadCmmGroup.hs
- testsuite/tests/wasm/should_run/control-flow/RunWasm.hs
- utils/genprimopcode/Lexer.x
- utils/genprimopcode/Main.hs
- utils/genprimopcode/Parser.y
- utils/genprimopcode/ParserM.hs
- utils/genprimopcode/Syntax.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/344decf713237110e6b1b51483292b…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/344decf713237110e6b1b51483292b…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/backports-9.14] 2 commits: Fix a long-standing assertion error in normSplitTyConApp_maybe
by Ben Gamari (@bgamari) 15 Aug '25
by Ben Gamari (@bgamari) 15 Aug '25
15 Aug '25
Ben Gamari pushed to branch wip/backports-9.14 at Glasgow Haskell Compiler / GHC
Commits:
e09e1443 by Simon Peyton Jones at 2025-08-15T12:25:41-04:00
Fix a long-standing assertion error in normSplitTyConApp_maybe
(cherry picked from commit 60db2c66b870bac28615d272936bef6905befdbb)
- - - - -
7b814248 by Simon Peyton Jones at 2025-08-15T12:25:50-04:00
Add comment to coercion optimiser
(cherry picked from commit b2b95dce34ce7f6a8f0acdd637cbe2cafc56c922)
- - - - -
2 changed files:
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/Utils.hs
Changes:
=====================================
compiler/GHC/Core/Coercion/Opt.hs
=====================================
@@ -208,10 +208,12 @@ optCoercion' env co
in
warnPprTrace (not (isReflCo out_co) && isReflexiveCo out_co)
"optCoercion: reflexive but not refl" details $
--- assertPpr (substTyUnchecked env in_ty1 `eqType` out_ty1 &&
--- substTyUnchecked env in_ty2 `eqType` out_ty2 &&
--- in_role == out_role)
--- (hang (text "optCoercion changed types!") 2 details) $
+ -- The coercion optimiser should usually optimise
+ -- co:ty~ty --> Refl ty
+ -- But given a silly `newtype N = MkN N`, the axiom has type (N ~ N),
+ -- and so that can trigger this warning (e.g. test str002).
+ -- Maybe we should optimise that coercion to (Refl N), but it
+ -- just doesn't seem worth the bother
out_co
| otherwise
=====================================
compiler/GHC/Core/Utils.hs
=====================================
@@ -2730,8 +2730,10 @@ normSplitTyConApp_maybe fam_envs ty
| let Reduction co ty1 = topNormaliseType_maybe fam_envs ty
`orElse` (mkReflRedn Representational ty)
, Just (tc, tc_args) <- splitTyConApp_maybe ty1
- = assertPpr (not (isNewTyCon tc)) (ppr ty $$ ppr ty1) $ -- Check post-condition
- Just (tc, tc_args, co)
+ , not (isNewTyCon tc) -- How can tc be a newtype, after `topNormaliseType`?
+ -- Answer: if it is a recursive newtype, `topNormaliseType`
+ -- may be a no-op. Example: tc226
+ = Just (tc, tc_args, co)
normSplitTyConApp_maybe _ _ = Nothing
{-
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/779a7bc6c1efa07e0cdf8eb125936b…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/779a7bc6c1efa07e0cdf8eb125936b…
You're receiving this email because of your account on gitlab.haskell.org.
1
0