[Git][ghc/ghc][wip/symbolizer] compiler/rts: add debug symbolizer
by Cheng Shao (@TerrorJack) 15 Aug '25
by Cheng Shao (@TerrorJack) 15 Aug '25
15 Aug '25
Cheng Shao pushed to branch wip/symbolizer at Glasgow Haskell Compiler / GHC
Commits:
1c5f14f2 by Cheng Shao at 2025-08-15T06:18:01+02:00
compiler/rts: add debug symbolizer
- - - - -
10 changed files:
- + compiler/GHC/Cmm/GenerateDebugSymbolStub.hs
- compiler/GHC/Driver/CodeOutput.hs
- compiler/GHC/Driver/Main.hs
- compiler/ghc.cabal.in
- rts/Printer.c
- rts/Printer.h
- rts/RtsStartup.c
- rts/include/Rts.h
- + rts/include/rts/Debug.h
- rts/rts.cabal
Changes:
=====================================
compiler/GHC/Cmm/GenerateDebugSymbolStub.hs
=====================================
@@ -0,0 +1,124 @@
+{-# LANGUAGE MultiWayIf #-}
+
+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 ", "[]")
+ | 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"
+ ctor_decls =
+ vcat
+ $ [ text
+ "extern void registerDebugSymbol( void *addr, const char *sym );"
+ ]
+ ++ [ 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
+ ]
+ ctor_body =
+ vcat
+ $ [ text "registerDebugSymbol"
+ <> parens
+ ( text "(void*)&"
+ <> pprCLabel platform lbl
+ <> comma
+ <> doubleQuotes (pprCLabel platform lbl)
+ )
+ <> semi
+ | (lbl, _) <- lbls
+ ]
+ cstub = 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.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
=====================================
rts/Printer.c
=====================================
@@ -43,7 +43,7 @@ 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);
@@ -853,30 +853,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
- * ------------------------------------------------------------------------*/
-
-extern void DEBUG_LoadSymbols( const char *name STG_UNUSED )
-{
- /* nothing, yet */
-}
-
void findPtr(P_ p, int); /* keep gcc -Wall happy */
int searched = 0;
@@ -981,6 +957,29 @@ void printObj( StgClosure *obj )
#endif /* DEBUG */
+/* --------------------------------------------------------------------------
+ * Simple lookup table
+ * address -> function name
+ * ------------------------------------------------------------------------*/
+
+static HashTable * add_to_fname_table = NULL;
+
+void registerDebugSymbol( void *addr, const char *sym ) {
+ if (add_to_fname_table == NULL) {
+ add_to_fname_table = allocHashTable();
+ }
+
+ insertHashTable(add_to_fname_table, (StgWord)addr, 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/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/Debug.h
=====================================
@@ -0,0 +1,16 @@
+/* -----------------------------------------------------------------------------
+ *
+ * (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
+
+void registerDebugSymbol( void *addr, const char *sym );
=====================================
rts/rts.cabal
=====================================
@@ -280,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/-/commit/1c5f14f2bab4f6fa9e84fa911bc34cc…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1c5f14f2bab4f6fa9e84fa911bc34cc…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T21730-import] Revert whitespace changes
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:
bc29a798 by Brandon Chinn at 2025-08-14T18:47:07-07:00
Revert whitespace changes
- - - - -
2 changed files:
- compiler/GHC/Driver/Session/Inspect.hs
- compiler/GHC/Runtime/Loader.hs
Changes:
=====================================
compiler/GHC/Driver/Session/Inspect.hs
=====================================
@@ -132,8 +132,7 @@ availsToGlobalRdrEnv hsc_env mod avails
-- all the specified modules into the global interactive module
imp_spec = ImpSpec { is_decl = decl, is_item = ImpAll}
decl = ImpDeclSpec { is_mod = mod, is_as = moduleName mod,
- is_qual = False,
- is_isboot = NotBoot, is_pkg_qual = NoPkgQual,
+ is_qual = False, is_isboot = NotBoot, is_pkg_qual = NoPkgQual,
is_dloc = srcLocSpan interactiveSrcLoc,
is_level = NormalLevel }
=====================================
compiler/GHC/Runtime/Loader.hs
=====================================
@@ -354,8 +354,7 @@ lookupRdrNameInModuleForPlugins hsc_env mod_name rdr_name = do
Just iface -> do
-- Try and find the required name in the exports
let decl_spec = ImpDeclSpec { is_mod = mod, is_as = mod_name, is_pkg_qual = NoPkgQual
- , is_qual = False
- , is_dloc = noSrcSpan, is_isboot = NotBoot, is_level = SpliceLevel }
+ , is_qual = False, is_dloc = noSrcSpan, is_isboot = NotBoot, is_level = SpliceLevel }
imp_spec = ImpSpec decl_spec ImpAll
env = mkGlobalRdrEnv
$ gresFromAvails hsc_env (Just imp_spec) (mi_exports iface)
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bc29a798654f3452a23ce5ea019b881…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bc29a798654f3452a23ce5ea019b881…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/backports-9.14] 2 commits: Make injecting implicit bindings into its own pass
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:
60d9447e by Simon Peyton Jones at 2025-08-14T22:28:12-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)
- - - - -
1f853c2e by Simon Peyton Jones at 2025-08-14T22:30:21-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)
- - - - -
93 changed files:
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/ByteCode/InfoTable.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/FamInstEnv.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/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/Types/Demand.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Make.hs
- compiler/GHC/Types/RepType.hs
- compiler/GHC/Types/TyThing.hs
- compiler/ghc.cabal.in
- testsuite/tests/core-to-stg/T24124.stderr
- testsuite/tests/deSugar/should_compile/T2431.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/indexed-types/should_compile/T2238.hs
- testsuite/tests/numeric/should_compile/T15547.stderr
- testsuite/tests/numeric/should_compile/T23907.stderr
- testsuite/tests/roles/should_compile/Roles14.stderr
- testsuite/tests/roles/should_compile/Roles3.stderr
- testsuite/tests/roles/should_compile/Roles4.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/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
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0ad30b895a8fadb2c591e83fbd9165…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0ad30b895a8fadb2c591e83fbd9165…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/backports-9.14] 3 commits: Bump GHC on darwin CI to 9.10.1
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:
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
- - - - -
3 changed files:
- .gitlab/darwin/toolchain.nix
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
Changes:
=====================================
.gitlab/darwin/toolchain.nix
=====================================
@@ -16,18 +16,17 @@ let
ghcBindists = let version = ghc.version; in {
aarch64-darwin = hostPkgs.fetchurl {
url = "https://downloads.haskell.org/ghc/${version}/ghc-${version}-aarch64-apple-d…";
- sha256 = "sha256-c1GTMJf3/yiW/t4QL532EswD5JVlgA4getkfsxj4TaA=";
+ sha256 = "sha256-/6+DtdeossBJIMbjkJwL4h3eJ7rzgNCV+ifoQKOi6AQ=";
};
x86_64-darwin = hostPkgs.fetchurl {
url = "https://downloads.haskell.org/ghc/${version}/ghc-${version}-x86_64-apple-da…";
- sha256 = "sha256-LrYniMG0phsvyW6dhQC+3ompvzcxnwAe6GezEqqzoTQ=";
+ sha256 = "sha256-jPIhiJMOENesUnDUJeIaPatgavc6ZVSTY5NFIAxlC+k=";
};
};
ghc = pkgs.stdenv.mkDerivation rec {
- # Using 9.6.2 because of #24050
- version = "9.6.2";
+ version = "9.10.1";
name = "ghc";
src = ghcBindists.${pkgs.stdenv.hostPlatform.system};
configureFlags = [
=====================================
.gitlab/generate-ci/gen_ci.hs
=====================================
@@ -478,7 +478,7 @@ opsysVariables _ (Windows {}) = mconcat
, "LANG" =: "en_US.UTF-8"
, "CABAL_INSTALL_VERSION" =: "3.10.2.0"
, "HADRIAN_ARGS" =: "--docs=no-sphinx-pdfs"
- , "GHC_VERSION" =: "9.6.4"
+ , "GHC_VERSION" =: "9.10.1"
]
opsysVariables _ _ = mempty
=====================================
.gitlab/jobs.yaml
=====================================
@@ -3698,7 +3698,7 @@
"BUILD_FLAVOUR": "validate",
"CABAL_INSTALL_VERSION": "3.10.2.0",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "GHC_VERSION": "9.6.4",
+ "GHC_VERSION": "9.10.1",
"HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"LANG": "en_US.UTF-8",
@@ -3761,7 +3761,7 @@
"BUILD_FLAVOUR": "validate",
"CABAL_INSTALL_VERSION": "3.10.2.0",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "GHC_VERSION": "9.6.4",
+ "GHC_VERSION": "9.10.1",
"HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"LANG": "en_US.UTF-8",
@@ -5579,7 +5579,7 @@
"BUILD_FLAVOUR": "release",
"CABAL_INSTALL_VERSION": "3.10.2.0",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "GHC_VERSION": "9.6.4",
+ "GHC_VERSION": "9.10.1",
"HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
"IGNORE_PERF_FAILURES": "all",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
@@ -5643,7 +5643,7 @@
"BUILD_FLAVOUR": "release",
"CABAL_INSTALL_VERSION": "3.10.2.0",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "GHC_VERSION": "9.6.4",
+ "GHC_VERSION": "9.10.1",
"HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
"IGNORE_PERF_FAILURES": "all",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
@@ -7982,7 +7982,7 @@
"BUILD_FLAVOUR": "validate",
"CABAL_INSTALL_VERSION": "3.10.2.0",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "GHC_VERSION": "9.6.4",
+ "GHC_VERSION": "9.10.1",
"HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"LANG": "en_US.UTF-8",
@@ -8044,7 +8044,7 @@
"BUILD_FLAVOUR": "validate",
"CABAL_INSTALL_VERSION": "3.10.2.0",
"CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
- "GHC_VERSION": "9.6.4",
+ "GHC_VERSION": "9.10.1",
"HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
"INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
"LANG": "en_US.UTF-8",
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/db5147a264dd029996cc442a2acd2f…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/db5147a264dd029996cc442a2acd2f…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/symbolizer] 11 commits: Make injecting implicit bindings into its own pass
by Cheng Shao (@TerrorJack) 15 Aug '25
by Cheng Shao (@TerrorJack) 15 Aug '25
15 Aug '25
Cheng Shao pushed to branch wip/symbolizer at Glasgow Haskell Compiler / GHC
Commits:
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.
- - - - -
596a7476 by Cheng Shao at 2025-08-15T02:41:19+02:00
rts: remove libbfd logic
- - - - -
8f8ea2b5 by Cheng Shao at 2025-08-15T02:44:09+02:00
compiler/rts: add debug symbolizer
- - - - -
123 changed files:
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/ByteCode/InfoTable.hs
- + compiler/GHC/Cmm/GenerateDebugSymbolStub.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/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/CodeOutput.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/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/Types/Demand.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Make.hs
- compiler/GHC/Types/RepType.hs
- compiler/GHC/Types/TyThing.hs
- compiler/ghc.cabal.in
- configure.ac
- docs/users_guide/eventlog-formats.rst
- hadrian/cfg/system.config.in
- hadrian/src/Oracles/Flag.hs
- hadrian/src/Settings/Packages.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/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
- − 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/js/mem.js
- rts/rts.cabal
- testsuite/driver/testlib.py
- testsuite/tests/core-to-stg/T24124.stderr
- testsuite/tests/deSugar/should_compile/T2431.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/indexed-types/should_compile/T2238.hs
- testsuite/tests/interface-stability/template-haskell-exports.stdout
- testsuite/tests/numeric/should_compile/T15547.stderr
- testsuite/tests/numeric/should_compile/T23907.stderr
- testsuite/tests/quasiquotation/T4491/test.T
- testsuite/tests/roles/should_compile/Roles14.stderr
- testsuite/tests/roles/should_compile/Roles3.stderr
- testsuite/tests/roles/should_compile/Roles4.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/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
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f65420f2df26cf623e2453f47c125e…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f65420f2df26cf623e2453f47c125e…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/symbolizer] compiler/rts: add debug symbolizer
by Cheng Shao (@TerrorJack) 15 Aug '25
by Cheng Shao (@TerrorJack) 15 Aug '25
15 Aug '25
Cheng Shao pushed to branch wip/symbolizer at Glasgow Haskell Compiler / GHC
Commits:
f65420f2 by Cheng Shao at 2025-08-15T02:35:45+02:00
compiler/rts: add debug symbolizer
- - - - -
10 changed files:
- + compiler/GHC/Cmm/GenerateDebugSymbolStub.hs
- compiler/GHC/Driver/CodeOutput.hs
- compiler/GHC/Driver/Main.hs
- compiler/ghc.cabal.in
- rts/Printer.c
- rts/Printer.h
- rts/RtsStartup.c
- rts/include/Rts.h
- + rts/include/rts/Debug.h
- rts/rts.cabal
Changes:
=====================================
compiler/GHC/Cmm/GenerateDebugSymbolStub.hs
=====================================
@@ -0,0 +1,81 @@
+{-# LANGUAGE MultiWayIf #-}
+
+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 qualified Data.Map.Strict as Map
+import Data.Maybe
+import GHC.Cmm
+import GHC.Cmm.CLabel
+import GHC.Data.FastString
+import GHC.Data.Stream (Stream)
+import qualified GHC.Data.Stream 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 (Section sec_type _) (CmmStaticsRaw lbl _)) =
+ liftIO $ when (externallyVisibleCLabel lbl) $ modifyIORef' lbls_ref $ Map.insert lbl (data_label_type sec_type lbl)
+ per_decl (CmmProc _ lbl _ _)
+ | platformTablesNextToCode platform = pure ()
+ | otherwise = liftIO $ when (externallyVisibleCLabel lbl) $ modifyIORef' lbls_ref $ Map.insert lbl (proc_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 ", "[]")
+ | 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"
+ ctor_decls =
+ vcat
+ $ [ text
+ "extern void registerDebugSymbol( void *addr, const char *sym );"
+ ]
+ ++ [ 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
+ ]
+ ctor_body =
+ vcat
+ $ [ text "registerDebugSymbol"
+ <> parens
+ ( text "(void*)&"
+ <> pprCLabel platform lbl
+ <> comma
+ <> doubleQuotes (pprCLabel platform lbl)
+ )
+ <> semi
+ | (lbl, _) <- lbls
+ ]
+ cstub = 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
=====================================
@@ -2093,7 +2093,7 @@ hscGenHardCode hsc_env cgguts location 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 location
+ codeOutput platform logger tmpfs llvm_config dflags (hsc_units hsc_env) this_mod output_filename location
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)
@@ -2247,7 +2247,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.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
=====================================
rts/Printer.c
=====================================
@@ -43,7 +43,7 @@ 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);
@@ -853,30 +853,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
- * ------------------------------------------------------------------------*/
-
-extern void DEBUG_LoadSymbols( const char *name STG_UNUSED )
-{
- /* nothing, yet */
-}
-
void findPtr(P_ p, int); /* keep gcc -Wall happy */
int searched = 0;
@@ -981,6 +957,29 @@ void printObj( StgClosure *obj )
#endif /* DEBUG */
+/* --------------------------------------------------------------------------
+ * Simple lookup table
+ * address -> function name
+ * ------------------------------------------------------------------------*/
+
+static HashTable * add_to_fname_table = NULL;
+
+void registerDebugSymbol( void *addr, const char *sym ) {
+ if (add_to_fname_table == NULL) {
+ add_to_fname_table = allocHashTable();
+ }
+
+ insertHashTable(add_to_fname_table, (StgWord)addr, 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/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/Debug.h
=====================================
@@ -0,0 +1,16 @@
+/* -----------------------------------------------------------------------------
+ *
+ * (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
+
+void registerDebugSymbol( void *addr, const char *sym );
=====================================
rts/rts.cabal
=====================================
@@ -280,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/-/commit/f65420f2df26cf623e2453f47c125e0…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f65420f2df26cf623e2453f47c125e0…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 11 commits: Make injecting implicit bindings into its own pass
by Marge Bot (@marge-bot) 14 Aug '25
by Marge Bot (@marge-bot) 14 Aug '25
14 Aug '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
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.
- - - - -
82aabee1 by Recursion Ninja at 2025-08-14T18:31:32-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#
- - - - -
0982b7bb by Cheng Shao at 2025-08-14T18:31:33-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.
- - - - -
123 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/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/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/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/Types/Demand.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Make.hs
- compiler/GHC/Types/RepType.hs
- compiler/GHC/Types/TyThing.hs
- compiler/ghc.cabal.in
- docs/users_guide/eventlog-formats.rst
- hadrian/src/Settings/Builders/RunTest.hs
- libraries/ghc-internal/cbits/pdep.c
- libraries/ghc-internal/cbits/pext.c
- 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/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/js/mem.js
- testsuite/config/ghc
- testsuite/driver/testlib.py
- testsuite/tests/core-to-stg/T24124.stderr
- testsuite/tests/deSugar/should_compile/T2431.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/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/foundation.hs
- testsuite/tests/quasiquotation/T4491/test.T
- testsuite/tests/roles/should_compile/Roles14.stderr
- testsuite/tests/roles/should_compile/Roles3.stderr
- testsuite/tests/roles/should_compile/Roles4.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/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/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/fac5919abd06e97ec604c908e59a06…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fac5919abd06e97ec604c908e59a06…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] users-guide: Drop the THREAD_RUNNABLE event
by Marge Bot (@marge-bot) 14 Aug '25
by Marge Bot (@marge-bot) 14 Aug '25
14 Aug '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
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.
- - - - -
1 changed file:
- docs/users_guide/eventlog-formats.rst
Changes:
=====================================
docs/users_guide/eventlog-formats.rst
=====================================
@@ -228,16 +228,7 @@ Thread and scheduling events
values)
The indicated thread has stopped running for the reason given by ``status``.
-
-
-.. event-type:: THREAD_RUNNABLE
-
- :tag: 3
- :length: fixed
- :field ThreadId: thread id
-
- The indicated thread is has been marked as ready to run.
-
+
.. event-type:: MIGRATE_THREAD
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/248f78ca88fcc8af9dc37bff2f081af…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/248f78ca88fcc8af9dc37bff2f081af…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
14 Aug '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
2a411fc4 by Sylvain Henry at 2025-08-14T17:59:09-04:00
JS: export HEAP8 symbol (#26290)
Newer Emscripten requires this.
- - - - -
2 changed files:
- rts/js/mem.js
- testsuite/driver/testlib.py
Changes:
=====================================
rts/js/mem.js
=====================================
@@ -1,5 +1,5 @@
//#OPTIONS:CPP
-//#OPTIONS:EMCC:EXPORTED_RUNTIME_METHODS=addFunction,removeFunction,getEmptyTableSlot
+//#OPTIONS:EMCC:EXPORTED_RUNTIME_METHODS=addFunction,removeFunction,getEmptyTableSlot,HEAP8
// #define GHCJS_TRACE_META 1
=====================================
testsuite/driver/testlib.py
=====================================
@@ -3004,6 +3004,8 @@ def normalise_errmsg(s: str) -> str:
s = re.sub('.*warning: argument unused during compilation:.*\n', '', s)
# Emscripten displays cache info and old emcc doesn't support EMCC_LOGGING=0
s = re.sub('cache:INFO: .*\n', '', s)
+ # Old emcc warns when we export HEAP8 but new one requires it (see #26290)
+ s = s.replace('warning: invalid item in EXPORTED_RUNTIME_METHODS: HEAP8\nemcc: warning: warnings in JS library compilation [-Wjs-compiler]\n','')
return s
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2a411fc45d19a37615a6a47e0530c01…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2a411fc45d19a37615a6a47e0530c01…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] 2 commits: template-haskell: move some identifiers from ghc-internal to template-haskell
by Marge Bot (@marge-bot) 14 Aug '25
by Marge Bot (@marge-bot) 14 Aug '25
14 Aug '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
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
- - - - -
10 changed files:
- 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/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
- testsuite/tests/interface-stability/template-haskell-exports.stdout
- testsuite/tests/quasiquotation/T4491/test.T
- testsuite/tests/th/Makefile
Changes:
=====================================
libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs
=====================================
@@ -555,20 +555,6 @@ pragInlD name inline rm phases
pragOpaqueD :: Quote m => Name -> m Dec
pragOpaqueD name = pure $ PragmaD $ OpaqueP name
-{-# DEPRECATED pragSpecD "Please use 'pragSpecED' instead. 'pragSpecD' will be removed in GHC 9.18." #-}
-pragSpecD :: Quote m => Name -> m Type -> Phases -> m Dec
-pragSpecD n ty phases
- = do
- ty1 <- ty
- pure $ PragmaD $ SpecialiseP n ty1 Nothing phases
-
-{-# DEPRECATED pragSpecInlD "Please use 'pragSpecInlED' instead. 'pragSpecInlD' will be removed in GHC 9.18." #-}
-pragSpecInlD :: Quote m => Name -> m Type -> Inline -> Phases -> m Dec
-pragSpecInlD n ty inline phases
- = do
- ty1 <- ty
- pure $ PragmaD $ SpecialiseP n ty1 (Just inline) phases
-
pragSpecED :: Quote m
=> Maybe [m (TyVarBndr ())] -> [m RuleBndr]
-> m Exp
@@ -868,22 +854,6 @@ implicitParamT n t
t' <- t
pure $ ImplicitParamT n t'
-{-# DEPRECATED classP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please use 'conT' and 'appT'." #-}
-classP :: Quote m => Name -> [m Type] -> m Pred
-classP cla tys
- = do
- tysl <- sequenceA tys
- pure (foldl AppT (ConT cla) tysl)
-
-{-# DEPRECATED equalP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please see 'equalityT'." #-}
-equalP :: Quote m => m Type -> m Type -> m Pred
-equalP tleft tright
- = do
- tleft1 <- tleft
- tright1 <- tright
- eqT <- equalityT
- pure (foldl AppT eqT [tleft1, tright1])
-
promotedT :: Quote m => Name -> m Type
promotedT = pure . PromotedT
@@ -906,20 +876,6 @@ noSourceStrictness = pure NoSourceStrictness
sourceLazy = pure SourceLazy
sourceStrict = pure SourceStrict
-{-# DEPRECATED isStrict
- ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
- "Example usage: 'bang noSourceUnpackedness sourceStrict'"] #-}
-{-# DEPRECATED notStrict
- ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
- "Example usage: 'bang noSourceUnpackedness noSourceStrictness'"] #-}
-{-# DEPRECATED unpacked
- ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
- "Example usage: 'bang sourceUnpack sourceStrict'"] #-}
-isStrict, notStrict, unpacked :: Quote m => m Strict
-isStrict = bang noSourceUnpackedness sourceStrict
-notStrict = bang noSourceUnpackedness noSourceStrictness
-unpacked = bang sourceUnpack sourceStrict
-
bang :: Quote m => m SourceUnpackedness -> m SourceStrictness -> m Bang
bang u s = do u' <- u
s' <- s
@@ -931,16 +887,6 @@ bangType = liftA2 (,)
varBangType :: Quote m => Name -> m BangType -> m VarBangType
varBangType v bt = (\(b, t) -> (v, b, t)) <$> bt
-{-# DEPRECATED strictType
- "As of @template-haskell-2.11.0.0@, 'StrictType' has been replaced by 'BangType'. Please use 'bangType' instead." #-}
-strictType :: Quote m => m Strict -> m Type -> m StrictType
-strictType = bangType
-
-{-# DEPRECATED varStrictType
- "As of @template-haskell-2.11.0.0@, 'VarStrictType' has been replaced by 'VarBangType'. Please use 'varBangType' instead." #-}
-varStrictType :: Quote m => Name -> m StrictType -> m VarStrictType
-varStrictType = varBangType
-
-- * Type Literals
-- MonadFail here complicates things (a lot) because it would mean we would
=====================================
libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs
=====================================
@@ -24,40 +24,22 @@
module GHC.Internal.TH.Lift
( Lift(..)
- -- * Generic Lift implementations
- , dataToQa
- , dataToCodeQ
- , dataToExpQ
- , liftDataTyped
- , liftData
- , dataToPatQ
-- * Wired-in names
, liftString
- , trueName
- , falseName
- , nothingName
- , justName
- , leftName
- , rightName
- , nonemptyName
)
where
import GHC.Internal.TH.Syntax
import qualified GHC.Internal.TH.Lib as Lib (litE) -- See wrinkle (W4) of Note [Tracking dependencies on primitives]
-import GHC.Internal.Lexeme ( startsVarSym, startsVarId )
import GHC.Internal.Data.Either
-import GHC.Internal.Type.Reflection
import GHC.Internal.Data.Bool
import GHC.Internal.Base hiding (NonEmpty(..), Type, Module, inline)
-import GHC.Internal.Data.Foldable
import GHC.Internal.Data.NonEmpty (NonEmpty(..))
import GHC.Internal.Integer
import GHC.Internal.Real
import GHC.Internal.Word
import GHC.Internal.Int
-import GHC.Internal.Data.Data hiding (Fixity)
import GHC.Internal.Natural
import GHC.Internal.ForeignPtr
@@ -294,20 +276,6 @@ deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f)
deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g)
=> Lift (# a | b | c | d | e | f | g #)
-trueName, falseName :: Name
-trueName = 'True
-falseName = 'False
-
-nothingName, justName :: Name
-nothingName = 'Nothing
-justName = 'Just
-
-leftName, rightName :: Name
-leftName = 'Left
-rightName = 'Right
-
-nonemptyName :: Name
-nonemptyName = '(:|)
-----------------------------------------------------
--
@@ -443,157 +411,3 @@ deriving instance Lift Info
deriving instance Lift AnnLookup
-- | @since template-haskell-2.22.1.0
deriving instance Lift Extension
-
------------------------------------------------------
---
--- Generic Lift implementations
---
------------------------------------------------------
-
--- | 'dataToQa' is an internal utility function for constructing generic
--- conversion functions from types with 'Data' instances to various
--- quasi-quoting representations. See the source of 'dataToExpQ' and
--- 'dataToPatQ' for two example usages: @mkCon@, @mkLit@
--- and @appQ@ are overloadable to account for different syntax for
--- expressions and patterns; @antiQ@ allows you to override type-specific
--- cases, a common usage is just @const Nothing@, which results in
--- no overloading.
-dataToQa :: forall m a k q. (Quote m, Data a)
- => (Name -> k)
- -> (Lit -> m q)
- -> (k -> [m q] -> m q)
- -> (forall b . Data b => b -> Maybe (m q))
- -> a
- -> m q
-dataToQa mkCon mkLit appCon antiQ t =
- case antiQ t of
- Nothing ->
- case constrRep constr of
- AlgConstr _ ->
- appCon (mkCon funOrConName) conArgs
- where
- funOrConName :: Name
- funOrConName =
- case showConstr constr of
- "(:)" -> Name (mkOccName ":")
- (NameG DataName
- (mkPkgName "ghc-internal")
- (mkModName "GHC.Internal.Types"))
- con@"[]" -> Name (mkOccName con)
- (NameG DataName
- (mkPkgName "ghc-internal")
- (mkModName "GHC.Internal.Types"))
- con@('(':_) -> Name (mkOccName con)
- (NameG DataName
- (mkPkgName "ghc-internal")
- (mkModName "GHC.Internal.Tuple"))
-
- -- Tricky case: see Note [Data for non-algebraic types]
- fun@(x:_) | startsVarSym x || startsVarId x
- -> mkNameG_v tyconPkg tyconMod fun
- con -> mkNameG_d tyconPkg tyconMod con
-
- where
- tycon :: TyCon
- tycon = (typeRepTyCon . typeOf) t
-
- tyconPkg, tyconMod :: String
- tyconPkg = tyConPackage tycon
- tyconMod = tyConModule tycon
-
- conArgs :: [m q]
- conArgs = gmapQ (dataToQa mkCon mkLit appCon antiQ) t
- IntConstr n ->
- mkLit $ IntegerL n
- FloatConstr n ->
- mkLit $ RationalL n
- CharConstr c ->
- mkLit $ CharL c
- where
- constr :: Constr
- constr = toConstr t
-
- Just y -> y
-
-
-{- Note [Data for non-algebraic types]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Class Data was originally intended for algebraic data types. But
-it is possible to use it for abstract types too. For example, in
-package `text` we find
-
- instance Data Text where
- ...
- toConstr _ = packConstr
-
- packConstr :: Constr
- packConstr = mkConstr textDataType "pack" [] Prefix
-
-Here `packConstr` isn't a real data constructor, it's an ordinary
-function. Two complications
-
-* In such a case, we must take care to build the Name using
- mkNameG_v (for values), not mkNameG_d (for data constructors).
- See #10796.
-
-* The pseudo-constructor is named only by its string, here "pack".
- But 'dataToQa' needs the TyCon of its defining module, and has
- to assume it's defined in the same module as the TyCon itself.
- But nothing enforces that; #12596 shows what goes wrong if
- "pack" is defined in a different module than the data type "Text".
- -}
-
--- | A typed variant of 'dataToExpQ'.
-dataToCodeQ :: (Quote m, Data a)
- => (forall b . Data b => b -> Maybe (Code m b))
- -> a -> Code m a
-dataToCodeQ f = unsafeCodeCoerce . dataToExpQ (fmap unTypeCode . f)
-
--- | 'dataToExpQ' converts a value to a 'Exp' representation of the
--- same value, in the SYB style. It is generalized to take a function
--- override type-specific cases; see 'liftData' for a more commonly
--- used variant.
-dataToExpQ :: (Quote m, Data a)
- => (forall b . Data b => b -> Maybe (m Exp))
- -> a
- -> m Exp
-dataToExpQ = dataToQa varOrConE litE (foldl appE)
- where
- -- Make sure that VarE is used if the Constr value relies on a
- -- function underneath the surface (instead of a constructor).
- -- See #10796.
- varOrConE s =
- case nameSpace s of
- Just VarName -> return (VarE s)
- Just (FldName {}) -> return (VarE s)
- Just DataName -> return (ConE s)
- _ -> error $ "Can't construct an expression from name "
- ++ showName s
- appE x y = do { a <- x; b <- y; return (AppE a b)}
- litE c = return (LitE c)
-
--- | A typed variant of 'liftData'.
-liftDataTyped :: (Quote m, Data a) => a -> Code m a
-liftDataTyped = dataToCodeQ (const Nothing)
-
--- | 'liftData' is a variant of 'lift' in the 'Lift' type class which
--- works for any type with a 'Data' instance.
-liftData :: (Quote m, Data a) => a -> m Exp
-liftData = dataToExpQ (const Nothing)
-
--- | 'dataToPatQ' converts a value to a 'Pat' representation of the same
--- value, in the SYB style. It takes a function to handle type-specific cases,
--- alternatively, pass @const Nothing@ to get default behavior.
-dataToPatQ :: (Quote m, Data a)
- => (forall b . Data b => b -> Maybe (m Pat))
- -> a
- -> m Pat
-dataToPatQ = dataToQa id litP conP
- where litP l = return (LitP l)
- conP n ps =
- case nameSpace n of
- Just DataName -> do
- ps' <- sequence ps
- return (ConP n [] ps')
- _ -> error $ "Can't construct a pattern from name "
- ++ showName n
=====================================
libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
=====================================
@@ -22,9 +22,6 @@ module GHC.Internal.TH.Syntax
-- * Language extensions
, module GHC.Internal.LanguageExtensions
, ForeignSrcLang(..)
- -- * Notes
- -- ** Unresolved Infix
- -- $infix
) where
#ifdef BOOTSTRAP_TH
@@ -847,12 +844,6 @@ addTempFile suffix = Q (qAddTempFile suffix)
addTopDecls :: [Dec] -> Q ()
addTopDecls ds = Q (qAddTopDecls ds)
--- |
-addForeignFile :: ForeignSrcLang -> String -> Q ()
-addForeignFile = addForeignSource
-{-# DEPRECATED addForeignFile
- "Use 'Language.Haskell.TH.Syntax.addForeignSource' instead"
- #-} -- deprecated in 8.6
-- | Emit a foreign file which will be compiled and linked to the object for
-- the current module. Currently only languages that can be compiled with
@@ -1614,73 +1605,6 @@ maxPrecedence = (9::Int)
defaultFixity :: Fixity
defaultFixity = Fixity maxPrecedence InfixL
-
-{-
-Note [Unresolved infix]
-~~~~~~~~~~~~~~~~~~~~~~~
--}
-{- $infix #infix#
-
-When implementing antiquotation for quasiquoters, one often wants
-to parse strings into expressions:
-
-> parse :: String -> Maybe Exp
-
-But how should we parse @a + b * c@? If we don't know the fixities of
-@+@ and @*@, we don't know whether to parse it as @a + (b * c)@ or @(a
-+ b) * c@.
-
-In cases like this, use 'UInfixE', 'UInfixP', 'UInfixT', or 'PromotedUInfixT',
-which stand for \"unresolved infix expression / pattern / type / promoted
-constructor\", respectively. When the compiler is given a splice containing a
-tree of @UInfixE@ applications such as
-
-> UInfixE
-> (UInfixE e1 op1 e2)
-> op2
-> (UInfixE e3 op3 e4)
-
-it will look up and the fixities of the relevant operators and
-reassociate the tree as necessary.
-
- * trees will not be reassociated across 'ParensE', 'ParensP', or 'ParensT',
- which are of use for parsing expressions like
-
- > (a + b * c) + d * e
-
- * 'InfixE', 'InfixP', 'InfixT', and 'PromotedInfixT' expressions are never
- reassociated.
-
- * The 'UInfixE' constructor doesn't support sections. Sections
- such as @(a *)@ have no ambiguity, so 'InfixE' suffices. For longer
- sections such as @(a + b * c -)@, use an 'InfixE' constructor for the
- outer-most section, and use 'UInfixE' constructors for all
- other operators:
-
- > InfixE
- > Just (UInfixE ...a + b * c...)
- > op
- > Nothing
-
- Sections such as @(a + b +)@ and @((a + b) +)@ should be rendered
- into 'Exp's differently:
-
- > (+ a + b) ---> InfixE Nothing + (Just $ UInfixE a + b)
- > -- will result in a fixity error if (+) is left-infix
- > (+ (a + b)) ---> InfixE Nothing + (Just $ ParensE $ UInfixE a + b)
- > -- no fixity errors
-
- * Quoted expressions such as
-
- > [| a * b + c |] :: Q Exp
- > [p| a : b : c |] :: Q Pat
- > [t| T + T |] :: Q Type
-
- will never contain 'UInfixE', 'UInfixP', 'UInfixT', 'PromotedUInfixT',
- 'InfixT', 'PromotedInfixT, 'ParensE', 'ParensP', or 'ParensT' constructors.
-
--}
-
-----------------------------------------------------
--
-- The main syntax data types
=====================================
libraries/template-haskell/Language/Haskell/TH/Lib.hs
=====================================
@@ -395,3 +395,66 @@ mdoE = Internal.mdoE Nothing
conP :: Quote m => Name -> [m Pat] -> m Pat
conP n xs = Internal.conP n [] xs
+
+
+--------------------------------------------------------------------------------
+-- * Constraint predicates (deprecated)
+
+{-# DEPRECATED classP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please use 'conT' and 'appT'." #-}
+classP :: Quote m => Name -> [m Type] -> m Pred
+classP cla tys
+ = do
+ tysl <- sequenceA tys
+ pure (foldl AppT (ConT cla) tysl)
+
+{-# DEPRECATED equalP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please see 'equalityT'." #-}
+equalP :: Quote m => m Type -> m Type -> m Pred
+equalP tleft tright
+ = do
+ tleft1 <- tleft
+ tright1 <- tright
+ eqT <- equalityT
+ pure (foldl AppT eqT [tleft1, tright1])
+
+--------------------------------------------------------------------------------
+-- * Strictness queries (deprecated)
+{-# DEPRECATED isStrict
+ ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
+ "Example usage: 'bang noSourceUnpackedness sourceStrict'"] #-}
+{-# DEPRECATED notStrict
+ ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
+ "Example usage: 'bang noSourceUnpackedness noSourceStrictness'"] #-}
+{-# DEPRECATED unpacked
+ ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
+ "Example usage: 'bang sourceUnpack sourceStrict'"] #-}
+isStrict, notStrict, unpacked :: Quote m => m Strict
+isStrict = bang noSourceUnpackedness sourceStrict
+notStrict = bang noSourceUnpackedness noSourceStrictness
+unpacked = bang sourceUnpack sourceStrict
+
+{-# DEPRECATED strictType
+ "As of @template-haskell-2.11.0.0@, 'StrictType' has been replaced by 'BangType'. Please use 'bangType' instead." #-}
+strictType :: Quote m => m Strict -> m Type -> m StrictType
+strictType = bangType
+
+{-# DEPRECATED varStrictType
+ "As of @template-haskell-2.11.0.0@, 'VarStrictType' has been replaced by 'VarBangType'. Please use 'varBangType' instead." #-}
+varStrictType :: Quote m => Name -> m StrictType -> m VarStrictType
+varStrictType = varBangType
+
+--------------------------------------------------------------------------------
+-- * Specialisation pragmas (deprecated)
+
+{-# DEPRECATED pragSpecD "Please use 'pragSpecED' instead. 'pragSpecD' will be removed in GHC 9.18." #-}
+pragSpecD :: Quote m => Name -> m Type -> Phases -> m Dec
+pragSpecD n ty phases
+ = do
+ ty1 <- ty
+ pure $ PragmaD $ SpecialiseP n ty1 Nothing phases
+
+{-# DEPRECATED pragSpecInlD "Please use 'pragSpecInlED' instead. 'pragSpecInlD' will be removed in GHC 9.18." #-}
+pragSpecInlD :: Quote m => Name -> m Type -> Inline -> Phases -> m Dec
+pragSpecInlD n ty inline phases
+ = do
+ ty1 <- ty
+ pure $ PragmaD $ SpecialiseP n ty1 (Just inline) phases
=====================================
libraries/template-haskell/Language/Haskell/TH/Quote.hs
=====================================
@@ -19,12 +19,12 @@ module Language.Haskell.TH.Quote
, namedDefaultQuasiQuoter
, defaultQuasiQuoter
-- * For backwards compatibility
- ,dataToQa, dataToExpQ, dataToPatQ
+ , dataToQa, dataToExpQ, dataToPatQ
) where
import GHC.Boot.TH.Syntax
import GHC.Boot.TH.Quote
-import GHC.Boot.TH.Lift
+import Language.Haskell.TH.Syntax (dataToQa, dataToExpQ, dataToPatQ)
-- | 'quoteFile' takes a 'QuasiQuoter' and lifts it into one that read
=====================================
libraries/template-haskell/Language/Haskell/TH/Syntax.hs
=====================================
@@ -1,6 +1,8 @@
{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
-{-# LANGUAGE Safe #-}
+{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE UnboxedTuples #-}
module Language.Haskell.TH.Syntax (
@@ -190,19 +192,267 @@ module Language.Haskell.TH.Syntax (
nothingName,
rightName,
trueName,
+ -- * Notes
+ -- ** Unresolved Infix
+ -- $infix
)
where
import GHC.Boot.TH.Lift
import GHC.Boot.TH.Syntax
import System.FilePath
+import Data.Data hiding (Fixity(..))
+import Data.List.NonEmpty (NonEmpty(..))
+import GHC.Lexeme ( startsVarSym, startsVarId )
-- This module completely re-exports 'GHC.Boot.TH.Syntax',
-- and exports additionally functions that depend on filepath.
+-- |
+addForeignFile :: ForeignSrcLang -> String -> Q ()
+addForeignFile = addForeignSource
+{-# DEPRECATED addForeignFile
+ "Use 'Language.Haskell.TH.Syntax.addForeignSource' instead"
+ #-} -- deprecated in 8.6
+
-- | The input is a filepath, which if relative is offset by the package root.
makeRelativeToProject :: FilePath -> Q FilePath
makeRelativeToProject fp | isRelative fp = do
root <- getPackageRoot
return (root </> fp)
makeRelativeToProject fp = return fp
+
+trueName, falseName :: Name
+trueName = 'True
+falseName = 'False
+
+nothingName, justName :: Name
+nothingName = 'Nothing
+justName = 'Just
+
+leftName, rightName :: Name
+leftName = 'Left
+rightName = 'Right
+
+nonemptyName :: Name
+nonemptyName = '(:|)
+
+-----------------------------------------------------
+--
+-- Generic Lift implementations
+--
+-----------------------------------------------------
+
+-- | 'dataToQa' is an internal utility function for constructing generic
+-- conversion functions from types with 'Data' instances to various
+-- quasi-quoting representations. See the source of 'dataToExpQ' and
+-- 'dataToPatQ' for two example usages: @mkCon@, @mkLit@
+-- and @appQ@ are overloadable to account for different syntax for
+-- expressions and patterns; @antiQ@ allows you to override type-specific
+-- cases, a common usage is just @const Nothing@, which results in
+-- no overloading.
+dataToQa :: forall m a k q. (Quote m, Data a)
+ => (Name -> k)
+ -> (Lit -> m q)
+ -> (k -> [m q] -> m q)
+ -> (forall b . Data b => b -> Maybe (m q))
+ -> a
+ -> m q
+dataToQa mkCon mkLit appCon antiQ t =
+ case antiQ t of
+ Nothing ->
+ case constrRep constr of
+ AlgConstr _ ->
+ appCon (mkCon funOrConName) conArgs
+ where
+ funOrConName :: Name
+ funOrConName =
+ case showConstr constr of
+ "(:)" -> Name (mkOccName ":")
+ (NameG DataName
+ (mkPkgName "ghc-internal")
+ (mkModName "GHC.Internal.Types"))
+ con@"[]" -> Name (mkOccName con)
+ (NameG DataName
+ (mkPkgName "ghc-internal")
+ (mkModName "GHC.Internal.Types"))
+ con@('(':_) -> Name (mkOccName con)
+ (NameG DataName
+ (mkPkgName "ghc-internal")
+ (mkModName "GHC.Internal.Tuple"))
+
+ -- Tricky case: see Note [Data for non-algebraic types]
+ fun@(x:_) | startsVarSym x || startsVarId x
+ -> mkNameG_v tyconPkg tyconMod fun
+ con -> mkNameG_d tyconPkg tyconMod con
+
+ where
+ tycon :: TyCon
+ tycon = (typeRepTyCon . typeOf) t
+
+ tyconPkg, tyconMod :: String
+ tyconPkg = tyConPackage tycon
+ tyconMod = tyConModule tycon
+
+ conArgs :: [m q]
+ conArgs = gmapQ (dataToQa mkCon mkLit appCon antiQ) t
+ IntConstr n ->
+ mkLit $ IntegerL n
+ FloatConstr n ->
+ mkLit $ RationalL n
+ CharConstr c ->
+ mkLit $ CharL c
+ where
+ constr :: Constr
+ constr = toConstr t
+
+ Just y -> y
+
+
+{- Note [Data for non-algebraic types]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Class Data was originally intended for algebraic data types. But
+it is possible to use it for abstract types too. For example, in
+package `text` we find
+
+ instance Data Text where
+ ...
+ toConstr _ = packConstr
+
+ packConstr :: Constr
+ packConstr = mkConstr textDataType "pack" [] Prefix
+
+Here `packConstr` isn't a real data constructor, it's an ordinary
+function. Two complications
+
+* In such a case, we must take care to build the Name using
+ mkNameG_v (for values), not mkNameG_d (for data constructors).
+ See #10796.
+
+* The pseudo-constructor is named only by its string, here "pack".
+ But 'dataToQa' needs the TyCon of its defining module, and has
+ to assume it's defined in the same module as the TyCon itself.
+ But nothing enforces that; #12596 shows what goes wrong if
+ "pack" is defined in a different module than the data type "Text".
+ -}
+
+-- | A typed variant of 'dataToExpQ'.
+dataToCodeQ :: (Quote m, Data a)
+ => (forall b . Data b => b -> Maybe (Code m b))
+ -> a -> Code m a
+dataToCodeQ f = unsafeCodeCoerce . dataToExpQ (fmap unTypeCode . f)
+
+-- | 'dataToExpQ' converts a value to a 'Exp' representation of the
+-- same value, in the SYB style. It is generalized to take a function
+-- override type-specific cases; see 'liftData' for a more commonly
+-- used variant.
+dataToExpQ :: (Quote m, Data a)
+ => (forall b . Data b => b -> Maybe (m Exp))
+ -> a
+ -> m Exp
+dataToExpQ = dataToQa varOrConE litE (foldl appE)
+ where
+ -- Make sure that VarE is used if the Constr value relies on a
+ -- function underneath the surface (instead of a constructor).
+ -- See #10796.
+ varOrConE s =
+ case nameSpace s of
+ Just VarName -> return (VarE s)
+ Just (FldName {}) -> return (VarE s)
+ Just DataName -> return (ConE s)
+ _ -> error $ "Can't construct an expression from name "
+ ++ showName s
+ appE x y = do { a <- x; b <- y; return (AppE a b)}
+ litE c = return (LitE c)
+
+-- | A typed variant of 'liftData'.
+liftDataTyped :: (Quote m, Data a) => a -> Code m a
+liftDataTyped = dataToCodeQ (const Nothing)
+
+-- | 'liftData' is a variant of 'lift' in the 'Lift' type class which
+-- works for any type with a 'Data' instance.
+liftData :: (Quote m, Data a) => a -> m Exp
+liftData = dataToExpQ (const Nothing)
+
+-- | 'dataToPatQ' converts a value to a 'Pat' representation of the same
+-- value, in the SYB style. It takes a function to handle type-specific cases,
+-- alternatively, pass @const Nothing@ to get default behavior.
+dataToPatQ :: (Quote m, Data a)
+ => (forall b . Data b => b -> Maybe (m Pat))
+ -> a
+ -> m Pat
+dataToPatQ = dataToQa id litP conP
+ where litP l = return (LitP l)
+ conP n ps =
+ case nameSpace n of
+ Just DataName -> do
+ ps' <- sequence ps
+ return (ConP n [] ps')
+ _ -> error $ "Can't construct a pattern from name "
+ ++ showName n
+
+{-
+Note [Unresolved infix]
+~~~~~~~~~~~~~~~~~~~~~~~
+-}
+{- $infix #infix#
+
+When implementing antiquotation for quasiquoters, one often wants
+to parse strings into expressions:
+
+> parse :: String -> Maybe Exp
+
+But how should we parse @a + b * c@? If we don't know the fixities of
+@+@ and @*@, we don't know whether to parse it as @a + (b * c)@ or @(a
++ b) * c@.
+
+In cases like this, use 'UInfixE', 'UInfixP', 'UInfixT', or 'PromotedUInfixT',
+which stand for \"unresolved infix expression / pattern / type / promoted
+constructor\", respectively. When the compiler is given a splice containing a
+tree of @UInfixE@ applications such as
+
+> UInfixE
+> (UInfixE e1 op1 e2)
+> op2
+> (UInfixE e3 op3 e4)
+
+it will look up and the fixities of the relevant operators and
+reassociate the tree as necessary.
+
+ * trees will not be reassociated across 'ParensE', 'ParensP', or 'ParensT',
+ which are of use for parsing expressions like
+
+ > (a + b * c) + d * e
+
+ * 'InfixE', 'InfixP', 'InfixT', and 'PromotedInfixT' expressions are never
+ reassociated.
+
+ * The 'UInfixE' constructor doesn't support sections. Sections
+ such as @(a *)@ have no ambiguity, so 'InfixE' suffices. For longer
+ sections such as @(a + b * c -)@, use an 'InfixE' constructor for the
+ outer-most section, and use 'UInfixE' constructors for all
+ other operators:
+
+ > InfixE
+ > Just (UInfixE ...a + b * c...)
+ > op
+ > Nothing
+
+ Sections such as @(a + b +)@ and @((a + b) +)@ should be rendered
+ into 'Exp's differently:
+
+ > (+ a + b) ---> InfixE Nothing + (Just $ UInfixE a + b)
+ > -- will result in a fixity error if (+) is left-infix
+ > (+ (a + b)) ---> InfixE Nothing + (Just $ ParensE $ UInfixE a + b)
+ > -- no fixity errors
+
+ * Quoted expressions such as
+
+ > [| a * b + c |] :: Q Exp
+ > [p| a : b : c |] :: Q Pat
+ > [t| T + T |] :: Q Type
+
+ will never contain 'UInfixE', 'UInfixP', 'UInfixT', 'PromotedUInfixT',
+ 'InfixT', 'PromotedInfixT, 'ParensE', 'ParensP', or 'ParensT' constructors.
+
+-}
=====================================
libraries/template-haskell/tests/all.T
=====================================
@@ -1,4 +1,4 @@
# difficult to test TH with profiling, because we have to build twice
-test('dataToExpQUnit', [omit_ways(prof_ways), req_th], compile, ['-v0'])
-test('dataToCodeQUnit', [omit_ways(prof_ways), req_th], compile, ['-v0'])
+test('dataToExpQUnit', [omit_ways(prof_ways), req_th], compile, ['-package template-haskell -v0'])
+test('dataToCodeQUnit', [omit_ways(prof_ways), req_th], compile, ['-package template-haskell -v0'])
test('pragCompletePpr', [omit_ways(prof_ways), req_th], compile_and_run, [''])
=====================================
testsuite/tests/interface-stability/template-haskell-exports.stdout
=====================================
@@ -1375,7 +1375,7 @@ module Language.Haskell.TH.Quote where
quoteFile :: QuasiQuoter -> QuasiQuoter
module Language.Haskell.TH.Syntax where
- -- Safety: Safe
+ -- Safety: Trustworthy
type AnnLookup :: *
data AnnLookup = AnnLookupModule Module | AnnLookupName Name
type AnnTarget :: *
=====================================
testsuite/tests/quasiquotation/T4491/test.T
=====================================
@@ -7,4 +7,4 @@ test('T4491',
# the TH way
only_ways([config.ghc_th_way]),
],
- compile_and_run, [''])
+ compile_and_run, ['-package template-haskell'])
=====================================
testsuite/tests/th/Makefile
=====================================
@@ -9,8 +9,8 @@ T2386:
'$(TEST_HC)' $(TEST_HC_OPTS) $(ghcThWayFlags) -v0 -c T2386.hs
T7445:
- '$(TEST_HC)' $(TEST_HC_OPTS) $(ghcThWayFlags) -v0 -c T7445a.hs
- '$(TEST_HC)' $(TEST_HC_OPTS) $(ghcThWayFlags) -v0 -c T7445.hs
+ '$(TEST_HC)' $(TEST_HC_OPTS) $(ghcThWayFlags) -package template-haskell -v0 -c T7445a.hs
+ '$(TEST_HC)' $(TEST_HC_OPTS) $(ghcThWayFlags) -package template-haskell -v0 -c T7445.hs
HC_OPTS = -XTemplateHaskell -package template-haskell
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/91310ad0a7672dbe865f79a2f446d8…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/91310ad0a7672dbe865f79a2f446d8…
You're receiving this email because of your account on gitlab.haskell.org.
1
0