
13 Aug '25
Ben Gamari pushed to branch wip/backports-9.14 at Glasgow Haskell Compiler / GHC
Commits:
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)
- - - - -
5b1d9b41 by Ben Gamari at 2025-08-12T12:45:20-04:00
configure: Drop probing of ld.gold
As noted in #25716, `gold` has been dropped from binutils-2.44.
Fixes #25716.
Metric Increase:
size_hello_artifact_gzip
size_hello_unicode_gzip
ghc_prim_so
(cherry picked from commit c635f164cb62bcb3f34166adc24e5a9437415311)
- - - - -
a444cab6 by fendor at 2025-08-13T09:20:59-04:00
Bump GHC on darwin CI to 9.10.1
(cherry picked from commit 358bc4fc8324a0685f336142d0d608cbd51d54f9)
- - - - -
2391e2cf by Zubin Duggal at 2025-08-13T09:59:41-04:00
ci: upgrade bootstrap compiler on windows to 9.10.1
(cherry picked from commit c8d76a2994b8620c54adc2069f4728135d6b5059)
- - - - -
db5147a2 by Ben Gamari at 2025-08-13T10:01:43-04:00
Accept performance shifts
Metric Increase:
WWRec
- - - - -
47 changed files:
- .gitlab/darwin/toolchain.nix
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/Driver/Main.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToJS/Prim.hs
- compiler/GHC/Types/Name/Cache.hs
- libraries/base/base.cabal.in
- libraries/base/changelog.md
- libraries/base/src/GHC/Exts.hs
- − libraries/base/src/GHC/IOPort.hs
- 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/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
- m4/find_ld.m4
- rts/Prelude.h
- rts/PrimOps.cmm
- rts/RtsSymbols.c
- rts/external-symbols.list.in
- rts/include/stg/MiscClosures.h
- rts/include/stg/SMP.h
- rts/win32/AsyncWinIO.c
- rts/win32/libHSghc-internal.def
- testsuite/tests/driver/recomp015/all.T
- testsuite/tests/hiefile/should_run/TestUtils.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/primops/should_run/UnliftedIOPort.hs
- testsuite/tests/primops/should_run/all.T
- utils/genprimopcode/Main.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3381d4ba7529b4b6fd6ffd3e1d78b7…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3381d4ba7529b4b6fd6ffd3e1d78b7…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/fendor/stack-annotation-with-backtraces] Changes to tie everything together
by Hannes Siebenhandl (@fendor) 13 Aug '25
by Hannes Siebenhandl (@fendor) 13 Aug '25
13 Aug '25
Hannes Siebenhandl pushed to branch wip/fendor/stack-annotation-with-backtraces at Glasgow Haskell Compiler / GHC
Commits:
022ce2bc by fendor at 2025-08-13T15:40:03+02:00
Changes to tie everything together
- - - - -
5 changed files:
- libraries/ghc-experimental/src/GHC/Stack/Annotation/Experimental.hs
- libraries/ghc-internal/ghc-internal.cabal.in
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- + libraries/ghc-internal/src/GHC/Internal/Stack/Annotation.hs
- libraries/ghc-internal/src/GHC/Internal/Stack/Decode.hs
Changes:
=====================================
libraries/ghc-experimental/src/GHC/Stack/Annotation/Experimental.hs
=====================================
@@ -27,29 +27,12 @@ import Data.Typeable
import GHC.Exts
import GHC.IO
import GHC.Internal.Stack
-
--- ----------------------------------------------------------------------------
--- StackAnnotation
--- ----------------------------------------------------------------------------
-
--- | 'StackAnnotation's are types which can be pushed onto the call stack
--- as the payload of 'AnnFrame' stack frames.
---
-class StackAnnotation a where
- displayStackAnnotation :: a -> String
+import GHC.Internal.Stack.Annotation
-- ----------------------------------------------------------------------------
-- Annotations
-- ----------------------------------------------------------------------------
--- |
--- The @SomeStackAnnotation@ type is the root of the stack annotation type hierarchy.
--- When the call stack is annotated with a value of type @a@, behind the scenes it is
--- encapsulated in a @SomeStackAnnotation@.
---
-data SomeStackAnnotation where
- SomeStackAnnotation :: forall a. (Typeable a, StackAnnotation a) => a -> SomeStackAnnotation
-
instance StackAnnotation SomeStackAnnotation where
displayStackAnnotation (SomeStackAnnotation a) = displayStackAnnotation a
=====================================
libraries/ghc-internal/ghc-internal.cabal.in
=====================================
@@ -295,6 +295,7 @@ Library
GHC.Internal.Stable
GHC.Internal.StableName
GHC.Internal.Stack
+ GHC.Internal.Stack.Annotation
GHC.Internal.Stack.CCS
GHC.Internal.Stack.CloneStack
GHC.Internal.Stack.Constants
=====================================
libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
=====================================
@@ -11,7 +11,7 @@ import GHC.Internal.IORef
import GHC.Internal.IO.Unsafe (unsafePerformIO)
import GHC.Internal.Exception.Context
import GHC.Internal.Ptr
-import GHC.Internal.Data.Maybe (fromMaybe)
+import GHC.Internal.Data.Maybe (fromMaybe, mapMaybe)
import GHC.Internal.Stack.Types as GHC.Stack (CallStack, HasCallStack)
import qualified GHC.Internal.Stack as HCS
import qualified GHC.Internal.ExecutionStack.Internal as ExecStack
@@ -144,7 +144,7 @@ displayBacktraces bts = concat
displayExec = unlines . map (indent 2 . flip ExecStack.showLocation "") . fromMaybe [] . ExecStack.stackFrames
-- The unsafePerformIO here is safe as 'StackSnapshot' makes sure neither the stack frames nor
-- references closures can be garbage collected.
- displayIpe = unlines . map (indent 2 . CloneStack.prettyStackEntry) . unsafePerformIO . CloneStack.decode
+ displayIpe = unlines . mapMaybe (fmap (indent 2) . CloneStack.prettyStackFrameWithIpe) . unsafePerformIO . CloneStack.decodeStackWithIpe
displayHsc = unlines . map (indent 2 . prettyCallSite) . HCS.getCallStack
where prettyCallSite (f, loc) = f ++ ", called at " ++ HCS.prettySrcLoc loc
=====================================
libraries/ghc-internal/src/GHC/Internal/Stack/Annotation.hs
=====================================
@@ -0,0 +1,28 @@
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+module GHC.Internal.Stack.Annotation where
+
+import GHC.Internal.Base
+import GHC.Internal.Data.Typeable
+
+-- ----------------------------------------------------------------------------
+-- StackAnnotation
+-- ----------------------------------------------------------------------------
+
+-- | 'StackAnnotation's are types which can be pushed onto the call stack
+-- as the payload of 'AnnFrame' stack frames.
+--
+class StackAnnotation a where
+ displayStackAnnotation :: a -> String
+
+-- ----------------------------------------------------------------------------
+-- Annotations
+-- ----------------------------------------------------------------------------
+
+-- |
+-- The @SomeStackAnnotation@ type is the root of the stack annotation type hierarchy.
+-- When the call stack is annotated with a value of type @a@, behind the scenes it is
+-- encapsulated in a @SomeStackAnnotation@.
+--
+data SomeStackAnnotation where
+ SomeStackAnnotation :: forall a. (Typeable a, StackAnnotation a) => a -> SomeStackAnnotation
=====================================
libraries/ghc-internal/src/GHC/Internal/Stack/Decode.hs
=====================================
@@ -4,6 +4,7 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GHCForeignImportPrim #-}
{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
@@ -40,6 +41,7 @@ import GHC.Internal.Data.Tuple
import GHC.Internal.Foreign.Ptr
import GHC.Internal.Foreign.Storable
import GHC.Internal.Exts
+import GHC.Internal.Unsafe.Coerce
import GHC.Internal.ClosureTypes
import GHC.Internal.Heap.Closures
@@ -53,6 +55,7 @@ import GHC.Internal.Heap.Closures
)
import GHC.Internal.Heap.Constants (wORD_SIZE_IN_BITS)
import GHC.Internal.Heap.InfoTable
+import GHC.Internal.Stack.Annotation
import GHC.Internal.Stack.Constants
import GHC.Internal.Stack.CloneStack
import GHC.Internal.InfoProv.Types (InfoProv (..), ipLoc, lookupIPE)
@@ -443,7 +446,7 @@ unpackStackFrameTo (StackSnapshot stackSnapshot#, index) unpackUnderflowFrame fi
ANN_FRAME ->
let annotation = getClosureBox stackSnapshot# (index + offsetStgAnnFrameAnn)
in
- mkStackFrameResult $
+ mkStackFrameResult $
AnnFrame
{ info_tbl = info,
annotation = annotation
@@ -561,9 +564,16 @@ decodeStackWithFrameUnpack unpackFrame (StackSnapshot stack#) = do
-- Pretty printing functions for stack entires, stack frames and provenance info
-- ----------------------------------------------------------------------------
+
prettyStackFrameWithIpe :: (StackFrame, Maybe InfoProv) -> Maybe String
-prettyStackFrameWithIpe (_frame, mipe) =
- (prettyStackEntry . toStackEntry) <$> mipe
+prettyStackFrameWithIpe (frame, mipe) =
+ case frame of
+ AnnFrame {annotation = Box someStackAnno } ->
+ case unsafeCoerce someStackAnno of
+ SomeStackAnnotation ann ->
+ Just $ displayStackAnnotation ann
+ _ ->
+ (prettyStackEntry . toStackEntry) <$> mipe
prettyStackEntry :: StackEntry -> String
prettyStackEntry (StackEntry {moduleName=mod_nm, functionName=fun_nm, srcLoc=loc}) =
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/022ce2bcfa4100088279bbaabc62015…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/022ce2bcfa4100088279bbaabc62015…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 21 commits: Make injecting implicit bindings into its own pass
by Marge Bot (@marge-bot) 13 Aug '25
by Marge Bot (@marge-bot) 13 Aug '25
13 Aug '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
08002896 by Simon Peyton Jones at 2025-08-13T09:06:37-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
- - - - -
1692be06 by Simon Peyton Jones at 2025-08-13T09:06:37-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
T16577
T21839r
T5642
Metric Increase:
T15164
T21839c
T3294
T5321FD
T5321Fun
WWRec
- - - - -
974a2fbb by Simon Peyton Jones at 2025-08-13T09:06:37-04:00
Slight improvement to pre/postInlineUnconditionally
Avoids an extra simplifier iteration
- - - - -
b76b865a by Simon Peyton Jones at 2025-08-13T09:06:37-04:00
Fix a long-standing assertion error in normSplitTyConApp_maybe
- - - - -
07604da1 by Simon Peyton Jones at 2025-08-13T09:06:37-04:00
Add comment to coercion optimiser
- - - - -
2552d21d by Florian Ragwitz at 2025-08-13T09:06:38-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.
- - - - -
bcf2456b by Florian Ragwitz at 2025-08-13T09:06:39-04:00
Add release notes for 9.16.1 and move description of latest HPC changes there.
- - - - -
2608f4d6 by Ben Gamari at 2025-08-13T09:06:40-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.
- - - - -
f26b7b23 by Andreas Klebinger at 2025-08-13T09:06:42-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
- - - - -
8ff41905 by fendor at 2025-08-13T09:06:44-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`).
- - - - -
5803957a by fendor at 2025-08-13T09:06:44-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.
- - - - -
a313e44c by fendor at 2025-08-13T09:06:44-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.
- - - - -
e0173cab by Reed Mullanix at 2025-08-13T09:06:51-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
- - - - -
b0c5d896 by Simon Hengel at 2025-08-13T09:06:52-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
- - - - -
cdd30d38 by Recursion Ninja at 2025-08-13T09:06:53-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#
- - - - -
dbaeaa36 by Zubin Duggal at 2025-08-13T09:06:55-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
- - - - -
1b3d77c1 by Simon Hengel at 2025-08-13T09:06:57-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`.
- - - - -
87cc8c93 by Teo Camarasu at 2025-08-13T09:06:58-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>
- - - - -
7a1ee1e9 by Teo Camarasu at 2025-08-13T09:06:58-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
- - - - -
efc20739 by Oleg Grenrus at 2025-08-13T09:07:00-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.
- - - - -
f92c69fa by Sylvain Henry at 2025-08-13T09:07:21-04:00
Fix Data.List unqualified import warning
- - - - -
169 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/release-notes.rst
- 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/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
- rts/Messages.c
- rts/StgMiscClosures.cmm
- rts/Updates.h
- rts/external-symbols.list.in
- rts/rts.cabal
- 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/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/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/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/165247dcd2fe312e8dbd9d2c34c996…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/165247dcd2fe312e8dbd9d2c34c996…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/ubxsumtag] 59 commits: level imports: Fix infinite loop with cyclic module imports
by Luite Stegeman (@luite) 13 Aug '25
by Luite Stegeman (@luite) 13 Aug '25
13 Aug '25
Luite Stegeman pushed to branch wip/ubxsumtag at Glasgow Haskell Compiler / GHC
Commits:
8b731e3c by Matthew Pickering at 2025-07-21T13:36:43-04:00
level imports: Fix infinite loop with cyclic module imports
I didn't anticipate that downsweep would run before we checked for
cyclic imports. Therefore we need to use the reachability function which
handles cyclic graphs.
Fixes #26087
- - - - -
d751a9f1 by Pierre Thierry at 2025-07-21T13:37:28-04:00
Fix documentation about deriving from generics
- - - - -
f8d9d016 by Andrew Lelechenko at 2025-07-22T21:13:28-04:00
Fix issues with toRational for types capable to represent infinite and not-a-number values
This commit fixes all of the following pitfalls:
> toRational (read "Infinity" :: Double)
179769313486231590772930519078902473361797697894230657273430081157732675805500963132708477322407536021120113879871393357658789768814416622492847430639474124377767893424865485276302219601246094119453082952085005768838150682342462881473913110540827237163350510684586298239947245938479716304835356329624224137216 % 1
> toRational (read "NaN" :: Double)
269653970229347386159395778618353710042696546841345985910145121736599013708251444699062715983611304031680170819807090036488184653221624933739271145959211186566651840137298227914453329401869141179179624428127508653257226023513694322210869665811240855745025766026879447359920868907719574457253034494436336205824 % 1
> realToFrac (read "NaN" :: Double) -- With -O0
Infinity
> realToFrac (read "NaN" :: Double) -- With -O1
NaN
> realToFrac (read "NaN" :: Double) :: CDouble
Infinity
> realToFrac (read "NaN" :: CDouble) :: Double
Infinity
Implements https://github.com/haskell/core-libraries-committee/issues/338
- - - - -
5dabc718 by Zubin Duggal at 2025-07-22T21:14:10-04:00
haddock: Don't warn about missing link destinations for derived names.
Fixes #26114
- - - - -
9c3a0937 by Matthew Pickering at 2025-07-22T21:14:52-04:00
template haskell: use a precise condition when implicitly lifting
Implicit lifting corrects a level error by replacing references to `x`
with `$(lift x)`, therefore you can use a level `n` binding at level `n
+ 1`, if it can be lifted.
Therefore, we now have a precise check that the use level is 1 more than
the bind level.
Before this bug was not observable as you only had 0 and 1 contexts but
it is easily evident when using explicit level imports.
Fixes #26088
- - - - -
5144b22f by Andreas Klebinger at 2025-07-22T21:15:34-04:00
Add since tag and more docs for do-clever-arg-eta-expansion
Fixes #26113
- - - - -
c865623b by Andreas Klebinger at 2025-07-22T21:15:34-04:00
Add since tag for -fexpose-overloaded-unfoldings
Fixes #26112
- - - - -
49a44ab7 by Simon Hengel at 2025-07-23T17:59:55+07:00
Refactor GHC.Driver.Errors.printMessages
- - - - -
84711c39 by Simon Hengel at 2025-07-23T18:27:34+07:00
Respect `-fdiagnostics-as-json` for error messages from pre-processors
(fixes #25480)
- - - - -
d046b5ab by Simon Hengel at 2025-07-24T06:12:05-04:00
Include the rendered message in -fdiagnostics-as-json output
This implements #26173.
- - - - -
d2b89603 by Ben Gamari at 2025-07-24T06:12:47-04:00
rts/Interpreter: Factor out ctoi tuple info tables into data
Instead of a massive case let's put this into data which we can reuse
elsewhere.
- - - - -
4bc78496 by Sebastian Graf at 2025-07-24T16:19:34-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.
- - - - -
0a583689 by Sylvain Henry at 2025-07-24T16:20:26-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.
- - - - -
a49eca26 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Renaming around predicate types
.. we were (as it turned out) abstracting over
type-class selectors in SPECIALISATION rules!
Wibble isEqPred
- - - - -
f80375dd by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Refactor of Specialise.hs
This patch just tidies up `specHeader` a bit, removing one
of its many results, and adding some comments.
No change in behaviour.
Also add a few more `HasDebugCallStack` contexts.
- - - - -
1bd12371 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Improve treatment of SPECIALISE pragmas -- again!
This MR does another major refactor of the way that SPECIALISE
pragmas work, to fix #26115, #26116, #26117.
* We now /always/ solve forall-constraints in an all-or-nothing way.
See Note [Solving a Wanted forall-constraint] in GHC.Tc.Solver.Solve
This means we might have unsolved quantified constraints, which need
to be reported. See `inert_insts` in `getUnsolvedInerts`.
* I refactored the short-cut solver for type classes to work by
recursively calling the solver rather than by having a little baby
solver that kept being not clever enough.
See Note [Shortcut solving] in GHC.Tc.Solver.Dict
* I totally rewrote the desugaring of SPECIALISE pragmas, again.
The new story is in Note [Desugaring new-form SPECIALISE pragmas]
in GHC.HsToCore.Binds
Both old-form and new-form SPECIALISE pragmas now route through the same
function `dsSpec_help`. The tricky function `decomposeRuleLhs` is now used only
for user-written RULES, not for SPECIALISE pragmas.
* I improved `solveOneFromTheOther` to account for rewriter sets. Previously
it would solve a non-rewritten dict from a rewritten one. For equalities
we were already dealing with this, in
Some incidental refactoring
* A small refactor: `ebv_tcvs` in `EvBindsBar` now has a list of coercions, rather
than a set of tyvars. We just delay taking the free vars.
* GHC.Core.FVs.exprFVs now returns /all/ free vars.
Use `exprLocalFVs` for Local vars.
Reason: I wanted another variant for /evidence/ variables.
* Ues `EvId` in preference to `EvVar`. (Evidence variables are always Ids.)
Rename `isEvVar` to `isEvId`.
* I moved `inert_safehask` out of `InertCans` and into `InertSet` where it
more properly belongs.
Compiler-perf changes:
* There was a palpable bug (#26117) which this MR fixes in
newWantedEvVar, which bypassed all the subtle overlapping-Given
and shortcutting logic. (See the new `newWantedEvVar`.) Fixing this
but leads to extra dictionary bindings; they are optimised away quickly
but they made CoOpt_Read allocate 3.6% more.
* Hpapily T15164 improves.
* The net compiler-allocation change is 0.0%
Metric Decrease:
T15164
Metric Increase:
CoOpt_Read
T12425
- - - - -
953fd8f1 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Solve forall-constraints immediately, or not at all
This MR refactors the constraint solver to solve forall-constraints immediately,
rather than emitting an implication constraint to be solved later.
The most immediate motivation was that when solving quantified constraints
in SPECIALISE pragmas, we really really don't want to leave behind half-
solved implications. Also it's in tune with the approach of the new
short-cut solver, which recursively invokes the solver.
It /also/ saves quite a bit of plumbing; e.g
- The `wl_implics` field of `WorkList` is gone,
- The types of `solveSimpleWanteds` and friends are simplified.
- An EvFun contains binding, rather than an EvBindsVar ref-cell that
will in the future contain bindings. That makes `evVarsOfTerm`
simpler. Much nicer.
It also improves error messages a bit.
All described in Note [Solving a Wanted forall-constraint] in
GHC.Tc.Solver.Solve.
One tiresome point: in the tricky case of `inferConstraintsCoerceBased`
we make a forall-constraint. This we /do/ want to partially solve, so
we can infer a suitable context. (I'd be quite happy to force the user to
write a context, bt I don't want to change behavior.) So we want to generate
an /implication/ constraint in `emitPredSpecConstraints` rather than a
/forall-constraint/ as we were doing before. Discussed in (WFA3) of
the above Note.
Incidental refactoring
* `GHC.Tc.Deriv.Infer.inferConstraints` was consulting the state monad for
the DerivEnv that the caller had just consulted. Nicer to pass it as an
argument I think, so I have done that. No change in behaviour.
- - - - -
6921ab42 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Remove duplicated code in Ast.hs for evTermFreeVars
This is just a tidy up.
- - - - -
1165f587 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Small tc-tracing changes only
- - - - -
0776ffe0 by Simon Hengel at 2025-07-26T04:54:20-04:00
Respect `-fdiagnostics-as-json` for core diagnostics (see #24113)
- - - - -
cc1116e0 by Andrew Lelechenko at 2025-07-26T04:55:01-04:00
docs: add since pragma to Data.List.NonEmpty.mapMaybe
- - - - -
ee2dc248 by Simon Hengel at 2025-07-31T06:25:35-04:00
Update comments on `OptKind` to reflect the code reality
- - - - -
b029633a by Wen Kokke at 2025-07-31T06:26:21-04:00
rts: Disable --eventlog-flush-interval unless compiled with -threaded.
This commit fixes issue #26222:
Using --eventlog-flush-interval with the non-threaded RTS leads to eventlog corruption.
https://gitlab.haskell.org/ghc/ghc/-/issues/26222
This commit makes three changes when code is compiled against the non-threaded RTS:
1. It disables the --eventlog-flush-interval flag.
2. It disables the documentation for the --eventlog-flush-interval flag.
3. It disables the relevant state from RtsConfig and code from Timer.
4. It updates the entry for --eventlog-flush-interval in the users guide.
- - - - -
31159f1d by Wen Kokke at 2025-07-31T06:26:21-04:00
rts: Split T20006 into tests with and without -threaded
- - - - -
618687ef by Simon Hengel at 2025-07-31T06:27:03-04:00
docs/users_guide/win32-dlls.rst: Remove references to `readline`
- - - - -
083e40f1 by Rodrigo Mesquita at 2025-08-01T04:38:23-04:00
debugger: Uniquely identify breakpoints by internal id
Since b85b11994e0130ff2401dd4bbdf52330e0bcf776 (support inlining
breakpoints), a breakpoint has been identified at runtime by *two* pairs
of <module,index>.
- The first, aka a 'BreakpointId', uniquely identifies a breakpoint in
the source of a module by using the Tick index. A Tick index can index
into ModBreaks.modBreaks_xxx to fetch source-level information about
where that tick originated.
- When a user specifies e.g. a line breakpoint using :break, we'll reverse
engineer what a Tick index for that line
- We update the `BreakArray` of that module (got from the
LoaderState) at that tick index to `breakOn`.
- A BCO we can stop at is headed by a BRK_FUN instruction. This
instruction stores in an operand the `tick index` it is associated
to. We look it up in the associated `BreakArray` (also an operand)
and check wheter it was set to `breakOn`.
- The second, aka the `ibi_info_mod` + `ibi_info_ix` of the
`InternalBreakpointId`, uniquely index into the `imodBreaks_breakInfo`
-- the information we gathered during code generation about the
existing breakpoint *ocurrences*.
- Note that with optimisation there may be many occurrences of the
same source-tick-breakpoint across different modules. The
`ibi_info_ix` is unique per occurrence, but the `bi_tick_ix` may be
shared. See Note [Breakpoint identifiers] about this.
- Note that besides the tick ids, info ids are also stored in
`BRK_FUN` so the break handler can refer to the associated
`CgBreakInfo`.
In light of that, the driving changes come from the desire to have the
info_id uniquely identify the breakpoint at runtime, and the source tick
id being derived from it:
- An InternalBreakpointId should uniquely identify a breakpoint just
from the code-generation identifiers of `ibi_info_ix` and `ibi_info_mod`.
So we drop `ibi_tick_mod` and `ibi_tick_ix`.
- A BRK_FUN instruction need only record the "internal breakpoint id",
not the tick-level id.
So we drop the tick mod and tick index operands.
- A BreakArray should be indexed by InternalBreakpointId rather than
BreakpointId
That means we need to do some more work when setting a breakpoint.
Specifically, we need to figure out the internal ids (occurrences of a
breakpoint) from the source-level BreakpointId we want to set the
breakpoint at (recall :break refers to breaks at the source level).
Besides this change being an improvement to the handling of breakpoints
(it's clearer to have a single unique identifier than two competing
ones), it unlocks the possibility of generating "internal" breakpoints
during Cg (needed for #26042).
It should also be easier to introduce multi-threaded-aware `BreakArrays`
following this change (needed for #26064).
Se also the new Note [ModBreaks vs InternalModBreaks]
On i386-linux:
-------------------------
Metric Decrease:
interpreter_steplocal
-------------------------
- - - - -
bf03bbaa by Simon Hengel at 2025-08-01T04:39:05-04:00
Don't use MCDiagnostic for `ghcExit`
This changes the error message of `ghcExit` from
```
<no location info>: error:
Compilation had errors
```
to
```
Compilation had errors
```
- - - - -
a889ec75 by Simon Hengel at 2025-08-01T04:39:05-04:00
Respect `-fdiagnostics-as-json` for driver diagnostics (see #24113)
- - - - -
81577fe7 by Ben Gamari at 2025-08-02T04:29:39-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.
- - - - -
01136779 by Andreas Klebinger at 2025-08-02T04:30:20-04:00
rts: Support COFF BigObj files in archives.
- - - - -
1f9e4f54 by Stephen Morgan at 2025-08-03T15:14:08+10:00
refactor: Modify Data.List.sortOn to use (>) instead of compare. (#26184)
This lets a more efficient (>) operation be used if one exists.
This is technically a breaking change for malformed Ord instances, where
x > y is not equivalent to compare x y == GT.
Discussed by the CLC in issue #332: https://github.com/haskell/core-libraries-committee/issues/332
- - - - -
4f6bc9cf by fendor at 2025-08-04T17:50:06-04:00
Revert "base: Expose Backtraces constructor and fields"
This reverts commit 17db44c5b32fff82ea988fa4f1a233d1a27bdf57.
- - - - -
bcdec657 by Zubin Duggal at 2025-08-05T10:37:29+05:30
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
- - - - -
57d3b4a8 by Andrew Lelechenko at 2025-08-05T18:36:31-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.
- - - - -
c2a78cea by Peng Fan at 2025-08-05T18:37:27-04:00
NCG/LA64: implement atomic write with finer-grained DBAR hints
Signed-off-by: Peng Fan <fanpeng(a)loongson.cn>
- - - - -
95231c8e by Teo Camarasu at 2025-08-06T08:35:58-04:00
CODEOWNERS: add CLC as codeowner of base
We also remove hvr, since I think he is no longer active
- - - - -
77df0ded by Andrew Lelechenko at 2025-08-06T08:36:39-04:00
Bump submodule text to 2.1.3
- - - - -
8af260d0 by Nikolaos Chatzikonstantinou at 2025-08-06T08:37:23-04:00
docs: fix internal import in getopt examples
This external-facing doc example shouldn't mention GHC internals when
using 'fromMaybe'.
- - - - -
69cc16ca by Marc Scholten at 2025-08-06T15:51:28-04:00
README: Add note on ghc.nix
- - - - -
93a2f450 by Daniel Díaz at 2025-08-06T15:52:14-04:00
Link to the "Strict Bindings" docs from the linear types docs
Strict Bidings are relevant for the kinds of multiplicity annotations
linear lets support.
- - - - -
246b7853 by Matthew Pickering at 2025-08-07T06:58:30-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
- - - - -
358bc4fc by fendor at 2025-08-07T06:59:12-04:00
Bump GHC on darwin CI to 9.10.1
- - - - -
1903ae35 by Matthew Pickering at 2025-08-07T12:21:10+01:00
ipe: Place strings and metadata into specific .ipe section
By placing the .ipe metadata into a specific section it can be stripped
from the final binary if desired.
```
objcopy --remove-section .ipe <binary>
upx <binary>
```
Towards #21766
- - - - -
c80dd91c by Matthew Pickering at 2025-08-07T12:22:42+01:00
ipe: Place magic word at the start of entries in the .ipe section
The magic word "IPE\nIPE\n" is placed at the start of .ipe sections,
then if the section is stripped, we can check whether the section starts
with the magic word or not to determine whether there is metadata
present or not.
Towards #21766
- - - - -
cab42666 by Matthew Pickering at 2025-08-07T12:22:42+01:00
ipe: Use stable IDs for IPE entries
IPEs have historically been indexed and reported by their address.
This makes it impossible to compare profiles between runs, since the
addresses may change (due to ASLR) and also makes it tricky to separate
out the IPE map from the binary.
This small patch adds a stable identifier for each IPE entry.
The stable identifier is a single 64 bit word. The high-bits are a
per-module identifier and the low bits identify which entry in each
module.
1. When a node is added into the IPE buffer it is assigned a unique
identifier from an incrementing global counter.
2. Each entry already has an index by it's position in the
`IpeBufferListNode`.
The two are combined together by the `IPE_ENTRY_KEY` macro.
Info table profiling uses the stable identifier rather than the address
of the info table.
The benefits of this change are:
* Profiles from different runs can be easily compared
* The metadata can be extracted from the binary (via the eventlog for
example) and then stripped from the executable.
Fixes #21766
- - - - -
2860a9a5 by Simon Peyton Jones at 2025-08-07T20:29:18-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!
- - - - -
2157db2d by sterni at 2025-08-08T15:32:39-04:00
hadrian: enable terminfo if --with-curses-* flags are given
The GHC make build system used to support WITH_TERMINFO in ghc.mk which
allowed controlling whether to build GHC with terminfo or not. hadrian
has replaced this with a system where this is effectively controlled by
the cross-compiling setting (the default WITH_TERMINFO value was bassed
on CrossCompiling, iirc).
This behavior is undesireable in some cases and there is not really a
good way to work around it. Especially for downstream packagers,
modifying this via UserSettings is not really feasible since such a
source file has to be kept in sync with Settings/Default.hs manually
since it can't import Settings.Default or any predefined Flavour
definitions.
To avoid having to add a new setting to cfg/system.config and/or a new
configure flag (though I'm happy to implement both if required), I've
chosen to take --with-curses-* being set explicitly as an indication
that the user wants to have terminfo enabled. This would work for
Nixpkgs which sets these flags [1] as well as haskell.nix [2] (which
goes to some extreme measures [3] [4] to force terminfo in all scenarios).
In general, I'm an advocate for making the GHC build be the same for
native and cross insofar it is possible since it makes packaging GHC and
Haskell related things while still supporting cross much less
compilicated. A more minimal GHC with reduced dependencies should
probably be a specific flavor, not the default.
Partially addresses #26288 by forcing terminfo to be built if the user
explicitly passes configure flags related to it. However, it isn't built
by default when cross-compiling yet nor is there an explicit way to
control the package being built.
[1]: https://github.com/NixOS/nixpkgs/blob/3a7266fcefcb9ce353df49ba3f292d0644376…
[2]: https://github.com/input-output-hk/haskell.nix/blob/6eaafcdf04bab7be745d1aa…
[3]: https://github.com/input-output-hk/haskell.nix/blob/6eaafcdf04bab7be745d1aa…
[4]: https://github.com/input-output-hk/haskell.nix/blob/6eaafcdf04bab7be745d1aa…
- - - - -
b3c31488 by David Feuer at 2025-08-08T15:33:21-04:00
Add default QuasiQuoters
Add `defaultQuasiQuoter` and `namedDefaultQuasiQuoter` to make it easier
to write `QuasiQuoters` that give helpful error messages when they're
used in inappropriate contexts.
Closes #24434.
- - - - -
03555ed8 by Sylvain Henry at 2025-08-10T22:20:57-04:00
Handle non-fractional CmmFloats in Cmm's CBE (#26229)
Since f8d9d016305be355f518c141f6c6d4826f2de9a2, toRational for Float and
Double converts float's infinity and NaN into Rational's infinity and
NaN (respectively 1%0 and 0%0).
Cmm CommonBlockEliminator hashing function needs to take these values
into account as they can appear as literals now. See added testcase.
- - - - -
6c956af3 by J. Ryan Stinnett at 2025-08-10T22:21:42-04:00
Fix extensions list in `DoAndIfThenElse` docs
- - - - -
6dc420b1 by J. Ryan Stinnett at 2025-08-10T22:21:42-04:00
Document status of `RelaxedPolyRec` extension
This adds a brief extension page explaining the status of the
`RelaxedPolyRec` extension. The behaviour of this mode is already
explained elsewhere, so this page is mainly for completeness so that
various lists of extensions have somewhere to point to for this flag.
Fixes #18630
- - - - -
18036d52 by Simon Peyton Jones at 2025-08-11T11:31:20-04:00
Take more care in zonkEqTypes on AppTy/AppTy
This patch fixes #26256.
See Note [zonkEqTypes and the PKTI] in GHC.Tc.Solver.Equality
- - - - -
c8d76a29 by Zubin Duggal at 2025-08-11T11:32:02-04:00
ci: upgrade bootstrap compiler on windows to 9.10.1
- - - - -
34fc50c1 by Ben Gamari at 2025-08-11T13:36:25-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.
- - - - -
56b32c5a by sheaf at 2025-08-12T10:00:19-04:00
Improve deep subsumption
This commit improves the DeepSubsumption sub-typing implementation
in GHC.Tc.Utils.Unify.tc_sub_type_deep by being less eager to fall back
to unification.
For example, we now are properly able to prove the subtyping relationship
((∀ a. a->a) -> Int) -> Bool <= β[tau] Bool
for an unfilled metavariable β. In this case (with an AppTy on the right),
we used to fall back to unification. No longer: now, given that the LHS
is a FunTy and that the RHS is a deep rho type (does not need any instantiation),
we try to make the RHS into a FunTy, viz.
β := (->) γ
We can then continue using covariance & contravariance of the function
arrow, which allows us to prove the subtyping relationship, instead of
trying to unify which would cause us to error out with:
Couldn't match expected type ‘β’ with actual type ‘(->) ((∀ a. a -> a) -> Int)
See Note [FunTy vs non-FunTy case in tc_sub_type_deep] in GHC.Tc.Utils.Unify.
The other main improvement in this patch concerns type inference.
The main subsumption logic happens (before & after this patch) in
GHC.Tc.Gen.App.checkResultTy. However, before this patch, all of the
DeepSubsumption logic only kicked in in 'check' mode, not in 'infer' mode.
This patch adds deep instantiation in the 'infer' mode of checkResultTy
when we are doing deep subsumption, which allows us to accept programs
such as:
f :: Int -> (forall a. a->a)
g :: Int -> Bool -> Bool
test1 b =
case b of
True -> f
False -> g
test2 b =
case b of
True -> g
False -> f
See Note [Deeply instantiate in checkResultTy when inferring].
Finally, we add representation-polymorphism checks to ensure that the
lambda abstractions we introduce when doing subsumption obey the
representation polymorphism invariants of Note [Representation polymorphism invariants]
in GHC.Core. See Note [FunTy vs FunTy case in tc_sub_type_deep].
This is accompanied by a courtesy change to `(<.>) :: HsWrapper -> HsWrapper -> HsWrapper`,
adding the equation:
WpCast c1 <.> WpCast c2 = WpCast (c1 `mkTransCo` c2)
This is useful because mkWpFun does not introduce an eta-expansion when
both of the argument & result wrappers are casts; so this change allows
us to avoid introducing lambda abstractions when casts suffice.
Fixes #26225
- - - - -
d175aff8 by Sylvain Henry at 2025-08-12T10:01:31-04:00
Add regression test for #18619
- - - - -
a3983a26 by Sylvain Henry at 2025-08-12T10:02:20-04:00
RTS: remove some TSAN annotations (#20464)
Use RELAXED_LOAD_ALWAYS macro instead.
- - - - -
0434af81 by Ben Gamari at 2025-08-12T10:03:02-04:00
Bump time submodule to 1.15
Also required bumps of Cabal, directory, and hpc.
- - - - -
0fd3f7b2 by Luite Stegeman at 2025-08-13T11:57:19+02:00
Use slots smaller than word as tag for smaller unboxed sums
This packs unboxed sums more efficiently by allowing
Word8, Word16 and Word32 for the tag field if the number of
constructors is small enough
- - - - -
291 changed files:
- .gitlab/darwin/toolchain.nix
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- CODEOWNERS
- README.md
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/PrimOps/Ids.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/Breakpoints.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Cmm.hs
- compiler/GHC/Cmm/CommonBlockElim.hs
- compiler/GHC/Cmm/Utils.hs
- compiler/GHC/CmmToAsm/LA64/CodeGen.hs
- compiler/GHC/CmmToAsm/PPC/Ppr.hs
- compiler/GHC/CmmToAsm/Ppr.hs
- compiler/GHC/CmmToLlvm/Data.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/Make.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/Monad.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/Unfold/Make.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/CmdLine.hs
- compiler/GHC/Driver/Errors.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Breakpoints.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Pmc/Solver/Types.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Stg/Unarise.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm/InfoTableProv.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToJS/Prim.hs
- compiler/GHC/SysTools/Process.hs
- compiler/GHC/SysTools/Tasks.hs
- compiler/GHC/Tc/Deriv.hs
- compiler/GHC/Tc/Deriv/Infer.hs
- compiler/GHC/Tc/Deriv/Utils.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Rewrite.hs
- compiler/GHC/Tc/Solver/Solve.hs
- + compiler/GHC/Tc/Solver/Solve.hs-boot
- compiler/GHC/Tc/Solver/Types.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Concrete.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Utils/TcType.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Tc/Validity.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/Types/Error.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/Var.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Utils/Error.hs
- compiler/GHC/Utils/Logger.hs
- compiler/ghc.cabal.in
- configure.ac
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/conf.py
- docs/users_guide/debug-info.rst
- + docs/users_guide/diagnostics-as-json-schema-1_2.json
- docs/users_guide/expected-undocumented-flags.txt
- docs/users_guide/exts/doandifthenelse.rst
- docs/users_guide/exts/linear_types.rst
- + docs/users_guide/exts/relaxed_poly_rec.rst
- docs/users_guide/exts/strict.rst
- docs/users_guide/exts/types.rst
- docs/users_guide/runtime_control.rst
- docs/users_guide/using-optimisation.rst
- docs/users_guide/using.rst
- docs/users_guide/win32-dlls.rst
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Monad.hs
- ghc/ghc-bin.cabal.in
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Packages.hs
- hadrian/stack.yaml
- hadrian/stack.yaml.lock
- libraries/Cabal
- libraries/base/base.cabal.in
- libraries/base/changelog.md
- libraries/base/src/Control/Exception/Backtrace.hs
- libraries/base/src/Data/List/NonEmpty.hs
- libraries/base/src/GHC/Exts.hs
- libraries/base/src/GHC/Generics.hs
- − libraries/base/src/GHC/IOPort.hs
- libraries/base/src/System/Console/GetOpt.hs
- libraries/directory
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
- libraries/ghc-internal/ghc-internal.cabal.in
- libraries/ghc-internal/src/GHC/Internal/Data/OldList.hs
- 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/Exts.hs
- libraries/ghc-internal/src/GHC/Internal/Float.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-internal/src/GHC/Internal/Real.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Quote.hs
- libraries/ghc-prim/changelog.md
- libraries/ghci/GHCi/Debugger.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/Run.hs
- libraries/hpc
- libraries/template-haskell/Language/Haskell/TH/Quote.hs
- libraries/template-haskell/changelog.md
- libraries/text
- libraries/time
- libraries/unix
- rts/Disassembler.c
- rts/Exception.cmm
- rts/IPE.c
- rts/Interpreter.c
- rts/Prelude.h
- rts/PrimOps.cmm
- rts/ProfHeap.c
- rts/RaiseAsync.c
- rts/RtsFlags.c
- rts/RtsSymbols.c
- rts/STM.c
- rts/Timer.c
- rts/eventlog/EventLog.c
- rts/external-symbols.list.in
- rts/include/rts/Flags.h
- rts/include/rts/IPE.h
- rts/include/stg/MiscClosures.h
- rts/include/stg/SMP.h
- rts/linker/LoadArchive.c
- rts/posix/ticker/Pthread.c
- rts/posix/ticker/TimerFd.c
- rts/win32/AsyncWinIO.c
- rts/win32/libHSghc-internal.def
- testsuite/tests/codeGen/should_compile/T25166.stdout → testsuite/tests/codeGen/should_compile/T25166.stdout-ws-32
- + testsuite/tests/codeGen/should_compile/T25166.stdout-ws-64
- testsuite/tests/corelint/LintEtaExpand.stderr
- testsuite/tests/corelint/T21115b.stderr
- + testsuite/tests/cpranal/sigs/T25944.hs
- + testsuite/tests/cpranal/sigs/T25944.stderr
- testsuite/tests/cpranal/sigs/all.T
- testsuite/tests/deriving/should_compile/T20815.hs
- testsuite/tests/deriving/should_fail/T12768.stderr
- testsuite/tests/deriving/should_fail/T1496.stderr
- testsuite/tests/deriving/should_fail/T5498.stderr
- testsuite/tests/deriving/should_fail/T7148.stderr
- testsuite/tests/deriving/should_fail/T7148a.stderr
- testsuite/tests/driver/json.stderr
- testsuite/tests/driver/json_warn.stderr
- 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/HieQueries.stdout
- testsuite/tests/hiefile/should_run/TestUtils.hs
- testsuite/tests/impredicative/T17332.stderr
- testsuite/tests/indexed-types/should_fail/T5439.stderr
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/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/interface-stability/template-haskell-exports.stdout
- + testsuite/tests/lib/stm/T26028.hs
- + testsuite/tests/lib/stm/T26028.stdout
- + testsuite/tests/lib/stm/all.T
- + testsuite/tests/numeric/should_compile/T26229.hs
- testsuite/tests/numeric/should_compile/all.T
- + testsuite/tests/numeric/should_run/T18619.hs
- + testsuite/tests/numeric/should_run/T18619.stderr
- testsuite/tests/numeric/should_run/T9810.stdout
- testsuite/tests/numeric/should_run/all.T
- testsuite/tests/partial-sigs/should_compile/T10403.stderr
- + testsuite/tests/partial-sigs/should_compile/T26256.hs
- + testsuite/tests/partial-sigs/should_compile/T26256.stderr
- testsuite/tests/partial-sigs/should_compile/all.T
- testsuite/tests/partial-sigs/should_fail/T10615.stderr
- testsuite/tests/primops/should_run/UnliftedIOPort.hs
- testsuite/tests/primops/should_run/all.T
- testsuite/tests/quantified-constraints/T15290a.stderr
- testsuite/tests/quantified-constraints/T19690.stderr
- testsuite/tests/quantified-constraints/T19921.stderr
- testsuite/tests/quantified-constraints/T21006.stderr
- + testsuite/tests/rep-poly/NoEtaRequired.hs
- testsuite/tests/rep-poly/T21906.stderr
- testsuite/tests/rep-poly/all.T
- testsuite/tests/roles/should_fail/RolesIArray.stderr
- testsuite/tests/rts/flags/all.T
- testsuite/tests/rts/ipe/ipeMap.c
- testsuite/tests/rts/ipe/ipe_lib.c
- + testsuite/tests/simplCore/should_compile/T26115.hs
- + testsuite/tests/simplCore/should_compile/T26115.stderr
- + testsuite/tests/simplCore/should_compile/T26116.hs
- + testsuite/tests/simplCore/should_compile/T26116.stderr
- + testsuite/tests/simplCore/should_compile/T26117.hs
- + testsuite/tests/simplCore/should_compile/T26117.stderr
- testsuite/tests/simplCore/should_compile/all.T
- + 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/T26087.stderr
- + testsuite/tests/splice-imports/T26087A.hs
- + testsuite/tests/splice-imports/T26087B.hs
- + testsuite/tests/splice-imports/T26088.stderr
- + testsuite/tests/splice-imports/T26088A.hs
- + testsuite/tests/splice-imports/T26088B.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/typecheck/should_compile/T12427a.stderr
- testsuite/tests/typecheck/should_compile/T23171.hs
- + testsuite/tests/typecheck/should_compile/T26225.hs
- + testsuite/tests/typecheck/should_compile/T26225b.hs
- + testsuite/tests/typecheck/should_compile/T26256a.hs
- testsuite/tests/typecheck/should_compile/TcSpecPragmas.stderr
- testsuite/tests/typecheck/should_compile/all.T
- − testsuite/tests/typecheck/should_fail/T12563.stderr
- testsuite/tests/typecheck/should_fail/T14605.hs
- testsuite/tests/typecheck/should_fail/T14605.stderr
- testsuite/tests/typecheck/should_fail/T14618.stderr
- testsuite/tests/typecheck/should_fail/T15801.stderr
- testsuite/tests/typecheck/should_fail/T18640a.stderr
- testsuite/tests/typecheck/should_fail/T18640b.stderr
- testsuite/tests/typecheck/should_fail/T19627.stderr
- testsuite/tests/typecheck/should_fail/T21530b.stderr
- testsuite/tests/typecheck/should_fail/T22912.stderr
- testsuite/tests/typecheck/should_fail/T6022.stderr
- testsuite/tests/typecheck/should_fail/T8883.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/typecheck/should_fail/tcfail140.stderr
- testsuite/tests/typecheck/should_fail/tcfail174.stderr
- testsuite/tests/unboxedsums/unboxedsums_unit_tests.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/c8dfcce9b9ea223474aa6d1e0445c8…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c8dfcce9b9ea223474aa6d1e0445c8…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc] Pushed new branch wip/fendor/stack-annotation-with-backtraces
by Hannes Siebenhandl (@fendor) 13 Aug '25
by Hannes Siebenhandl (@fendor) 13 Aug '25
13 Aug '25
Hannes Siebenhandl pushed new branch wip/fendor/stack-annotation-with-backtraces at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fendor/stack-annotation-with-…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/fendor/remove-stg_stackDecode] 3 commits: Implement `decode` in terms of `decodeStackWithIpe`
by Hannes Siebenhandl (@fendor) 13 Aug '25
by Hannes Siebenhandl (@fendor) 13 Aug '25
13 Aug '25
Hannes Siebenhandl pushed to branch wip/fendor/remove-stg_stackDecode at Glasgow Haskell Compiler / GHC
Commits:
f5fcf224 by fendor at 2025-08-13T14:07:51+02:00
Implement `decode` in terms of `decodeStackWithIpe`
Uses the more efficient stack decoder implementation.
- - - - -
271be2a9 by fendor at 2025-08-13T14:07:51+02:00
Remove stg_decodeStackzh
- - - - -
03f6874f by fendor at 2025-08-13T14:07:51+02:00
Remove ghcHeap from list of toolTargets
- - - - -
15 changed files:
- hadrian/src/Rules/ToolArgs.hs
- libraries/base/src/GHC/Stack/CloneStack.hs
- libraries/ghc-internal/cbits/Stack.cmm
- libraries/ghc-internal/cbits/StackCloningDecoding.cmm
- libraries/ghc-internal/jsbits/base.js
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- libraries/ghc-internal/src/GHC/Internal/Stack/CloneStack.hs
- libraries/ghc-internal/src/GHC/Internal/Stack/Decode.hs
- rts/CloneStack.c
- rts/CloneStack.h
- rts/RtsSymbols.c
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
Changes:
=====================================
hadrian/src/Rules/ToolArgs.hs
=====================================
@@ -160,7 +160,7 @@ toolTargets = [ cabalSyntax
, ghcPlatform
, ghcToolchain
, ghcToolchainBin
- , ghcHeap
+ -- , ghcHeap -- # depends on ghcInternal library
, ghci
, ghcPkg -- # executable
, haddock -- # depends on ghc library
=====================================
libraries/base/src/GHC/Stack/CloneStack.hs
=====================================
@@ -17,3 +17,4 @@ module GHC.Stack.CloneStack (
) where
import GHC.Internal.Stack.CloneStack
+import GHC.Internal.Stack.Decode
=====================================
libraries/ghc-internal/cbits/Stack.cmm
=====================================
@@ -146,14 +146,14 @@ isArgGenBigRetFunTypezh(P_ stack, W_ offsetWords) {
return (type);
}
-// (StgInfoTable*) getInfoTableAddrzh(StgStack* stack, StgWord offsetWords)
-getInfoTableAddrzh(P_ stack, W_ offsetWords) {
- P_ p, info;
+// (StgInfoTable*, StgInfoTable*) getInfoTableAddrszh(StgStack* stack, StgWord offsetWords)
+getInfoTableAddrszh(P_ stack, W_ offsetWords) {
+ P_ p, info_struct, info_entry;
p = StgStack_sp(stack) + WDS(offsetWords);
ASSERT(LOOKS_LIKE_CLOSURE_PTR(p));
- info = %GET_STD_INFO(UNTAG(p));
-
- return (info);
+ info_struct = %GET_STD_INFO(UNTAG(p));
+ info_entry = %GET_ENTRY(UNTAG(p));
+ return (info_struct, info_entry);
}
// (StgInfoTable*) getStackInfoTableAddrzh(StgStack* stack)
=====================================
libraries/ghc-internal/cbits/StackCloningDecoding.cmm
=====================================
@@ -17,10 +17,3 @@ stg_sendCloneStackMessagezh (gcptr threadId, gcptr mVarStablePtr) {
return ();
}
-
-stg_decodeStackzh (gcptr stgStack) {
- gcptr stackEntries;
- ("ptr" stackEntries) = ccall decodeClonedStack(MyCapability() "ptr", stgStack "ptr");
-
- return (stackEntries);
-}
=====================================
libraries/ghc-internal/jsbits/base.js
=====================================
@@ -1245,9 +1245,8 @@ function h$mkdir(path, path_offset, mode) {
// It is required by Google Closure Compiler to be at least defined if
// somewhere it is used
-var h$stg_cloneMyStackzh, h$stg_decodeStackzh
+var h$stg_cloneMyStackzh
h$stg_cloneMyStackzh
- = h$stg_decodeStackzh
= function () {
throw new Error('Stack Cloning Decoding: Not Implemented Yet')
}
=====================================
libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
=====================================
@@ -16,6 +16,7 @@ import qualified GHC.Internal.Stack as HCS
import qualified GHC.Internal.ExecutionStack as ExecStack
import qualified GHC.Internal.ExecutionStack.Internal as ExecStack
import qualified GHC.Internal.Stack.CloneStack as CloneStack
+import qualified GHC.Internal.Stack.Decode as CloneStack
import qualified GHC.Internal.Stack.CCS as CCS
-- | How to collect a backtrace when an exception is thrown.
=====================================
libraries/ghc-internal/src/GHC/Internal/Stack/CloneStack.hs
=====================================
@@ -15,34 +15,20 @@
-- @since base-4.17.0.0
module GHC.Internal.Stack.CloneStack (
StackSnapshot(..),
- StackEntry(..),
cloneMyStack,
cloneThreadStack,
- decode,
- prettyStackEntry
) where
import GHC.Internal.MVar
-import GHC.Internal.Data.Maybe (catMaybes)
import GHC.Internal.Base
-import GHC.Internal.Foreign.Storable
import GHC.Internal.Conc.Sync
-import GHC.Internal.IO (unsafeInterleaveIO)
-import GHC.Internal.InfoProv.Types (InfoProv (..), ipLoc, lookupIPE, StgInfoTable)
-import GHC.Internal.Num
-import GHC.Internal.Real (div)
import GHC.Internal.Stable
-import GHC.Internal.Text.Show
-import GHC.Internal.Ptr
-import GHC.Internal.ClosureTypes
-- | A frozen snapshot of the state of an execution stack.
--
-- @since base-4.17.0.0
data StackSnapshot = StackSnapshot !StackSnapshot#
-foreign import prim "stg_decodeStackzh" decodeStack# :: StackSnapshot# -> State# RealWorld -> (# State# RealWorld, ByteArray# #)
-
foreign import prim "stg_cloneMyStackzh" cloneMyStack# :: State# RealWorld -> (# State# RealWorld, StackSnapshot# #)
foreign import prim "stg_sendCloneStackMessagezh" sendCloneStackMessage# :: ThreadId# -> StablePtr# PrimMVar -> State# RealWorld -> (# State# RealWorld, (# #) #)
@@ -205,64 +191,3 @@ cloneThreadStack (ThreadId tid#) = do
IO $ \s -> case sendCloneStackMessage# tid# ptr s of (# s', (# #) #) -> (# s', () #)
freeStablePtr boxedPtr
takeMVar resultVar
-
--- | Representation for the source location where a return frame was pushed on the stack.
--- This happens every time when a @case ... of@ scrutinee is evaluated.
-data StackEntry = StackEntry
- { functionName :: String,
- moduleName :: String,
- srcLoc :: String,
- closureType :: ClosureType
- }
- deriving (Show, Eq)
-
--- | Decode a 'StackSnapshot' to a stacktrace (a list of 'StackEntry').
--- The stack trace is created from return frames with according 'InfoProvEnt'
--- entries. To generate them, use the GHC flag @-finfo-table-map@. If there are
--- no 'InfoProvEnt' entries, an empty list is returned.
---
--- Please note:
---
--- * To gather 'StackEntry' from libraries, these have to be
--- compiled with @-finfo-table-map@, too.
--- * Due to optimizations by GHC (e.g. inlining) the stacktrace may change
--- with different GHC parameters and versions.
--- * The stack trace is empty (by design) if there are no return frames on
--- the stack. (These are pushed every time when a @case ... of@ scrutinee
--- is evaluated.)
---
--- @since base-4.17.0.0
-decode :: StackSnapshot -> IO [StackEntry]
-decode stackSnapshot = catMaybes `fmap` getDecodedStackArray stackSnapshot
-
-toStackEntry :: InfoProv -> StackEntry
-toStackEntry infoProv =
- StackEntry
- { functionName = ipLabel infoProv,
- moduleName = ipMod infoProv,
- srcLoc = ipLoc infoProv,
- closureType = ipDesc infoProv
- }
-
-getDecodedStackArray :: StackSnapshot -> IO [Maybe StackEntry]
-getDecodedStackArray (StackSnapshot s) =
- IO $ \s0 -> case decodeStack# s s0 of
- (# s1, arr #) ->
- let n = I# (sizeofByteArray# arr) `div` wordSize - 1
- in unIO (go arr n) s1
- where
- go :: ByteArray# -> Int -> IO [Maybe StackEntry]
- go _stack (-1) = return []
- go stack i = do
- infoProv <- lookupIPE (stackEntryAt stack i)
- rest <- unsafeInterleaveIO $ go stack (i-1)
- return ((toStackEntry `fmap` infoProv) : rest)
-
- stackEntryAt :: ByteArray# -> Int -> Ptr StgInfoTable
- stackEntryAt stack (I# i) = Ptr (indexAddrArray# stack i)
-
- wordSize = sizeOf (nullPtr :: Ptr ())
-
-prettyStackEntry :: StackEntry -> String
-prettyStackEntry (StackEntry {moduleName=mod_nm, functionName=fun_nm, srcLoc=loc}) =
- " " ++ mod_nm ++ "." ++ fun_nm ++ " (" ++ loc ++ ")"
=====================================
libraries/ghc-internal/src/GHC/Internal/Stack/Decode.hs
=====================================
@@ -13,7 +13,16 @@
{-# LANGUAGE UnliftedFFITypes #-}
module GHC.Internal.Stack.Decode (
+ -- * High-level stack decoders
+ decode,
decodeStack,
+ decodeStackWithIpe,
+ -- * Stack decoder helpers
+ decodeStackWithFrameUnpack,
+ -- * StackEntry
+ StackEntry(..),
+ -- * Pretty printing
+ prettyStackEntry,
)
where
@@ -23,7 +32,10 @@ import GHC.Internal.Real
import GHC.Internal.Word
import GHC.Internal.Num
import GHC.Internal.Data.Bits
+import GHC.Internal.Data.Functor
+import GHC.Internal.Data.Maybe (catMaybes)
import GHC.Internal.Data.List
+import GHC.Internal.Data.Tuple
import GHC.Internal.Foreign.Ptr
import GHC.Internal.Foreign.Storable
import GHC.Internal.Exts
@@ -42,6 +54,7 @@ import GHC.Internal.Heap.Constants (wORD_SIZE_IN_BITS)
import GHC.Internal.Heap.InfoTable
import GHC.Internal.Stack.Constants
import GHC.Internal.Stack.CloneStack
+import GHC.Internal.InfoProv.Types (InfoProv (..), ipLoc, lookupIPE)
{- Note [Decoding the stack]
~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -153,14 +166,17 @@ foreign import prim "getSmallBitmapzh" getSmallBitmap# :: SmallBitmapGetter
foreign import prim "getRetFunSmallBitmapzh" getRetFunSmallBitmap# :: SmallBitmapGetter
-foreign import prim "getInfoTableAddrzh" getInfoTableAddr# :: StackSnapshot# -> Word# -> Addr#
+foreign import prim "getInfoTableAddrszh" getInfoTableAddrs# :: StackSnapshot# -> Word# -> (# Addr#, Addr# #)
foreign import prim "getStackInfoTableAddrzh" getStackInfoTableAddr# :: StackSnapshot# -> Addr#
-getInfoTableOnStack :: StackSnapshot# -> WordOffset -> IO StgInfoTable
+-- | Get the 'StgInfoTable' of the stack frame.
+-- Additionally, provides 'InfoProv' for the 'StgInfoTable' if there is any.
+getInfoTableOnStack :: StackSnapshot# -> WordOffset -> IO (StgInfoTable, Maybe InfoProv)
getInfoTableOnStack stackSnapshot# index =
- let infoTablePtr = Ptr (getInfoTableAddr# stackSnapshot# (wordOffsetToWord# index))
- in peekItbl infoTablePtr
+ let !(# itbl_struct#, itbl_ptr# #) = getInfoTableAddrs# stackSnapshot# (wordOffsetToWord# index)
+ in
+ (,) <$> peekItbl (Ptr itbl_struct#) <*> lookupIPE (Ptr itbl_ptr#)
getInfoTableForStack :: StackSnapshot# -> IO StgInfoTable
getInfoTableForStack stackSnapshot# =
@@ -279,18 +295,66 @@ decodeSmallBitmap getterFun# stackSnapshot# index relativePayloadOffset =
(bitmapWordPointerness size bitmap)
unpackStackFrame :: StackFrameLocation -> IO StackFrame
-unpackStackFrame (StackSnapshot stackSnapshot#, index) = do
- info <- getInfoTableOnStack stackSnapshot# index
+unpackStackFrame stackFrameLoc = do
+ unpackStackFrameTo stackFrameLoc
+ (\ info _ nextChunk -> do
+ stackClosure <- decodeStack nextChunk
+ pure $
+ UnderflowFrame
+ { info_tbl = info,
+ nextChunk = stackClosure
+ }
+ )
+ (\ frame _ -> pure frame)
+
+unpackStackFrameWithIpe :: StackFrameLocation -> IO [(StackFrame, Maybe InfoProv)]
+unpackStackFrameWithIpe stackFrameLoc = do
+ unpackStackFrameTo stackFrameLoc
+ (\ info mIpe nextChunk@(StackSnapshot stack#) -> do
+ framesWithIpe <- decodeStackWithIpe nextChunk
+ pure
+ [ ( UnderflowFrame
+ { info_tbl = info,
+ nextChunk =
+ GenStgStackClosure
+ { ssc_info = info,
+ ssc_stack_size = getStackFields stack#,
+ ssc_stack = map fst framesWithIpe
+ }
+ }
+ , mIpe
+ )
+ ]
+ )
+ (\ frame mIpe -> pure [(frame, mIpe)])
+
+unpackStackFrameTo ::
+ forall a .
+ StackFrameLocation ->
+ -- ^ Decode the given 'StackFrame'.
+ (StgInfoTable -> Maybe InfoProv -> StackSnapshot -> IO a) ->
+ -- ^ How to handle 'UNDERFLOW_FRAME's.
+ (StackFrame -> Maybe InfoProv -> IO a) ->
+ -- ^ How to handle all other 'StackFrame' values.
+ IO a
+unpackStackFrameTo (StackSnapshot stackSnapshot#, index) unpackUnderflowFrame finaliseStackFrame = do
+ (info, m_info_prov) <- getInfoTableOnStack stackSnapshot# index
unpackStackFrame' info
+ (unpackUnderflowFrame info m_info_prov)
+ (`finaliseStackFrame` m_info_prov)
where
- unpackStackFrame' :: StgInfoTable -> IO StackFrame
- unpackStackFrame' info =
+ unpackStackFrame' ::
+ StgInfoTable ->
+ (StackSnapshot -> IO a) ->
+ (StackFrame -> IO a) ->
+ IO a
+ unpackStackFrame' info mkUnderflowResult mkStackFrameResult =
case tipe info of
RET_BCO -> do
let bco' = getClosureBox stackSnapshot# (index + offsetStgClosurePayload)
-- The arguments begin directly after the payload's one element
bcoArgs' <- decodeLargeBitmap getBCOLargeBitmap# stackSnapshot# index (offsetStgClosurePayload + 1)
- pure
+ mkStackFrameResult
RetBCO
{ info_tbl = info,
bco = bco',
@@ -299,14 +363,14 @@ unpackStackFrame (StackSnapshot stackSnapshot#, index) = do
RET_SMALL ->
let payload' = decodeSmallBitmap getSmallBitmap# stackSnapshot# index offsetStgClosurePayload
in
- pure $
+ mkStackFrameResult $
RetSmall
{ info_tbl = info,
stack_payload = payload'
}
RET_BIG -> do
payload' <- decodeLargeBitmap getLargeBitmap# stackSnapshot# index offsetStgClosurePayload
- pure $
+ mkStackFrameResult $
RetBig
{ info_tbl = info,
stack_payload = payload'
@@ -318,7 +382,7 @@ unpackStackFrame (StackSnapshot stackSnapshot#, index) = do
if isArgGenBigRetFunType stackSnapshot# index == True
then decodeLargeBitmap getRetFunLargeBitmap# stackSnapshot# index offsetStgRetFunFramePayload
else pure $ decodeSmallBitmap getRetFunSmallBitmap# stackSnapshot# index offsetStgRetFunFramePayload
- pure $
+ mkStackFrameResult $
RetFun
{ info_tbl = info,
retFunSize = retFunSize',
@@ -328,31 +392,26 @@ unpackStackFrame (StackSnapshot stackSnapshot#, index) = do
UPDATE_FRAME ->
let updatee' = getClosureBox stackSnapshot# (index + offsetStgUpdateFrameUpdatee)
in
- pure $
+ mkStackFrameResult $
UpdateFrame
{ info_tbl = info,
updatee = updatee'
}
CATCH_FRAME -> do
let handler' = getClosureBox stackSnapshot# (index + offsetStgCatchFrameHandler)
- pure $
+ mkStackFrameResult $
CatchFrame
{ info_tbl = info,
handler = handler'
}
UNDERFLOW_FRAME -> do
let nextChunk' = getUnderflowFrameNextChunk stackSnapshot# index
- stackClosure <- decodeStack nextChunk'
- pure $
- UnderflowFrame
- { info_tbl = info,
- nextChunk = stackClosure
- }
- STOP_FRAME -> pure $ StopFrame {info_tbl = info}
+ mkUnderflowResult nextChunk'
+ STOP_FRAME -> mkStackFrameResult $ StopFrame {info_tbl = info}
ATOMICALLY_FRAME -> do
let atomicallyFrameCode' = getClosureBox stackSnapshot# (index + offsetStgAtomicallyFrameCode)
result' = getClosureBox stackSnapshot# (index + offsetStgAtomicallyFrameResult)
- pure $
+ mkStackFrameResult $
AtomicallyFrame
{ info_tbl = info,
atomicallyFrameCode = atomicallyFrameCode',
@@ -363,7 +422,7 @@ unpackStackFrame (StackSnapshot stackSnapshot#, index) = do
first_code' = getClosureBox stackSnapshot# (index + offsetStgCatchRetryFrameRunningFirstCode)
alt_code' = getClosureBox stackSnapshot# (index + offsetStgCatchRetryFrameAltCode)
in
- pure $
+ mkStackFrameResult $
CatchRetryFrame
{ info_tbl = info,
running_alt_code = running_alt_code',
@@ -374,7 +433,7 @@ unpackStackFrame (StackSnapshot stackSnapshot#, index) = do
let catchFrameCode' = getClosureBox stackSnapshot# (index + offsetStgCatchSTMFrameCode)
handler' = getClosureBox stackSnapshot# (index + offsetStgCatchSTMFrameHandler)
in
- pure $
+ mkStackFrameResult $
CatchStmFrame
{ info_tbl = info,
catchFrameCode = catchFrameCode',
@@ -393,6 +452,54 @@ intToWord# i = int2Word# (toInt# i)
wordOffsetToWord# :: WordOffset -> Word#
wordOffsetToWord# wo = intToWord# (fromIntegral wo)
+-- ----------------------------------------------------------------------------
+-- Simplified source location representation of provenance information
+-- ----------------------------------------------------------------------------
+
+-- | Representation for the source location where a return frame was pushed on the stack.
+-- This happens every time when a @case ... of@ scrutinee is evaluated.
+data StackEntry = StackEntry
+ { functionName :: String,
+ moduleName :: String,
+ srcLoc :: String,
+ closureType :: ClosureType
+ }
+ deriving (Show, Eq)
+
+toStackEntry :: InfoProv -> StackEntry
+toStackEntry infoProv =
+ StackEntry
+ { functionName = ipLabel infoProv,
+ moduleName = ipMod infoProv,
+ srcLoc = ipLoc infoProv,
+ closureType = ipDesc infoProv
+ }
+
+-- ----------------------------------------------------------------------------
+-- Stack decoders
+-- ----------------------------------------------------------------------------
+
+-- | Decode a 'StackSnapshot' to a stacktrace (a list of 'StackEntry').
+-- The stack trace is created from return frames with according 'InfoProvEnt'
+-- entries. To generate them, use the GHC flag @-finfo-table-map@. If there are
+-- no 'InfoProvEnt' entries, an empty list is returned.
+--
+-- Please note:
+--
+-- * To gather 'StackEntry' from libraries, these have to be
+-- compiled with @-finfo-table-map@, too.
+-- * Due to optimizations by GHC (e.g. inlining) the stacktrace may change
+-- with different GHC parameters and versions.
+-- * The stack trace is empty (by design) if there are no return frames on
+-- the stack. (These are pushed every time when a @case ... of@ scrutinee
+-- is evaluated.)
+--
+-- @since base-4.17.0.0
+decode :: StackSnapshot -> IO [StackEntry]
+decode stackSnapshot =
+ (map toStackEntry . catMaybes . map snd . reverse) <$> decodeStackWithIpe stackSnapshot
+
+
-- | Location of a stackframe on the stack
--
-- It's defined by the `StackSnapshot` (@StgStack@) and the offset to the bottom
@@ -405,19 +512,31 @@ type StackFrameLocation = (StackSnapshot, WordOffset)
--
-- See /Note [Decoding the stack]/.
decodeStack :: StackSnapshot -> IO StgStackClosure
-decodeStack (StackSnapshot stack#) = do
+decodeStack snapshot@(StackSnapshot stack#) = do
+ (stackInfo, ssc_stack) <- decodeStackWithFrameUnpack unpackStackFrame snapshot
+ pure
+ GenStgStackClosure
+ { ssc_info = stackInfo,
+ ssc_stack_size = getStackFields stack#,
+ ssc_stack = ssc_stack
+ }
+
+decodeStackWithIpe :: StackSnapshot -> IO [(StackFrame, Maybe InfoProv)]
+decodeStackWithIpe snapshot =
+ concat . snd <$> decodeStackWithFrameUnpack unpackStackFrameWithIpe snapshot
+
+-- ----------------------------------------------------------------------------
+-- Write your own stack decoder!
+-- ----------------------------------------------------------------------------
+
+decodeStackWithFrameUnpack :: (StackFrameLocation -> IO a) -> StackSnapshot -> IO (StgInfoTable, [a])
+decodeStackWithFrameUnpack unpackFrame (StackSnapshot stack#) = do
info <- getInfoTableForStack stack#
case tipe info of
STACK -> do
- let stack_size' = getStackFields stack#
- sfls = stackFrameLocations stack#
- stack' <- mapM unpackStackFrame sfls
- pure $
- GenStgStackClosure
- { ssc_info = info,
- ssc_stack_size = stack_size',
- ssc_stack = stack'
- }
+ let sfls = stackFrameLocations stack#
+ stack' <- mapM unpackFrame sfls
+ pure (info, stack')
_ -> error $ "Expected STACK closure, got " ++ show info
where
stackFrameLocations :: StackSnapshot# -> [StackFrameLocation]
@@ -428,3 +547,11 @@ decodeStack (StackSnapshot stack#) = do
go :: Maybe StackFrameLocation -> [StackFrameLocation]
go Nothing = []
go (Just r) = r : go (advanceStackFrameLocation r)
+
+-- ----------------------------------------------------------------------------
+-- Pretty printing functions for stack entires, stack frames and provenance info
+-- ----------------------------------------------------------------------------
+
+prettyStackEntry :: StackEntry -> String
+prettyStackEntry (StackEntry {moduleName=mod_nm, functionName=fun_nm, srcLoc=loc}) =
+ mod_nm ++ "." ++ fun_nm ++ " (" ++ loc ++ ")"
=====================================
rts/CloneStack.c
=====================================
@@ -26,11 +26,6 @@
#include <string.h>
-static StgWord getStackFrameCount(StgStack* stack);
-static StgWord getStackChunkClosureCount(StgStack* stack);
-static StgArrBytes* allocateByteArray(Capability *cap, StgWord bytes);
-static void copyPtrsToArray(StgArrBytes* arr, StgStack* stack);
-
static StgStack* cloneStackChunk(Capability* capability, const StgStack* stack)
{
StgWord spOffset = stack->sp - stack->stack;
@@ -112,94 +107,3 @@ void sendCloneStackMessage(StgTSO *tso STG_UNUSED, HsStablePtr mvar STG_UNUSED)
}
#endif // end !defined(THREADED_RTS)
-
-// Creates a MutableArray# (Haskell representation) that contains a
-// InfoProvEnt* for every stack frame on the given stack. Thus, the size of the
-// array is the count of stack frames.
-// Each InfoProvEnt* is looked up by lookupIPE(). If there's no IPE for a stack
-// frame it's represented by null.
-StgArrBytes* decodeClonedStack(Capability *cap, StgStack* stack) {
- StgWord closureCount = getStackFrameCount(stack);
-
- StgArrBytes* array = allocateByteArray(cap, sizeof(StgInfoTable*) * closureCount);
-
- copyPtrsToArray(array, stack);
-
- return array;
-}
-
-// Count the stack frames that are on the given stack.
-// This is the sum of all stack frames in all stack chunks of this stack.
-StgWord getStackFrameCount(StgStack* stack) {
- StgWord closureCount = 0;
- StgStack *last_stack = stack;
- while (true) {
- closureCount += getStackChunkClosureCount(last_stack);
-
- // check whether the stack ends in an underflow frame
- StgUnderflowFrame *frame = (StgUnderflowFrame *) (last_stack->stack
- + last_stack->stack_size - sizeofW(StgUnderflowFrame));
- if (frame->info == &stg_stack_underflow_frame_d_info
- ||frame->info == &stg_stack_underflow_frame_v16_info
- ||frame->info == &stg_stack_underflow_frame_v32_info
- ||frame->info == &stg_stack_underflow_frame_v64_info) {
- last_stack = frame->next_chunk;
- } else {
- break;
- }
- }
- return closureCount;
-}
-
-StgWord getStackChunkClosureCount(StgStack* stack) {
- StgWord closureCount = 0;
- StgPtr sp = stack->sp;
- StgPtr spBottom = stack->stack + stack->stack_size;
- for (; sp < spBottom; sp += stack_frame_sizeW((StgClosure *)sp)) {
- closureCount++;
- }
-
- return closureCount;
-}
-
-// Allocate and initialize memory for a ByteArray# (Haskell representation).
-StgArrBytes* allocateByteArray(Capability *cap, StgWord bytes) {
- // Idea stolen from PrimOps.cmm:stg_newArrayzh()
- StgWord words = sizeofW(StgArrBytes) + bytes;
-
- StgArrBytes* array = (StgArrBytes*) allocate(cap, words);
-
- SET_HDR(array, &stg_ARR_WORDS_info, CCS_SYSTEM);
- array->bytes = bytes;
- return array;
-}
-
-static void copyPtrsToArray(StgArrBytes* arr, StgStack* stack) {
- StgWord index = 0;
- StgStack *last_stack = stack;
- const StgInfoTable **result = (const StgInfoTable **) arr->payload;
- while (true) {
- StgPtr sp = last_stack->sp;
- StgPtr spBottom = last_stack->stack + last_stack->stack_size;
- for (; sp < spBottom; sp += stack_frame_sizeW((StgClosure *)sp)) {
- const StgInfoTable* infoTable = ((StgClosure *)sp)->header.info;
- result[index] = infoTable;
- index++;
- }
-
- // Ensure that we didn't overflow the result array
- ASSERT(index-1 < arr->bytes / sizeof(StgInfoTable*));
-
- // check whether the stack ends in an underflow frame
- StgUnderflowFrame *frame = (StgUnderflowFrame *) (last_stack->stack
- + last_stack->stack_size - sizeofW(StgUnderflowFrame));
- if (frame->info == &stg_stack_underflow_frame_d_info
- ||frame->info == &stg_stack_underflow_frame_v16_info
- ||frame->info == &stg_stack_underflow_frame_v32_info
- ||frame->info == &stg_stack_underflow_frame_v64_info) {
- last_stack = frame->next_chunk;
- } else {
- break;
- }
- }
-}
=====================================
rts/CloneStack.h
=====================================
@@ -15,8 +15,6 @@ StgStack* cloneStack(Capability* capability, const StgStack* stack);
void sendCloneStackMessage(StgTSO *tso, HsStablePtr mvar);
-StgArrBytes* decodeClonedStack(Capability *cap, StgStack* stack);
-
#include "BeginPrivate.h"
#if defined(THREADED_RTS)
=====================================
rts/RtsSymbols.c
=====================================
@@ -950,7 +950,6 @@ extern char **environ;
SymI_HasProto(lookupIPE) \
SymI_HasProto(sendCloneStackMessage) \
SymI_HasProto(cloneStack) \
- SymI_HasProto(decodeClonedStack) \
SymI_HasProto(stg_newPromptTagzh) \
SymI_HasProto(stg_promptzh) \
SymI_HasProto(stg_control0zh) \
=====================================
testsuite/tests/interface-stability/base-exports.stdout
=====================================
@@ -11678,7 +11678,7 @@ instance GHC.Internal.Classes.Eq GHC.Internal.Bignum.BigNat.BigNat -- Defined in
instance GHC.Internal.Classes.Eq GHC.Internal.Bignum.Natural.Natural -- Defined in ‘GHC.Internal.Bignum.Natural’
instance GHC.Internal.Classes.Eq GHC.RTS.Flags.IoManagerFlag -- Defined in ‘GHC.RTS.Flags’
instance forall a. GHC.Internal.Classes.Eq (GHC.Internal.StableName.StableName a) -- Defined in ‘GHC.Internal.StableName’
-instance GHC.Internal.Classes.Eq GHC.Internal.Stack.CloneStack.StackEntry -- Defined in ‘GHC.Internal.Stack.CloneStack’
+instance GHC.Internal.Classes.Eq GHC.Internal.Stack.Decode.StackEntry -- Defined in ‘GHC.Internal.Stack.Decode’
instance forall (n :: GHC.Internal.TypeNats.Nat). GHC.Internal.Classes.Eq (GHC.Internal.TypeNats.SNat n) -- Defined in ‘GHC.Internal.TypeNats’
instance GHC.Internal.Classes.Eq GHC.Internal.TypeNats.SomeNat -- Defined in ‘GHC.Internal.TypeNats’
instance forall (c :: GHC.Internal.Types.Char). GHC.Internal.Classes.Eq (GHC.Internal.TypeLits.SChar c) -- Defined in ‘GHC.Internal.TypeLits’
@@ -13137,7 +13137,8 @@ instance GHC.Internal.Show.Show GHC.RTS.Flags.ProfFlags -- Defined in ‘GHC.RTS
instance GHC.Internal.Show.Show GHC.RTS.Flags.RTSFlags -- Defined in ‘GHC.RTS.Flags’
instance GHC.Internal.Show.Show GHC.RTS.Flags.TickyFlags -- Defined in ‘GHC.RTS.Flags’
instance GHC.Internal.Show.Show GHC.RTS.Flags.TraceFlags -- Defined in ‘GHC.RTS.Flags’
-instance GHC.Internal.Show.Show GHC.Internal.Stack.CloneStack.StackEntry -- Defined in ‘GHC.Internal.Stack.CloneStack’
+instance GHC.Internal.Show.Show GHC.Internal.Stack.Decode.Pointerness -- Defined in ‘GHC.Internal.Stack.Decode’
+instance GHC.Internal.Show.Show GHC.Internal.Stack.Decode.StackEntry -- Defined in ‘GHC.Internal.Stack.Decode’
instance GHC.Internal.Show.Show GHC.Internal.StaticPtr.StaticPtrInfo -- Defined in ‘GHC.Internal.StaticPtr’
instance [safe] GHC.Internal.Show.Show GHC.Stats.GCDetails -- Defined in ‘GHC.Stats’
instance [safe] GHC.Internal.Show.Show GHC.Stats.RTSStats -- Defined in ‘GHC.Stats’
=====================================
testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
=====================================
@@ -14713,7 +14713,7 @@ instance GHC.Internal.Classes.Eq GHC.Internal.Bignum.BigNat.BigNat -- Defined in
instance GHC.Internal.Classes.Eq GHC.Internal.Bignum.Natural.Natural -- Defined in ‘GHC.Internal.Bignum.Natural’
instance GHC.Internal.Classes.Eq GHC.RTS.Flags.IoManagerFlag -- Defined in ‘GHC.RTS.Flags’
instance forall a. GHC.Internal.Classes.Eq (GHC.Internal.StableName.StableName a) -- Defined in ‘GHC.Internal.StableName’
-instance GHC.Internal.Classes.Eq GHC.Internal.Stack.CloneStack.StackEntry -- Defined in ‘GHC.Internal.Stack.CloneStack’
+instance GHC.Internal.Classes.Eq GHC.Internal.Stack.Decode.StackEntry -- Defined in ‘GHC.Internal.Stack.Decode’
instance forall (n :: GHC.Internal.TypeNats.Nat). GHC.Internal.Classes.Eq (GHC.Internal.TypeNats.SNat n) -- Defined in ‘GHC.Internal.TypeNats’
instance GHC.Internal.Classes.Eq GHC.Internal.TypeNats.SomeNat -- Defined in ‘GHC.Internal.TypeNats’
instance forall (c :: GHC.Internal.Types.Char). GHC.Internal.Classes.Eq (GHC.Internal.TypeLits.SChar c) -- Defined in ‘GHC.Internal.TypeLits’
@@ -16169,7 +16169,8 @@ instance GHC.Internal.Show.Show GHC.RTS.Flags.ProfFlags -- Defined in ‘GHC.RTS
instance GHC.Internal.Show.Show GHC.RTS.Flags.RTSFlags -- Defined in ‘GHC.RTS.Flags’
instance GHC.Internal.Show.Show GHC.RTS.Flags.TickyFlags -- Defined in ‘GHC.RTS.Flags’
instance GHC.Internal.Show.Show GHC.RTS.Flags.TraceFlags -- Defined in ‘GHC.RTS.Flags’
-instance GHC.Internal.Show.Show GHC.Internal.Stack.CloneStack.StackEntry -- Defined in ‘GHC.Internal.Stack.CloneStack’
+instance GHC.Internal.Show.Show GHC.Internal.Stack.Decode.Pointerness -- Defined in ‘GHC.Internal.Stack.Decode’
+instance GHC.Internal.Show.Show GHC.Internal.Stack.Decode.StackEntry -- Defined in ‘GHC.Internal.Stack.Decode’
instance GHC.Internal.Show.Show GHC.Internal.StaticPtr.StaticPtrInfo -- Defined in ‘GHC.Internal.StaticPtr’
instance [safe] GHC.Internal.Show.Show GHC.Stats.GCDetails -- Defined in ‘GHC.Stats’
instance [safe] GHC.Internal.Show.Show GHC.Stats.RTSStats -- Defined in ‘GHC.Stats’
=====================================
testsuite/tests/interface-stability/base-exports.stdout-mingw32
=====================================
@@ -11934,7 +11934,7 @@ instance GHC.Internal.Classes.Eq GHC.Internal.Bignum.BigNat.BigNat -- Defined in
instance GHC.Internal.Classes.Eq GHC.Internal.Bignum.Natural.Natural -- Defined in ‘GHC.Internal.Bignum.Natural’
instance GHC.Internal.Classes.Eq GHC.RTS.Flags.IoManagerFlag -- Defined in ‘GHC.RTS.Flags’
instance forall a. GHC.Internal.Classes.Eq (GHC.Internal.StableName.StableName a) -- Defined in ‘GHC.Internal.StableName’
-instance GHC.Internal.Classes.Eq GHC.Internal.Stack.CloneStack.StackEntry -- Defined in ‘GHC.Internal.Stack.CloneStack’
+instance GHC.Internal.Classes.Eq GHC.Internal.Stack.Decode.StackEntry -- Defined in ‘GHC.Internal.Stack.Decode’
instance forall (n :: GHC.Internal.TypeNats.Nat). GHC.Internal.Classes.Eq (GHC.Internal.TypeNats.SNat n) -- Defined in ‘GHC.Internal.TypeNats’
instance GHC.Internal.Classes.Eq GHC.Internal.TypeNats.SomeNat -- Defined in ‘GHC.Internal.TypeNats’
instance forall (c :: GHC.Internal.Types.Char). GHC.Internal.Classes.Eq (GHC.Internal.TypeLits.SChar c) -- Defined in ‘GHC.Internal.TypeLits’
@@ -13409,7 +13409,8 @@ instance GHC.Internal.Show.Show GHC.RTS.Flags.ProfFlags -- Defined in ‘GHC.RTS
instance GHC.Internal.Show.Show GHC.RTS.Flags.RTSFlags -- Defined in ‘GHC.RTS.Flags’
instance GHC.Internal.Show.Show GHC.RTS.Flags.TickyFlags -- Defined in ‘GHC.RTS.Flags’
instance GHC.Internal.Show.Show GHC.RTS.Flags.TraceFlags -- Defined in ‘GHC.RTS.Flags’
-instance GHC.Internal.Show.Show GHC.Internal.Stack.CloneStack.StackEntry -- Defined in ‘GHC.Internal.Stack.CloneStack’
+instance GHC.Internal.Show.Show GHC.Internal.Stack.Decode.Pointerness -- Defined in ‘GHC.Internal.Stack.Decode’
+instance GHC.Internal.Show.Show GHC.Internal.Stack.Decode.StackEntry -- Defined in ‘GHC.Internal.Stack.Decode’
instance GHC.Internal.Show.Show GHC.Internal.StaticPtr.StaticPtrInfo -- Defined in ‘GHC.Internal.StaticPtr’
instance [safe] GHC.Internal.Show.Show GHC.Stats.GCDetails -- Defined in ‘GHC.Stats’
instance [safe] GHC.Internal.Show.Show GHC.Stats.RTSStats -- Defined in ‘GHC.Stats’
=====================================
testsuite/tests/interface-stability/base-exports.stdout-ws-32
=====================================
@@ -11678,7 +11678,7 @@ instance GHC.Internal.Classes.Eq GHC.Internal.Bignum.BigNat.BigNat -- Defined in
instance GHC.Internal.Classes.Eq GHC.Internal.Bignum.Natural.Natural -- Defined in ‘GHC.Internal.Bignum.Natural’
instance GHC.Internal.Classes.Eq GHC.RTS.Flags.IoManagerFlag -- Defined in ‘GHC.RTS.Flags’
instance forall a. GHC.Internal.Classes.Eq (GHC.Internal.StableName.StableName a) -- Defined in ‘GHC.Internal.StableName’
-instance GHC.Internal.Classes.Eq GHC.Internal.Stack.CloneStack.StackEntry -- Defined in ‘GHC.Internal.Stack.CloneStack’
+instance GHC.Internal.Classes.Eq GHC.Internal.Stack.Decode.StackEntry -- Defined in ‘GHC.Internal.Stack.Decode’
instance forall (n :: GHC.Internal.TypeNats.Nat). GHC.Internal.Classes.Eq (GHC.Internal.TypeNats.SNat n) -- Defined in ‘GHC.Internal.TypeNats’
instance GHC.Internal.Classes.Eq GHC.Internal.TypeNats.SomeNat -- Defined in ‘GHC.Internal.TypeNats’
instance forall (c :: GHC.Internal.Types.Char). GHC.Internal.Classes.Eq (GHC.Internal.TypeLits.SChar c) -- Defined in ‘GHC.Internal.TypeLits’
@@ -13137,7 +13137,8 @@ instance GHC.Internal.Show.Show GHC.RTS.Flags.ProfFlags -- Defined in ‘GHC.RTS
instance GHC.Internal.Show.Show GHC.RTS.Flags.RTSFlags -- Defined in ‘GHC.RTS.Flags’
instance GHC.Internal.Show.Show GHC.RTS.Flags.TickyFlags -- Defined in ‘GHC.RTS.Flags’
instance GHC.Internal.Show.Show GHC.RTS.Flags.TraceFlags -- Defined in ‘GHC.RTS.Flags’
-instance GHC.Internal.Show.Show GHC.Internal.Stack.CloneStack.StackEntry -- Defined in ‘GHC.Internal.Stack.CloneStack’
+instance GHC.Internal.Show.Show GHC.Internal.Stack.Decode.Pointerness -- Defined in ‘GHC.Internal.Stack.Decode’
+instance GHC.Internal.Show.Show GHC.Internal.Stack.Decode.StackEntry -- Defined in ‘GHC.Internal.Stack.Decode’
instance GHC.Internal.Show.Show GHC.Internal.StaticPtr.StaticPtrInfo -- Defined in ‘GHC.Internal.StaticPtr’
instance [safe] GHC.Internal.Show.Show GHC.Stats.GCDetails -- Defined in ‘GHC.Stats’
instance [safe] GHC.Internal.Show.Show GHC.Stats.RTSStats -- Defined in ‘GHC.Stats’
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/61d7ebfb64a8a669a31eee9b68d89c…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/61d7ebfb64a8a669a31eee9b68d89c…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/andreask/linker_fix] rts: LoadArchive/LoadObj - refactor object verification.
by Andreas Klebinger (@AndreasK) 13 Aug '25
by Andreas Klebinger (@AndreasK) 13 Aug '25
13 Aug '25
Andreas Klebinger pushed to branch wip/andreask/linker_fix at Glasgow Haskell Compiler / GHC
Commits:
92bb42be by Andreas Klebinger at 2025-08-13T13:44:57+02:00
rts: LoadArchive/LoadObj - refactor object verification.
Fixes #26231.
We now consistently call `verifyAndInitOc` to check for valid object code.
Allowing us to replace the somewhat adhoc magic number checking in
loadArchive with the platform specific verification logic.
On windows this adds loadArchive support for
AArch64/32bit COFF bigobj files.
- - - - -
6 changed files:
- rts/Linker.c
- rts/LinkerInternals.h
- rts/linker/LoadArchive.c
- rts/linker/MachO.c
- rts/linker/MachO.h
- rts/linker/PEi386.c
Changes:
=====================================
rts/Linker.c
=====================================
@@ -1415,7 +1415,9 @@ preloadObjectFile (pathchar *path)
// We calculate the correct alignment from the header before
// reading the file, and then we misalign image on purpose so
// that the actual sections end up aligned again.
- misalignment = machoGetMisalignment(f);
+ machoGetMisalignment(f, &misalignment);
+ //machoGetMisalignment might fail to parse the header, but in that
+ //case so will verifyAndInitOc so we leave cleanup to after verifyAndInitOc.
image = stgMallocBytes(fileSize + misalignment, "loadObj(image)");
image += misalignment;
@@ -1441,14 +1443,11 @@ preloadObjectFile (pathchar *path)
/* FIXME (AP): =mapped= parameter unconditionally set to true */
oc = mkOc(STATIC_OBJECT, path, image, fileSize, true, NULL, misalignment);
-#if defined(OBJFORMAT_MACHO)
- if (ocVerifyImage_MachO( oc ))
- ocInit_MachO( oc );
-#endif
-#if defined(OBJFORMAT_ELF)
- if(ocVerifyImage_ELF( oc ))
- ocInit_ELF( oc );
-#endif
+ if (!verifyAndInitOc(oc)) {
+ freeObjectCode(oc);
+ debugBelch("loadObj: Failed to verify oc.\n");
+ return NULL;
+ }
return oc;
}
@@ -1505,27 +1504,44 @@ HsInt loadObj (pathchar *path)
return r;
}
+// Call the relevant VeriffyImage_* and ocInit_* functions.
+// Return 1 on success.
+HsInt verifyAndInitOc (ObjectCode* oc)
+{
+ int r;
+
+ IF_DEBUG(linker, ocDebugBelch(oc, "start\n"));
+
+ /* verify the in-memory image */
+#if defined(OBJFORMAT_ELF)
+ r = ocVerifyImage_ELF ( oc );
+ if(r) {
+ ocInit_ELF( oc );
+ }
+#elif defined(OBJFORMAT_PEi386)
+ r = ocVerifyImage_PEi386 ( oc );
+#elif defined(OBJFORMAT_MACHO)
+ r = ocVerifyImage_MachO ( oc );
+ if(r) {
+ ocInit_MachO( oc );
+ }
+#else
+ barf("loadObj: no verify method");
+#endif
+ if (!r) {
+ IF_DEBUG(linker, ocDebugBelch(oc, "ocVerifyImage_* failed\n"));
+ return r;
+ }
+ return 1;
+}
+
+// Precondition: oc already verified.
HsInt loadOc (ObjectCode* oc)
{
int r;
IF_DEBUG(linker, ocDebugBelch(oc, "start\n"));
- /* verify the in-memory image */
-# if defined(OBJFORMAT_ELF)
- r = ocVerifyImage_ELF ( oc );
-# elif defined(OBJFORMAT_PEi386)
- r = ocVerifyImage_PEi386 ( oc );
-# elif defined(OBJFORMAT_MACHO)
- r = ocVerifyImage_MachO ( oc );
-# else
- barf("loadObj: no verify method");
-# endif
- if (!r) {
- IF_DEBUG(linker, ocDebugBelch(oc, "ocVerifyImage_* failed\n"));
- return r;
- }
-
/* Note [loadOc orderings]
~~~~~~~~~~~~~~~~~~~~~~~
The order of `ocAllocateExtras` and `ocGetNames` matters. For MachO
=====================================
rts/LinkerInternals.h
=====================================
@@ -485,12 +485,18 @@ HsInt loadArchive_ (pathchar *path);
HsInt isAlreadyLoaded( pathchar *path );
OStatus getObjectLoadStatus_ (pathchar *path);
ObjectCode *lookupObjectByPath(pathchar *path);
+
+/* Verify an objects is an a format that can be loaded and initialize the oc struct if required. */
+HsInt verifyAndInitOc( ObjectCode *oc );
+
+//Expects the oc to be verified already.
HsInt loadOc( ObjectCode* oc );
ObjectCode* mkOc( ObjectType type, pathchar *path, char *image, int imageSize,
bool mapped, pathchar *archiveMemberName,
int misalignment
);
+
void initSegment(Segment *s, void *start, size_t size, SegmentProt prot, int n_sections);
void freeSegments(ObjectCode *oc);
=====================================
rts/linker/LoadArchive.c
=====================================
@@ -110,51 +110,6 @@ static bool loadFatArchive(char input[static 20], FILE* f, pathchar* path)
}
#endif
-enum ObjectFileFormat {
- NotObject,
- COFFAmd64,
- COFFI386,
- COFFAArch64,
- ELF,
- MachO32,
- MachO64,
-};
-
-static enum ObjectFileFormat identifyObjectFile_(char* buf, size_t sz)
-{
- if (sz > 2 && ((uint16_t*)buf)[0] == 0x8664) {
- return COFFAmd64;
- }
- if (sz > 2 && ((uint16_t*)buf)[0] == 0x014c) {
- return COFFI386;
- }
- if (sz > 2 && ((uint16_t*)buf)[0] == 0xaa64) {
- return COFFAArch64;
- }
- if (sz > 4 && memcmp(buf, "\x7f" "ELF", 4) == 0) {
- return ELF;
- }
- if (sz > 4 && ((uint32_t*)buf)[0] == 0xfeedface) {
- return MachO32;
- }
- if (sz > 4 && ((uint32_t*)buf)[0] == 0xfeedfacf) {
- return MachO64;
- }
- // BigObj COFF files ...
- if (sz > 8 && ((uint64_t*)buf)[0] == 0x86640002ffff0000) {
- return COFFAmd64;
- }
- return NotObject;
-}
-
-static enum ObjectFileFormat identifyObjectFile(FILE *f)
-{
- char buf[32];
- ssize_t sz = fread(buf, 1, 32, f);
- CHECK(fseek(f, -sz, SEEK_CUR) == 0);
- return identifyObjectFile_(buf, sz);
-}
-
static bool readThinArchiveMember(int n, int memberSize, pathchar* path,
char* fileName, char* image)
{
@@ -547,9 +502,11 @@ HsInt loadArchive_ (pathchar *path)
}
DEBUG_LOG("Found member file `%s'\n", fileName);
-
bool is_symbol_table = strcmp("", fileName) == 0;
- enum ObjectFileFormat object_fmt = is_symbol_table ? NotObject : identifyObjectFile(f);
+
+/////////////////////////////////////////////////
+// We found the member file. Load it into memory.
+/////////////////////////////////////////////////
#if defined(OBJFORMAT_PEi386)
/*
@@ -569,17 +526,20 @@ HsInt loadArchive_ (pathchar *path)
#endif // windows
DEBUG_LOG("\tthisFileNameSize = %d\n", (int)thisFileNameSize);
- DEBUG_LOG("\tisObject = %d\n", object_fmt);
- if ((!is_symbol_table && isThin) || object_fmt != NotObject) {
- DEBUG_LOG("Member is an object file...loading...\n");
+ if (!is_symbol_table && !isImportLib)
+ {
+ DEBUG_LOG("Member might be an object file...loading...\n");
#if defined(darwin_HOST_OS) || defined(ios_HOST_OS)
if (RTS_LINKER_USE_MMAP)
image = mmapAnonForLinker(memberSize);
else {
/* See loadObj() */
- misalignment = machoGetMisalignment(f);
+ if(!machoGetMisalignment(f, &misalignment))
+ DEBUG_LOG("Failed to load member as mach-o file. Skipping.\n");
+ continue;
+ }
image = stgMallocBytes(memberSize + misalignment,
"loadArchive(image)");
image += misalignment;
@@ -610,19 +570,23 @@ HsInt loadArchive_ (pathchar *path)
pathprintf(archiveMemberName, size+1, WSTR("%" PATH_FMT "(#%d:%.*s)"),
path, memberIdx, (int)thisFileNameSize, fileName);
+///////////////////////////////////////////////////////////////
+// Verfiy the object file is valid, and load it if appropriate.
+///////////////////////////////////////////////////////////////
+
+ // Prepare headers, doesn't load any data yet.
ObjectCode *oc = mkOc(STATIC_OBJECT, path, image, memberSize, false, archiveMemberName,
misalignment);
-#if defined(OBJFORMAT_MACHO)
- ASSERT(object_fmt == MachO32 || object_fmt == MachO64);
- ocInit_MachO( oc );
-#endif
-#if defined(OBJFORMAT_ELF)
- ASSERT(object_fmt == ELF);
- ocInit_ELF( oc );
-#endif
-
stgFree(archiveMemberName);
+ if(!verifyAndInitOc( oc ))
+ {
+ freeObjectCode( oc );
+ IF_DEBUG(linker, ocDebugBelch(oc, "Faild to verify ... skipping."));
+ continue;
+ }
+
+
if (0 == loadOc(oc)) {
stgFree(fileName);
fclose(f);
=====================================
rts/linker/MachO.c
=====================================
@@ -1725,31 +1725,41 @@ ocRunFini_MachO ( ObjectCode *oc )
/*
* Figure out by how much to shift the entire Mach-O file in memory
* when loading so that its single segment ends up 16-byte-aligned
+ *
+ * Returns 1 and sets misalignment_out to the detected misalignment if
+ * we successfully parsed the file.
+ *
+ * If we can't parse the file we set misalignment_out to 0 and return 0
*/
int
-machoGetMisalignment( FILE * f )
+machoGetMisalignment( FILE * f, int* misalignment_out )
{
MachOHeader header;
int misalignment;
+ *misalignment_out = 0;
{
size_t n = fread(&header, sizeof(header), 1, f);
if (n != 1) {
- barf("machoGetMisalignment: can't read the Mach-O header");
+ debugBelch("machoGetMisalignment: can't read the Mach-O header");
+ return 0;
}
}
fseek(f, -sizeof(header), SEEK_CUR);
if(header.magic != MH_MAGIC_64) {
- barf("Bad magic. Expected: %08x, got: %08x.",
+ debugBelch("Bad magic. Expected: %08x, got: %08x.",
MH_MAGIC_64, header.magic);
+ return 0;
}
misalignment = (header.sizeofcmds + sizeof(header))
& 0xF;
IF_DEBUG(linker, debugBelch("mach-o misalignment %d\n", misalignment));
- return misalignment ? (16 - misalignment) : 0;
+ misalignment = misalignment ? (16 - misalignment) : 0;
+ *misalignment_out = misalignment;
+ return 1;
}
#endif /* darwin_HOST_OS || ios_HOST_OS */
=====================================
rts/linker/MachO.h
=====================================
@@ -13,7 +13,7 @@ int ocGetNames_MachO ( ObjectCode* oc );
int ocResolve_MachO ( ObjectCode* oc );
int ocRunInit_MachO ( ObjectCode* oc );
int ocRunFini_MachO ( ObjectCode* oc );
-int machoGetMisalignment ( FILE * );
+int machoGetMisalignment ( FILE *, int* );
int ocAllocateExtras_MachO ( ObjectCode* oc );
SectionKind getSectionKind_MachO ( MachOSection *macho );
=====================================
rts/linker/PEi386.c
=====================================
@@ -775,6 +775,10 @@ COFF_OBJ_TYPE getObjectType ( char* image, pathchar* fileName )
*************/
COFF_HEADER_INFO* getHeaderInfo ( ObjectCode* oc )
{
+ if((size_t) oc->fileSize < sizeof(IMAGE_FILE_HEADER)) {
+ errorBelch ("Supposed COFF file smaller than minimum header size.\n");
+ return NULL;
+ }
COFF_OBJ_TYPE coff_type = getObjectType (oc->image, OC_INFORMATIVE_FILENAME(oc));
COFF_HEADER_INFO* info
@@ -808,6 +812,11 @@ COFF_HEADER_INFO* getHeaderInfo ( ObjectCode* oc )
stgFree (info);
info = NULL;
errorBelch ("Unknown COFF %d type in getHeaderInfo.", coff_type);
+ if(oc->archiveMemberName) {
+ errorBelch ("Archive %" PATH_FMT ".\n", oc->archiveMemberName);
+ }
+ errorBelch ("In %" PATH_FMT ".\n", oc->fileName);
+
}
break;
}
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/92bb42beca1722e7f42560552f8760a…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/92bb42beca1722e7f42560552f8760a…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/teo/move-out-bits-of-th-from-ghc-internal] 2 commits: template-haskell: move some identifiers from ghc-internal to template-haskell
by Teo Camarasu (@teo) 13 Aug '25
by Teo Camarasu (@teo) 13 Aug '25
13 Aug '25
Teo Camarasu pushed to branch wip/teo/move-out-bits-of-th-from-ghc-internal at Glasgow Haskell Compiler / GHC
Commits:
0d36a167 by Teo Camarasu at 2025-08-13T12:10:34+01: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
- - - - -
47533cb1 by Teo Camarasu at 2025-08-13T12:10:34+01:00
template-haskell: transfer $infix note to public module
This Haddock note should be in the public facing module
- - - - -
9 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
- 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.
+
+-}
=====================================
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/454606a0c04f9cc3f2364e92f773f2…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/454606a0c04f9cc3f2364e92f773f2…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/fendor/remove-stg_stackDecode] 4 commits: Move stack decoding logic from ghc-heap to ghc-internal
by Hannes Siebenhandl (@fendor) 13 Aug '25
by Hannes Siebenhandl (@fendor) 13 Aug '25
13 Aug '25
Hannes Siebenhandl pushed to branch wip/fendor/remove-stg_stackDecode at Glasgow Haskell Compiler / GHC
Commits:
599b7958 by fendor at 2025-08-13T12:42:18+02:00
Move stack decoding logic from ghc-heap to ghc-internal
The stack decoding logic in `ghc-heap` is more sophisticated than the one
currently employed in `CloneStack`. We want to use the stack decoding
implementation from `ghc-heap` in `base`.
We cannot simply depend on `ghc-heap` in `base` due do bootstrapping
issues.
Thus, we move the code that is necessary to implement stack decoding to
`ghc-internal`. This is the right location, as we don't want to add a
new API to `base`.
Moving the stack decoding logic and re-exposing it in ghc-heap is
insufficient, though, as we have a dependency cycle between.
* ghc-heap depends on stage1:ghc-internal
* stage0:ghc depends on stage0:ghc-heap
To fix this, we remove ghc-heap from the set of `stage0` dependencies.
This is not entirely straight-forward, as a couple of boot dependencies,
such as `ghci` depend on `ghc-heap`.
Luckily, the boot compiler of GHC is now >=9.10, so we can migrate `ghci`
to use `ghc-internal` instead of `ghc-heap`, which already exports the
relevant modules.
However, we cannot 100% remove ghc's dependency on `ghc-heap`, since
when we compile `stage0:ghc`, `stage1:ghc-internal` is not yet
available.
Thus, when we compile with the boot-compiler, we still depend on an
older version of `ghc-heap`, and only use the modules from `ghc-internal`,
if the `ghc-internal` version is recent enough.
-------------------------
Metric Increase:
size_hello_artifact
size_hello_artifact_gzip
size_hello_unicode
size_hello_unicode_gzip
-------------------------
These metric increases are unfortunate, they are most likely caused by
the larger (literally in terms of lines of code) stack decoder implementation
that are now linked into hello-word binaries.
On linux, it is almost a 10% increase, which is considerable.
- - - - -
3cc09cf4 by fendor at 2025-08-13T12:42:18+02:00
Implement `decode` in terms of `decodeStackWithIpe`
Uses the more efficient stack decoder implementation.
- - - - -
1a0d1b20 by fendor at 2025-08-13T12:42:18+02:00
Remove stg_decodeStackzh
- - - - -
61d7ebfb by fendor at 2025-08-13T12:42:18+02:00
Remove ghcHeap from list of toolTargets
- - - - -
42 changed files:
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Runtime/Heap/Inspect.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/ghc.cabal.in
- hadrian/src/Rules/ToolArgs.hs
- hadrian/src/Settings/Default.hs
- libraries/base/src/GHC/Stack/CloneStack.hs
- libraries/ghc-heap/GHC/Exts/Heap/ClosureTypes.hs
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
- + libraries/ghc-heap/GHC/Exts/Heap/Constants.hs
- + libraries/ghc-heap/GHC/Exts/Heap/InfoTable.hs
- + libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hs
- + libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hs
- libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/Types.hs
- + libraries/ghc-heap/GHC/Exts/Stack/Constants.hs
- libraries/ghc-heap/GHC/Exts/Stack/Decode.hs
- libraries/ghc-heap/ghc-heap.cabal.in
- libraries/ghc-heap/cbits/HeapPrim.cmm → libraries/ghc-internal/cbits/HeapPrim.cmm
- libraries/ghc-heap/cbits/Stack.cmm → libraries/ghc-internal/cbits/Stack.cmm
- libraries/ghc-internal/cbits/StackCloningDecoding.cmm
- libraries/ghc-heap/cbits/Stack_c.c → libraries/ghc-internal/cbits/Stack_c.c
- libraries/ghc-internal/ghc-internal.cabal.in
- libraries/ghc-internal/jsbits/base.js
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- + libraries/ghc-internal/src/GHC/Internal/Heap/Closures.hs
- libraries/ghc-heap/GHC/Exts/Heap/Constants.hsc → libraries/ghc-internal/src/GHC/Internal/Heap/Constants.hsc
- libraries/ghc-heap/GHC/Exts/Heap/InfoTable.hsc → libraries/ghc-internal/src/GHC/Internal/Heap/InfoTable.hsc
- libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc → libraries/ghc-internal/src/GHC/Internal/Heap/InfoTable/Types.hsc
- libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc → libraries/ghc-internal/src/GHC/Internal/Heap/InfoTableProf.hsc
- + libraries/ghc-internal/src/GHC/Internal/Heap/ProfInfo/Types.hs
- libraries/ghc-internal/src/GHC/Internal/Stack/CloneStack.hs
- libraries/ghc-heap/GHC/Exts/Stack/Constants.hsc → libraries/ghc-internal/src/GHC/Internal/Stack/Constants.hsc
- + libraries/ghc-internal/src/GHC/Internal/Stack/Decode.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/ghci.cabal.in
- rts/CloneStack.c
- rts/CloneStack.h
- rts/RtsSymbols.c
- 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
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e908a899d6f9a1d07fc32b33d3c232…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e908a899d6f9a1d07fc32b33d3c232…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

13 Aug '25
Matthew Pickering pushed new branch wip/gdc-files at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/gdc-files
You're receiving this email because of your account on gitlab.haskell.org.
1
0