[Git][ghc/ghc][wip/fendor/backtraces-decoders] 11 commits: compiler: Export a version of `newNameCache` that is not prone to footguns.
by Hannes Siebenhandl (@fendor) 07 Aug '25
by Hannes Siebenhandl (@fendor) 07 Aug '25
07 Aug '25
Hannes Siebenhandl pushed to branch wip/fendor/backtraces-decoders at Glasgow Haskell Compiler / GHC
Commits:
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.
- - - - -
1b245abe by fendor at 2025-08-07T09:10:37+02: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`).
- - - - -
097fe105 by fendor at 2025-08-07T09:10:37+02: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.
- - - - -
4c22cbdb by fendor at 2025-08-07T09:36:55+02:00
Expose Backtraces internals, as well as the API of `base.Control.Exception.Backtrace`
- - - - -
36 changed files:
- CODEOWNERS
- README.md
- compiler/GHC/CmmToAsm/LA64/CodeGen.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Types/Name/Cache.hs
- docs/users_guide/exts/linear_types.rst
- docs/users_guide/exts/strict.rst
- hadrian/stack.yaml
- hadrian/stack.yaml.lock
- libraries/base/src/System/Console/GetOpt.hs
- + libraries/ghc-experimental/src/GHC/Exception/Backtrace/Experimental.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/text
- testsuite/tests/arrows/should_compile/T21301.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/ghci/scripts/Defer02.stderr
- testsuite/tests/ghci/scripts/T15325.stderr
- testsuite/tests/hiefile/should_run/TestUtils.hs
- testsuite/tests/patsyn/should_run/ghci.stderr
- testsuite/tests/quotes/LiftErrMsgDefer.stderr
- testsuite/tests/safeHaskell/safeLanguage/SafeLang15.stderr
- testsuite/tests/type-data/should_run/T22332a.stderr
- 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/unsatisfiable/T23816.stderr
- testsuite/tests/unsatisfiable/UnsatDefer.stderr
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/68d564d74328a3b7247b13a5532b77…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/68d564d74328a3b7247b13a5532b77…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/9.10.3-backports] Revert "base: Expose Backtraces constructor and fields"
by Zubin (@wz1000) 07 Aug '25
by Zubin (@wz1000) 07 Aug '25
07 Aug '25
Zubin pushed to branch wip/9.10.3-backports at Glasgow Haskell Compiler / GHC
Commits:
1b256e63 by Zubin Duggal at 2025-08-07T12:55:18+05:30
Revert "base: Expose Backtraces constructor and fields"
This reverts commit 1d7e75354027b4ef917c69793d11f50a931a737d.
- - - - -
6 changed files:
- libraries/base/changelog.md
- libraries/base/src/Control/Exception/Backtrace.hs
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
Changes:
=====================================
libraries/base/changelog.md
=====================================
@@ -2,7 +2,6 @@
## 4.20.2 *July 2025*
* Fix incorrect results of `integerPowMod` when the base is 0 and the exponent is negative, and `integerRecipMod` when the modulus is zero ([#26017](https://gitlab.haskell.org/ghc/ghc/-/issues/26017)).
- * Expose constructor and field of `Backtraces` from `Control.Exception.Backtrace`, as per [CLC #199](https://github.com/haskell/core-libraries-committee/issues/199#issuecomment-1954662391)
## 4.20.1 *Jan 2025*
* Shipped with GHC 9.10.2
=====================================
libraries/base/src/Control/Exception/Backtrace.hs
=====================================
@@ -51,7 +51,7 @@ module Control.Exception.Backtrace
, getBacktraceMechanismState
, setBacktraceMechanismState
-- * Collecting backtraces
- , Backtraces(..)
+ , Backtraces
, displayBacktraces
, collectBacktraces
) where
=====================================
testsuite/tests/interface-stability/base-exports.stdout
=====================================
@@ -234,7 +234,7 @@ module Control.Exception where
type ErrorCall :: *
data ErrorCall = ErrorCallWithLocation GHC.Internal.Base.String GHC.Internal.Base.String
type Exception :: * -> Constraint
- class (ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
+ class (ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
toException :: e -> SomeException
fromException :: SomeException -> GHC.Internal.Maybe.Maybe e
displayException :: e -> GHC.Internal.Base.String
@@ -303,7 +303,7 @@ module Control.Exception where
module Control.Exception.Annotation where
-- Safety: None
type ExceptionAnnotation :: * -> Constraint
- class ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable a => ExceptionAnnotation a where
+ class ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable a => ExceptionAnnotation a where
displayExceptionAnnotation :: a -> GHC.Internal.Base.String
default displayExceptionAnnotation :: GHC.Internal.Show.Show a => a -> GHC.Internal.Base.String
{-# MINIMAL #-}
@@ -315,7 +315,7 @@ module Control.Exception.Backtrace where
type BacktraceMechanism :: *
data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
type Backtraces :: *
- data Backtraces = Backtraces {btrCostCentre :: GHC.Internal.Maybe.Maybe (GHC.Internal.Ptr.Ptr GHC.Internal.Stack.CCS.CostCentreStack), btrHasCallStack :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.Types.CallStack, btrExecutionStack :: GHC.Internal.Maybe.Maybe [GHC.Internal.ExecutionStack.Internal.Location], btrIpe :: GHC.Internal.Maybe.Maybe [GHC.Internal.Stack.CloneStack.StackEntry]}
+ data Backtraces = ...
collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Types.IO Backtraces
displayBacktraces :: Backtraces -> GHC.Internal.Base.String
getBacktraceMechanismState :: BacktraceMechanism -> GHC.Types.IO GHC.Types.Bool
@@ -345,7 +345,7 @@ module Control.Exception.Base where
type ErrorCall :: *
data ErrorCall = ErrorCallWithLocation GHC.Internal.Base.String GHC.Internal.Base.String
type Exception :: * -> Constraint
- class (ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
+ class (ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
toException :: e -> SomeException
fromException :: SomeException -> GHC.Internal.Maybe.Maybe e
displayException :: e -> GHC.Internal.Base.String
@@ -848,11 +848,11 @@ module Data.Data where
type TyCon :: *
data TyCon = ...
type TypeRep :: *
- type TypeRep = ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep
+ type TypeRep = ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep
type Typeable :: forall k. k -> Constraint
class Typeable a where
...
- {-# MINIMAL ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.typeRep# #-}
+ {-# MINIMAL ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.typeRep# #-}
cast :: forall a b. (Typeable a, Typeable b) => a -> GHC.Internal.Maybe.Maybe b
constrFields :: Constr -> [GHC.Internal.Base.String]
constrFixity :: Constr -> Fixity
@@ -895,7 +895,7 @@ module Data.Data where
showConstr :: Constr -> GHC.Internal.Base.String
showsTypeRep :: TypeRep -> GHC.Internal.Show.ShowS
splitTyConApp :: TypeRep -> (TyCon, [TypeRep])
- trLiftedRep :: ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.TypeRep GHC.Types.LiftedRep
+ trLiftedRep :: ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.TypeRep GHC.Types.LiftedRep
tyConFingerprint :: TyCon -> GHC.Internal.Fingerprint.Type.Fingerprint
tyConModule :: TyCon -> GHC.Internal.Base.String
tyConName :: TyCon -> GHC.Internal.Base.String
@@ -919,14 +919,14 @@ module Data.Dynamic where
-- Safety: Safe
type Dynamic :: *
data Dynamic where
- Dynamic :: forall a. ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.TypeRep a -> a -> Dynamic
+ Dynamic :: forall a. ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.TypeRep a -> a -> Dynamic
type Typeable :: forall k. k -> Constraint
class Typeable a where
...
- {-# MINIMAL ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.typeRep# #-}
+ {-# MINIMAL ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.typeRep# #-}
dynApp :: Dynamic -> Dynamic -> Dynamic
dynApply :: Dynamic -> Dynamic -> GHC.Internal.Maybe.Maybe Dynamic
- dynTypeRep :: Dynamic -> ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep
+ dynTypeRep :: Dynamic -> ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep
fromDyn :: forall a. Typeable a => Dynamic -> a -> a
fromDynamic :: forall a. Typeable a => Dynamic -> GHC.Internal.Maybe.Maybe a
toDyn :: forall a. Typeable a => a -> Dynamic
@@ -1809,11 +1809,11 @@ module Data.Typeable where
type TyCon :: *
data TyCon = ...
type TypeRep :: *
- type TypeRep = ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep
+ type TypeRep = ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep
type Typeable :: forall k. k -> Constraint
class Typeable a where
...
- {-# MINIMAL ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.typeRep# #-}
+ {-# MINIMAL ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.typeRep# #-}
cast :: forall a b. (Typeable a, Typeable b) => a -> GHC.Internal.Maybe.Maybe b
decT :: forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => GHC.Internal.Data.Either.Either ((a :~: b) -> GHC.Internal.Base.Void) (a :~: b)
eqT :: forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => GHC.Internal.Maybe.Maybe (a :~: b)
@@ -1828,7 +1828,7 @@ module Data.Typeable where
rnfTypeRep :: TypeRep -> ()
showsTypeRep :: TypeRep -> GHC.Internal.Show.ShowS
splitTyConApp :: TypeRep -> (TyCon, [TypeRep])
- trLiftedRep :: ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.TypeRep GHC.Types.LiftedRep
+ trLiftedRep :: ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.TypeRep GHC.Types.LiftedRep
tyConFingerprint :: TyCon -> GHC.Internal.Fingerprint.Type.Fingerprint
tyConModule :: TyCon -> GHC.Internal.Base.String
tyConName :: TyCon -> GHC.Internal.Base.String
@@ -5249,7 +5249,7 @@ module GHC.Event where
data EventManager = ...
type FdKey :: *
data FdKey
- = ghc-internal-9.1002.0:GHC.Internal.Event.Manager.FdKey {keyFd :: ! {-# UNPACK #-}(GHC.Internal.System.Posix.Types.N:Fd[0]
+ = ghc-internal-9.1001.0:GHC.Internal.Event.Manager.FdKey {keyFd :: ! {-# UNPACK #-}(GHC.Internal.System.Posix.Types.N:Fd[0]
; GHC.Internal.Foreign.C.Types.N:CInt[0])GHC.Internal.System.Posix.Types.Fd,
...}
type IOCallback :: *
@@ -5282,9 +5282,9 @@ module GHC.Event.TimeOut where
type TimeoutEdit :: *
type TimeoutEdit = TimeoutQueue -> TimeoutQueue
type TimeoutKey :: *
- newtype TimeoutKey = TK ghc-internal-9.1002.0:GHC.Internal.Event.Unique.Unique
+ newtype TimeoutKey = TK ghc-internal-9.1001.0:GHC.Internal.Event.Unique.Unique
type TimeoutQueue :: *
- type TimeoutQueue = ghc-internal-9.1002.0:GHC.Internal.Event.PSQ.PSQ TimeoutCallback
+ type TimeoutQueue = ghc-internal-9.1001.0:GHC.Internal.Event.PSQ.PSQ TimeoutCallback
module GHC.Exception where
-- Safety: Safe
@@ -5296,7 +5296,7 @@ module GHC.Exception where
type ErrorCall :: *
data ErrorCall = ErrorCallWithLocation GHC.Internal.Base.String GHC.Internal.Base.String
type Exception :: * -> Constraint
- class (ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
+ class (ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
toException :: e -> SomeException
fromException :: SomeException -> GHC.Internal.Maybe.Maybe e
displayException :: e -> GHC.Internal.Base.String
@@ -5325,7 +5325,7 @@ module GHC.Exception.Type where
type ArithException :: *
data ArithException = Overflow | Underflow | LossOfPrecision | DivideByZero | Denormal | RatioZeroDenominator
type Exception :: * -> Constraint
- class (ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
+ class (ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
toException :: e -> SomeException
fromException :: SomeException -> GHC.Internal.Maybe.Maybe e
displayException :: e -> GHC.Internal.Base.String
@@ -7878,8 +7878,8 @@ module GHC.IO.Handle where
hTryLock :: Handle -> LockMode -> GHC.Types.IO GHC.Types.Bool
hWaitForInput :: Handle -> GHC.Types.Int -> GHC.Types.IO GHC.Types.Bool
isEOF :: GHC.Types.IO GHC.Types.Bool
- mkDuplexHandle :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> NewlineMode -> GHC.Types.IO Handle
- mkFileHandle :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.IO.IOMode.IOMode -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> NewlineMode -> GHC.Types.IO Handle
+ mkDuplexHandle :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> NewlineMode -> GHC.Types.IO Handle
+ mkFileHandle :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.IO.IOMode.IOMode -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> NewlineMode -> GHC.Types.IO Handle
nativeNewline :: Newline
nativeNewlineMode :: NewlineMode
noNewlineTranslation :: NewlineMode
@@ -7929,11 +7929,11 @@ module GHC.IO.Handle.Internals where
ioe_notReadable :: forall a. GHC.Types.IO a
ioe_notWritable :: forall a. GHC.Types.IO a
ioe_semiclosedHandle :: forall a. GHC.Types.IO a
- mkDuplexHandle :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> GHC.Internal.IO.Handle.Types.NewlineMode -> GHC.Types.IO GHC.Internal.IO.Handle.Types.Handle
- mkDuplexHandleNoFinalizer :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> GHC.Internal.IO.Handle.Types.NewlineMode -> GHC.Types.IO GHC.Internal.IO.Handle.Types.Handle
- mkFileHandle :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.IO.IOMode.IOMode -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> GHC.Internal.IO.Handle.Types.NewlineMode -> GHC.Types.IO GHC.Internal.IO.Handle.Types.Handle
- mkFileHandleNoFinalizer :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.IO.IOMode.IOMode -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> GHC.Internal.IO.Handle.Types.NewlineMode -> GHC.Types.IO GHC.Internal.IO.Handle.Types.Handle
- mkHandle :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.IO.Handle.Types.HandleType -> GHC.Types.Bool -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> GHC.Internal.IO.Handle.Types.NewlineMode -> GHC.Internal.Maybe.Maybe HandleFinalizer -> GHC.Internal.Maybe.Maybe (GHC.Internal.MVar.MVar GHC.Internal.IO.Handle.Types.Handle__) -> GHC.Types.IO GHC.Internal.IO.Handle.Types.Handle
+ mkDuplexHandle :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> GHC.Internal.IO.Handle.Types.NewlineMode -> GHC.Types.IO GHC.Internal.IO.Handle.Types.Handle
+ mkDuplexHandleNoFinalizer :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> GHC.Internal.IO.Handle.Types.NewlineMode -> GHC.Types.IO GHC.Internal.IO.Handle.Types.Handle
+ mkFileHandle :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.IO.IOMode.IOMode -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> GHC.Internal.IO.Handle.Types.NewlineMode -> GHC.Types.IO GHC.Internal.IO.Handle.Types.Handle
+ mkFileHandleNoFinalizer :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.IO.IOMode.IOMode -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> GHC.Internal.IO.Handle.Types.NewlineMode -> GHC.Types.IO GHC.Internal.IO.Handle.Types.Handle
+ mkHandle :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.IO.Handle.Types.HandleType -> GHC.Types.Bool -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> GHC.Internal.IO.Handle.Types.NewlineMode -> GHC.Internal.Maybe.Maybe HandleFinalizer -> GHC.Internal.Maybe.Maybe (GHC.Internal.MVar.MVar GHC.Internal.IO.Handle.Types.Handle__) -> GHC.Types.IO GHC.Internal.IO.Handle.Types.Handle
openTextEncoding :: forall a. GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> GHC.Internal.IO.Handle.Types.HandleType -> (forall es ds. GHC.Internal.Maybe.Maybe (GHC.Internal.IO.Encoding.Types.TextEncoder es) -> GHC.Internal.Maybe.Maybe (GHC.Internal.IO.Encoding.Types.TextDecoder ds) -> GHC.Types.IO a) -> GHC.Types.IO a
readTextDevice :: GHC.Internal.IO.Handle.Types.Handle__ -> GHC.Internal.IO.Buffer.CharBuffer -> GHC.Types.IO GHC.Internal.IO.Buffer.CharBuffer
readTextDeviceNonBlocking :: GHC.Internal.IO.Handle.Types.Handle__ -> GHC.Internal.IO.Buffer.CharBuffer -> GHC.Types.IO GHC.Internal.IO.Buffer.CharBuffer
@@ -7997,7 +7997,7 @@ module GHC.IO.Handle.Types where
type Handle__ :: *
data Handle__
= forall dev enc_state dec_state.
- (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) =>
+ (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) =>
Handle__ {haDevice :: !dev,
haType :: HandleType,
haByteBuffer :: ! {-# UNPACK #-}(GHC.Internal.IORef.N:IORef[0] <GHC.Internal.IO.Buffer.Buffer GHC.Internal.Word.Word8>_N)(GHC.Internal.IORef.IORef (GHC.Internal.IO.Buffer.Buffer GHC.Internal.Word.Word8)),
@@ -9419,7 +9419,7 @@ module GHC.StaticPtr where
-- Safety: None
type IsStatic :: (* -> *) -> Constraint
class IsStatic p where
- fromStaticPtr :: forall a. ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable a => StaticPtr a -> p a
+ fromStaticPtr :: forall a. ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable a => StaticPtr a -> p a
{-# MINIMAL fromStaticPtr #-}
type StaticKey :: *
type StaticKey = GHC.Internal.Fingerprint.Type.Fingerprint
@@ -10816,8 +10816,8 @@ module Type.Reflection where
data (:~~:) a b where
HRefl :: forall {k1} (a :: k1). (:~~:) a a
pattern App :: forall k2 (t :: k2). () => forall k1 (a :: k1 -> k2) (b :: k1). (t ~ a b) => TypeRep a -> TypeRep b -> TypeRep t
- pattern Con :: forall k (a :: k). () => ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.NotApplication a => TyCon -> TypeRep a
- pattern Con' :: forall k (a :: k). () => ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.NotApplication a => TyCon -> [SomeTypeRep] -> TypeRep a
+ pattern Con :: forall k (a :: k). () => ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.NotApplication a => TyCon -> TypeRep a
+ pattern Con' :: forall k (a :: k). () => ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.NotApplication a => TyCon -> [SomeTypeRep] -> TypeRep a
pattern Fun :: forall k (fun :: k). () => forall (r1 :: GHC.Types.RuntimeRep) (r2 :: GHC.Types.RuntimeRep) (arg :: TYPE r1) (res :: TYPE r2). (k ~ *, fun ~~ (arg -> res)) => TypeRep arg -> TypeRep res -> TypeRep fun
type Module :: *
data Module = ...
@@ -10834,7 +10834,7 @@ module Type.Reflection where
type Typeable :: forall k. k -> Constraint
class Typeable a where
...
- {-# MINIMAL ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.typeRep# #-}
+ {-# MINIMAL ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.typeRep# #-}
decTypeRep :: forall k1 k2 (a :: k1) (b :: k2). TypeRep a -> TypeRep b -> GHC.Internal.Data.Either.Either ((a :~~: b) -> GHC.Internal.Base.Void) (a :~~: b)
eqTypeRep :: forall k1 k2 (a :: k1) (b :: k2). TypeRep a -> TypeRep b -> GHC.Internal.Maybe.Maybe (a :~~: b)
moduleName :: Module -> GHC.Internal.Base.String
@@ -10869,9 +10869,9 @@ module Type.Reflection.Unsafe where
data TypeRep a where
...
mkTrApp :: forall k1 k2 (a :: k1 -> k2) (b :: k1). TypeRep a -> TypeRep b -> TypeRep (a b)
- mkTrCon :: forall k (a :: k). TyCon -> [ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep] -> TypeRep a
+ mkTrCon :: forall k (a :: k). TyCon -> [ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep] -> TypeRep a
mkTyCon :: GHC.Internal.Base.String -> GHC.Internal.Base.String -> GHC.Internal.Base.String -> GHC.Types.Int -> KindRep -> TyCon
- someTypeRepFingerprint :: ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep -> GHC.Internal.Fingerprint.Type.Fingerprint
+ someTypeRepFingerprint :: ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep -> GHC.Internal.Fingerprint.Type.Fingerprint
tyConFingerprint :: TyCon -> GHC.Internal.Fingerprint.Type.Fingerprint
tyConKindArgs :: TyCon -> GHC.Types.Int
tyConKindRep :: TyCon -> KindRep
@@ -11202,9 +11202,9 @@ instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.I
instance forall a. (GHC.Classes.Ord a, GHC.Internal.Enum.Bounded a) => GHC.Internal.Base.Monoid (Data.Semigroup.Max a) -- Defined in ‘Data.Semigroup’
instance forall a. (GHC.Classes.Ord a, GHC.Internal.Enum.Bounded a) => GHC.Internal.Base.Monoid (Data.Semigroup.Min a) -- Defined in ‘Data.Semigroup’
instance forall m. GHC.Internal.Base.Monoid m => GHC.Internal.Base.Monoid (Data.Semigroup.WrappedMonoid m) -- Defined in ‘Data.Semigroup’
-instance GHC.Internal.Base.Monoid ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types.Event -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types’
-instance GHC.Internal.Base.Monoid ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types.EventLifetime -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types’
-instance GHC.Internal.Base.Monoid ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types.Lifetime -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Internal.Base.Monoid ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types.Event -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Internal.Base.Monoid ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types.EventLifetime -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Internal.Base.Monoid ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types.Lifetime -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types’
instance forall k (f :: k -> *) (p :: k) (g :: k -> *). (GHC.Internal.Base.Monoid (f p), GHC.Internal.Base.Monoid (g p)) => GHC.Internal.Base.Monoid ((GHC.Internal.Generics.:*:) f g p) -- Defined in ‘GHC.Internal.Generics’
instance forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1). GHC.Internal.Base.Monoid (f (g p)) => GHC.Internal.Base.Monoid ((GHC.Internal.Generics.:.:) f g p) -- Defined in ‘GHC.Internal.Generics’
instance forall a. (GHC.Internal.Generics.Generic a, GHC.Internal.Base.Monoid (GHC.Internal.Generics.Rep a ())) => GHC.Internal.Base.Monoid (GHC.Internal.Generics.Generically a) -- Defined in ‘GHC.Internal.Generics’
@@ -11260,9 +11260,9 @@ instance forall a. GHC.Internal.Base.Semigroup (Data.Semigroup.Last a) -- Define
instance forall a. GHC.Classes.Ord a => GHC.Internal.Base.Semigroup (Data.Semigroup.Max a) -- Defined in ‘Data.Semigroup’
instance forall a. GHC.Classes.Ord a => GHC.Internal.Base.Semigroup (Data.Semigroup.Min a) -- Defined in ‘Data.Semigroup’
instance forall m. GHC.Internal.Base.Monoid m => GHC.Internal.Base.Semigroup (Data.Semigroup.WrappedMonoid m) -- Defined in ‘Data.Semigroup’
-instance GHC.Internal.Base.Semigroup ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types.Event -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types’
-instance GHC.Internal.Base.Semigroup ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types.EventLifetime -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types’
-instance GHC.Internal.Base.Semigroup ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types.Lifetime -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Internal.Base.Semigroup ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types.Event -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Internal.Base.Semigroup ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types.EventLifetime -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Internal.Base.Semigroup ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types.Lifetime -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types’
instance forall k (f :: k -> *) (p :: k) (g :: k -> *). (GHC.Internal.Base.Semigroup (f p), GHC.Internal.Base.Semigroup (g p)) => GHC.Internal.Base.Semigroup ((GHC.Internal.Generics.:*:) f g p) -- Defined in ‘GHC.Internal.Generics’
instance forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1). GHC.Internal.Base.Semigroup (f (g p)) => GHC.Internal.Base.Semigroup ((GHC.Internal.Generics.:.:) f g p) -- Defined in ‘GHC.Internal.Generics’
instance forall a. (GHC.Internal.Generics.Generic a, GHC.Internal.Base.Semigroup (GHC.Internal.Generics.Rep a ())) => GHC.Internal.Base.Semigroup (GHC.Internal.Generics.Generically a) -- Defined in ‘GHC.Internal.Generics’
@@ -11390,20 +11390,20 @@ instance GHC.Internal.Control.Monad.Fix.MonadFix Data.Semigroup.First -- Defined
instance GHC.Internal.Control.Monad.Fix.MonadFix Data.Semigroup.Last -- Defined in ‘Data.Semigroup’
instance GHC.Internal.Control.Monad.Fix.MonadFix Data.Semigroup.Max -- Defined in ‘Data.Semigroup’
instance GHC.Internal.Control.Monad.Fix.MonadFix Data.Semigroup.Min -- Defined in ‘Data.Semigroup’
-instance forall (a :: * -> * -> *) b c. (ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable a, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable b, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable c, GHC.Internal.Data.Data.Data (a b c)) => GHC.Internal.Data.Data.Data (Control.Applicative.WrappedArrow a b c) -- Defined in ‘Control.Applicative’
-instance forall (m :: * -> *) a. (ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable m, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable a, GHC.Internal.Data.Data.Data (m a)) => GHC.Internal.Data.Data.Data (Control.Applicative.WrappedMonad m a) -- Defined in ‘Control.Applicative’
+instance forall (a :: * -> * -> *) b c. (ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable a, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable b, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable c, GHC.Internal.Data.Data.Data (a b c)) => GHC.Internal.Data.Data.Data (Control.Applicative.WrappedArrow a b c) -- Defined in ‘Control.Applicative’
+instance forall (m :: * -> *) a. (ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable m, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable a, GHC.Internal.Data.Data.Data (m a)) => GHC.Internal.Data.Data.Data (Control.Applicative.WrappedMonad m a) -- Defined in ‘Control.Applicative’
instance forall a. GHC.Internal.Data.Data.Data a => GHC.Internal.Data.Data.Data (GHC.Internal.Functor.ZipList.ZipList a) -- Defined in ‘GHC.Internal.Functor.ZipList’
instance GHC.Internal.Data.Data.Data Data.Array.Byte.ByteArray -- Defined in ‘Data.Array.Byte’
-instance forall s. ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable s => GHC.Internal.Data.Data.Data (Data.Array.Byte.MutableByteArray s) -- Defined in ‘Data.Array.Byte’
+instance forall s. ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable s => GHC.Internal.Data.Data.Data (Data.Array.Byte.MutableByteArray s) -- Defined in ‘Data.Array.Byte’
instance forall a. GHC.Internal.Data.Data.Data a => GHC.Internal.Data.Data.Data (Data.Complex.Complex a) -- Defined in ‘Data.Complex’
-instance forall i j (a :: i) (b :: j). (ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable i, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable j, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable a, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable b, a ~~ b) => GHC.Internal.Data.Data.Data (a GHC.Internal.Data.Type.Equality.:~~: b) -- Defined in ‘GHC.Internal.Data.Data’
+instance forall i j (a :: i) (b :: j). (ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable i, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable j, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable a, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable b, a ~~ b) => GHC.Internal.Data.Data.Data (a GHC.Internal.Data.Type.Equality.:~~: b) -- Defined in ‘GHC.Internal.Data.Data’
instance GHC.Internal.Data.Data.Data GHC.Internal.Data.Semigroup.Internal.All -- Defined in ‘GHC.Internal.Data.Data’
instance GHC.Internal.Data.Data.Data GHC.Internal.Data.Semigroup.Internal.Any -- Defined in ‘GHC.Internal.Data.Data’
instance forall a b. (GHC.Internal.Data.Data.Data a, GHC.Internal.Data.Data.Data b, GHC.Internal.Ix.Ix a) => GHC.Internal.Data.Data.Data (GHC.Internal.Arr.Array a b) -- Defined in ‘GHC.Internal.Data.Data’
instance GHC.Internal.Data.Data.Data GHC.Internal.Generics.Associativity -- Defined in ‘GHC.Internal.Data.Data’
instance GHC.Internal.Data.Data.Data GHC.Types.Bool -- Defined in ‘GHC.Internal.Data.Data’
instance GHC.Internal.Data.Data.Data GHC.Types.Char -- Defined in ‘GHC.Internal.Data.Data’
-instance forall k a (b :: k). (ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable k, GHC.Internal.Data.Data.Data a, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable b) => GHC.Internal.Data.Data.Data (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Data’
+instance forall k a (b :: k). (ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable k, GHC.Internal.Data.Data.Data a, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable b) => GHC.Internal.Data.Data.Data (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Data’
instance forall a. GHC.Internal.Data.Data.Data a => GHC.Internal.Data.Data.Data (GHC.Internal.Foreign.C.ConstPtr.ConstPtr a) -- Defined in ‘GHC.Internal.Data.Data’
instance GHC.Internal.Data.Data.Data GHC.Internal.Generics.DecidedStrictness -- Defined in ‘GHC.Internal.Data.Data’
instance GHC.Internal.Data.Data.Data GHC.Types.Double -- Defined in ‘GHC.Internal.Data.Data’
@@ -11451,10 +11451,10 @@ instance GHC.Internal.Data.Data.Data GHC.Internal.Word.Word32 -- Defined in ‘G
instance GHC.Internal.Data.Data.Data GHC.Internal.Word.Word64 -- Defined in ‘GHC.Internal.Data.Data’
instance GHC.Internal.Data.Data.Data GHC.Internal.Word.Word8 -- Defined in ‘GHC.Internal.Data.Data’
instance GHC.Internal.Data.Data.Data GHC.Internal.Foreign.Ptr.WordPtr -- Defined in ‘GHC.Internal.Data.Data’
-instance forall k (a :: k). (ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable k, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable a) => GHC.Internal.Data.Data.Data (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
-instance forall k1 (f :: k1 -> *) k2 (g :: k2 -> k1) (a :: k2). (ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable a, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable f, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable g, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable k1, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable k2, GHC.Internal.Data.Data.Data (f (g a))) => GHC.Internal.Data.Data.Data (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
-instance [safe] forall k (f :: k -> *) (g :: k -> *) (a :: k). (ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable a, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable f, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable g, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable k, GHC.Internal.Data.Data.Data (f a), GHC.Internal.Data.Data.Data (g a)) => GHC.Internal.Data.Data.Data (Data.Functor.Product.Product f g a) -- Defined in ‘Data.Functor.Product’
-instance [safe] forall k (f :: k -> *) (g :: k -> *) (a :: k). (ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable a, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable f, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable g, ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.Typeable k, GHC.Internal.Data.Data.Data (f a), GHC.Internal.Data.Data.Data (g a)) => GHC.Internal.Data.Data.Data (Data.Functor.Sum.Sum f g a) -- Defined in ‘Data.Functor.Sum’
+instance forall k (a :: k). (ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable k, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable a) => GHC.Internal.Data.Data.Data (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
+instance forall k1 (f :: k1 -> *) k2 (g :: k2 -> k1) (a :: k2). (ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable a, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable f, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable g, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable k1, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable k2, GHC.Internal.Data.Data.Data (f (g a))) => GHC.Internal.Data.Data.Data (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
+instance [safe] forall k (f :: k -> *) (g :: k -> *) (a :: k). (ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable a, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable f, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable g, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable k, GHC.Internal.Data.Data.Data (f a), GHC.Internal.Data.Data.Data (g a)) => GHC.Internal.Data.Data.Data (Data.Functor.Product.Product f g a) -- Defined in ‘Data.Functor.Product’
+instance [safe] forall k (f :: k -> *) (g :: k -> *) (a :: k). (ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable a, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable f, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable g, ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.Typeable k, GHC.Internal.Data.Data.Data (f a), GHC.Internal.Data.Data.Data (g a)) => GHC.Internal.Data.Data.Data (Data.Functor.Sum.Sum f g a) -- Defined in ‘Data.Functor.Sum’
instance forall a b. (GHC.Internal.Data.Data.Data a, GHC.Internal.Data.Data.Data b) => GHC.Internal.Data.Data.Data (Data.Semigroup.Arg a b) -- Defined in ‘Data.Semigroup’
instance forall a. GHC.Internal.Data.Data.Data a => GHC.Internal.Data.Data.Data (Data.Semigroup.First a) -- Defined in ‘Data.Semigroup’
instance forall a. GHC.Internal.Data.Data.Data a => GHC.Internal.Data.Data.Data (Data.Semigroup.Last a) -- Defined in ‘Data.Semigroup’
@@ -11520,7 +11520,7 @@ instance GHC.Internal.Data.Type.Equality.TestEquality GHC.Internal.TypeLits.SCha
instance GHC.Internal.Data.Type.Equality.TestEquality GHC.Internal.TypeLits.SSymbol -- Defined in ‘GHC.Internal.TypeLits’
instance forall k (a :: k). GHC.Internal.Data.Type.Equality.TestEquality ((GHC.Internal.Data.Type.Equality.:~:) a) -- Defined in ‘GHC.Internal.Data.Type.Equality’
instance forall k1 k (a :: k1). GHC.Internal.Data.Type.Equality.TestEquality ((GHC.Internal.Data.Type.Equality.:~~:) a) -- Defined in ‘GHC.Internal.Data.Type.Equality’
-instance forall k. GHC.Internal.Data.Type.Equality.TestEquality ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.TypeRep -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal’
+instance forall k. GHC.Internal.Data.Type.Equality.TestEquality ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.TypeRep -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal’
instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1). GHC.Internal.Data.Type.Equality.TestEquality f => GHC.Internal.Data.Type.Equality.TestEquality (Data.Functor.Compose.Compose f g) -- Defined in ‘Data.Functor.Compose’
instance forall a k (b :: k). GHC.Internal.Enum.Bounded a => GHC.Internal.Enum.Bounded (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Functor.Const’
instance forall a. GHC.Internal.Enum.Bounded a => GHC.Internal.Enum.Bounded (GHC.Internal.Data.Bits.And a) -- Defined in ‘GHC.Internal.Data.Bits’
@@ -11717,7 +11717,7 @@ instance GHC.Internal.Exception.Type.Exception GHC.Internal.Control.Exception.Ba
instance GHC.Internal.Exception.Type.Exception GHC.Internal.Control.Exception.Base.RecUpdError -- Defined in ‘GHC.Internal.Control.Exception.Base’
instance GHC.Internal.Exception.Type.Exception GHC.Internal.Control.Exception.Base.TypeError -- Defined in ‘GHC.Internal.Control.Exception.Base’
instance GHC.Internal.Exception.Type.Exception GHC.Internal.Data.Dynamic.Dynamic -- Defined in ‘GHC.Internal.Data.Dynamic’
-instance [safe] GHC.Internal.Exception.Type.Exception ghc-internal-9.1002.0:GHC.Internal.IO.Handle.Lock.Common.FileLockingNotSupported -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.IO.Handle.Lock.Common’
+instance [safe] GHC.Internal.Exception.Type.Exception ghc-internal-9.1001.0:GHC.Internal.IO.Handle.Lock.Common.FileLockingNotSupported -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.IO.Handle.Lock.Common’
instance GHC.Internal.Exception.Type.Exception GHC.Internal.IOPort.IOPortException -- Defined in ‘GHC.Internal.IOPort’
instance [safe] GHC.Internal.Exception.Type.Exception System.Timeout.Timeout -- Defined in ‘System.Timeout’
instance forall a k (b :: k). GHC.Internal.Float.Floating a => GHC.Internal.Float.Floating (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Functor.Const’
@@ -12389,8 +12389,8 @@ instance GHC.Internal.Show.Show GHC.Internal.Data.Data.DataRep -- Defined in ‘
instance GHC.Internal.Show.Show GHC.Internal.Data.Data.DataType -- Defined in ‘GHC.Internal.Data.Data’
instance GHC.Internal.Show.Show GHC.Internal.Data.Data.Fixity -- Defined in ‘GHC.Internal.Data.Data’
instance forall k (s :: k). GHC.Internal.Show.Show (GHC.Internal.Data.Proxy.Proxy s) -- Defined in ‘GHC.Internal.Data.Proxy’
-instance GHC.Internal.Show.Show ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal’
-instance forall k (a :: k). GHC.Internal.Show.Show (ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.TypeRep a) -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal’
+instance GHC.Internal.Show.Show ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal’
+instance forall k (a :: k). GHC.Internal.Show.Show (ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.TypeRep a) -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal’
instance GHC.Internal.Show.Show GHC.Internal.Data.Dynamic.Dynamic -- Defined in ‘GHC.Internal.Data.Dynamic’
instance forall a b. (GHC.Internal.Show.Show a, GHC.Internal.Show.Show b) => GHC.Internal.Show.Show (GHC.Internal.Data.Either.Either a b) -- Defined in ‘GHC.Internal.Data.Either’
instance forall k (a :: k). Data.Fixed.HasResolution a => GHC.Internal.Show.Show (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
@@ -12461,13 +12461,13 @@ instance GHC.Internal.Show.Show GHC.Internal.Foreign.C.Types.CWchar -- Defined i
instance forall a. GHC.Internal.Show.Show (GHC.Internal.Foreign.C.ConstPtr.ConstPtr a) -- Defined in ‘GHC.Internal.Foreign.C.ConstPtr’
instance forall a b. (GHC.Internal.Ix.Ix a, GHC.Internal.Show.Show a, GHC.Internal.Show.Show b) => GHC.Internal.Show.Show (GHC.Internal.Arr.Array a b) -- Defined in ‘GHC.Internal.Arr’
instance GHC.Internal.Show.Show GHC.Internal.ByteOrder.ByteOrder -- Defined in ‘GHC.Internal.ByteOrder’
-instance GHC.Internal.Show.Show ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types.Event -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types’
-instance GHC.Internal.Show.Show ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types.EventLifetime -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types’
-instance GHC.Internal.Show.Show ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types.Lifetime -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types’
-instance GHC.Internal.Show.Show ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types.Timeout -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types’
-instance GHC.Internal.Show.Show ghc-internal-9.1002.0:GHC.Internal.Event.Manager.FdKey -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Event.Manager’
-instance GHC.Internal.Show.Show ghc-internal-9.1002.0:GHC.Internal.Event.Manager.State -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Event.Manager’
-instance GHC.Internal.Show.Show ghc-internal-9.1002.0:GHC.Internal.Event.TimerManager.State -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Event.TimerManager’
+instance GHC.Internal.Show.Show ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types.Event -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Internal.Show.Show ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types.EventLifetime -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Internal.Show.Show ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types.Lifetime -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Internal.Show.Show ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types.Timeout -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Internal.Show.Show ghc-internal-9.1001.0:GHC.Internal.Event.Manager.FdKey -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Event.Manager’
+instance GHC.Internal.Show.Show ghc-internal-9.1001.0:GHC.Internal.Event.Manager.State -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Event.Manager’
+instance GHC.Internal.Show.Show ghc-internal-9.1001.0:GHC.Internal.Event.TimerManager.State -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Event.TimerManager’
instance GHC.Internal.Show.Show GHC.Internal.Fingerprint.Type.Fingerprint -- Defined in ‘GHC.Internal.Fingerprint.Type’
instance GHC.Internal.Show.Show GHC.Types.Double -- Defined in ‘GHC.Internal.Float’
instance GHC.Internal.Show.Show GHC.Types.Float -- Defined in ‘GHC.Internal.Float’
@@ -12500,7 +12500,7 @@ instance GHC.Internal.Show.Show GHC.Internal.IO.Handle.Types.Handle -- Defined i
instance GHC.Internal.Show.Show GHC.Internal.IO.Handle.Types.HandleType -- Defined in ‘GHC.Internal.IO.Handle.Types’
instance GHC.Internal.Show.Show GHC.Internal.IO.Handle.Types.Newline -- Defined in ‘GHC.Internal.IO.Handle.Types’
instance GHC.Internal.Show.Show GHC.Internal.IO.Handle.Types.NewlineMode -- Defined in ‘GHC.Internal.IO.Handle.Types’
-instance [safe] GHC.Internal.Show.Show ghc-internal-9.1002.0:GHC.Internal.IO.Handle.Lock.Common.FileLockingNotSupported -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.IO.Handle.Lock.Common’
+instance [safe] GHC.Internal.Show.Show ghc-internal-9.1001.0:GHC.Internal.IO.Handle.Lock.Common.FileLockingNotSupported -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.IO.Handle.Lock.Common’
instance GHC.Internal.Show.Show GHC.Internal.IO.Handle.HandlePosn -- Defined in ‘GHC.Internal.IO.Handle’
instance GHC.Internal.Show.Show GHC.Internal.IO.IOMode.IOMode -- Defined in ‘GHC.Internal.IO.IOMode’
instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.CCFlags -- Defined in ‘GHC.Internal.RTS.Flags’
@@ -12595,8 +12595,8 @@ instance GHC.Classes.Eq GHC.Internal.Data.Data.ConstrRep -- Defined in ‘GHC.In
instance GHC.Classes.Eq GHC.Internal.Data.Data.DataRep -- Defined in ‘GHC.Internal.Data.Data’
instance GHC.Classes.Eq GHC.Internal.Data.Data.Fixity -- Defined in ‘GHC.Internal.Data.Data’
instance forall k (s :: k). GHC.Classes.Eq (GHC.Internal.Data.Proxy.Proxy s) -- Defined in ‘GHC.Internal.Data.Proxy’
-instance GHC.Classes.Eq ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal’
-instance forall k (a :: k). GHC.Classes.Eq (ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.TypeRep a) -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal’
+instance GHC.Classes.Eq ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal’
+instance forall k (a :: k). GHC.Classes.Eq (ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.TypeRep a) -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal’
instance forall a b. (GHC.Classes.Eq a, GHC.Classes.Eq b) => GHC.Classes.Eq (GHC.Internal.Data.Either.Either a b) -- Defined in ‘GHC.Internal.Data.Either’
instance forall k (a :: k). GHC.Classes.Eq (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Classes.Eq (f (g a)) => GHC.Classes.Eq (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
@@ -12672,13 +12672,13 @@ instance forall a. GHC.Classes.Eq (GHC.Internal.Foreign.C.ConstPtr.ConstPtr a) -
instance forall i e. (GHC.Internal.Ix.Ix i, GHC.Classes.Eq e) => GHC.Classes.Eq (GHC.Internal.Arr.Array i e) -- Defined in ‘GHC.Internal.Arr’
instance forall s i e. GHC.Classes.Eq (GHC.Internal.Arr.STArray s i e) -- Defined in ‘GHC.Internal.Arr’
instance GHC.Classes.Eq GHC.Internal.ByteOrder.ByteOrder -- Defined in ‘GHC.Internal.ByteOrder’
-instance GHC.Classes.Eq ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types.Event -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types’
-instance GHC.Classes.Eq ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types.EventLifetime -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types’
-instance GHC.Classes.Eq ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types.Lifetime -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Event.Internal.Types’
-instance GHC.Classes.Eq ghc-internal-9.1002.0:GHC.Internal.Event.Manager.FdKey -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Event.Manager’
-instance GHC.Classes.Eq ghc-internal-9.1002.0:GHC.Internal.Event.Manager.State -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Event.Manager’
+instance GHC.Classes.Eq ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types.Event -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Classes.Eq ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types.EventLifetime -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Classes.Eq ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types.Lifetime -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Classes.Eq ghc-internal-9.1001.0:GHC.Internal.Event.Manager.FdKey -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Event.Manager’
+instance GHC.Classes.Eq ghc-internal-9.1001.0:GHC.Internal.Event.Manager.State -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Event.Manager’
instance GHC.Classes.Eq GHC.Internal.Event.TimeOut.TimeoutKey -- Defined in ‘GHC.Internal.Event.TimeOut’
-instance GHC.Classes.Eq ghc-internal-9.1002.0:GHC.Internal.Event.TimerManager.State -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Event.TimerManager’
+instance GHC.Classes.Eq ghc-internal-9.1001.0:GHC.Internal.Event.TimerManager.State -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Event.TimerManager’
instance GHC.Classes.Eq GHC.Internal.Stack.Types.SrcLoc -- Defined in ‘GHC.Internal.Stack.Types’
instance GHC.Classes.Eq GHC.Internal.Exts.SpecConstrAnnotation -- Defined in ‘GHC.Internal.Exts’
instance GHC.Classes.Eq GHC.Internal.Fingerprint.Type.Fingerprint -- Defined in ‘GHC.Internal.Fingerprint.Type’
@@ -12773,8 +12773,8 @@ instance GHC.Classes.Ord GHC.Internal.Unicode.GeneralCategory -- Defined in ‘G
instance forall k (a :: k) (b :: k). GHC.Classes.Ord (a GHC.Internal.Data.Type.Equality.:~: b) -- Defined in ‘GHC.Internal.Data.Type.Equality’
instance forall k1 k2 (a :: k1) (b :: k2). GHC.Classes.Ord (a GHC.Internal.Data.Type.Equality.:~~: b) -- Defined in ‘GHC.Internal.Data.Type.Equality’
instance forall k (s :: k). GHC.Classes.Ord (GHC.Internal.Data.Proxy.Proxy s) -- Defined in ‘GHC.Internal.Data.Proxy’
-instance GHC.Classes.Ord ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal’
-instance forall k (a :: k). GHC.Classes.Ord (ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal.TypeRep a) -- Defined in ‘ghc-internal-9.1002.0:GHC.Internal.Data.Typeable.Internal’
+instance GHC.Classes.Ord ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal’
+instance forall k (a :: k). GHC.Classes.Ord (ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal.TypeRep a) -- Defined in ‘ghc-internal-9.1001.0:GHC.Internal.Data.Typeable.Internal’
instance forall a b. (GHC.Classes.Ord a, GHC.Classes.Ord b) => GHC.Classes.Ord (GHC.Internal.Data.Either.Either a b) -- Defined in ‘GHC.Internal.Data.Either’
instance forall k (a :: k). GHC.Classes.Ord (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Classes.Ord (f (g a)) => GHC.Classes.Ord (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
=====================================
testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
=====================================
@@ -315,7 +315,7 @@ module Control.Exception.Backtrace where
type BacktraceMechanism :: *
data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
type Backtraces :: *
- data Backtraces = Backtraces {btrCostCentre :: GHC.Internal.Maybe.Maybe (GHC.Internal.Ptr.Ptr GHC.Internal.Stack.CCS.CostCentreStack), btrHasCallStack :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.Types.CallStack, btrExecutionStack :: GHC.Internal.Maybe.Maybe [GHC.Internal.ExecutionStack.Internal.Location], btrIpe :: GHC.Internal.Maybe.Maybe [GHC.Internal.Stack.CloneStack.StackEntry]}
+ data Backtraces = ...
collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Types.IO Backtraces
displayBacktraces :: Backtraces -> GHC.Internal.Base.String
getBacktraceMechanismState :: BacktraceMechanism -> GHC.Types.IO GHC.Types.Bool
@@ -5187,7 +5187,6 @@ module GHC.Constants where
module GHC.Desugar where
-- Safety: Safe
- (>>>) :: forall (arr :: * -> * -> *) a b c. GHC.Internal.Control.Arrow.Arrow arr => arr a b -> arr b c -> arr a c
type AnnotationWrapper :: *
data AnnotationWrapper = forall a. GHC.Internal.Data.Data.Data a => AnnotationWrapper a
toAnnotationWrapper :: forall a. GHC.Internal.Data.Data.Data a => a -> AnnotationWrapper
=====================================
testsuite/tests/interface-stability/base-exports.stdout-mingw32
=====================================
@@ -315,7 +315,7 @@ module Control.Exception.Backtrace where
type BacktraceMechanism :: *
data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
type Backtraces :: *
- data Backtraces = Backtraces {btrCostCentre :: GHC.Internal.Maybe.Maybe (GHC.Internal.Ptr.Ptr GHC.Internal.Stack.CCS.CostCentreStack), btrHasCallStack :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.Types.CallStack, btrExecutionStack :: GHC.Internal.Maybe.Maybe [GHC.Internal.ExecutionStack.Internal.Location], btrIpe :: GHC.Internal.Maybe.Maybe [GHC.Internal.Stack.CloneStack.StackEntry]}
+ data Backtraces = ...
collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Types.IO Backtraces
displayBacktraces :: Backtraces -> GHC.Internal.Base.String
getBacktraceMechanismState :: BacktraceMechanism -> GHC.Types.IO GHC.Types.Bool
=====================================
testsuite/tests/interface-stability/base-exports.stdout-ws-32
=====================================
@@ -315,7 +315,7 @@ module Control.Exception.Backtrace where
type BacktraceMechanism :: *
data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
type Backtraces :: *
- data Backtraces = Backtraces {btrCostCentre :: GHC.Internal.Maybe.Maybe (GHC.Internal.Ptr.Ptr GHC.Internal.Stack.CCS.CostCentreStack), btrHasCallStack :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.Types.CallStack, btrExecutionStack :: GHC.Internal.Maybe.Maybe [GHC.Internal.ExecutionStack.Internal.Location], btrIpe :: GHC.Internal.Maybe.Maybe [GHC.Internal.Stack.CloneStack.StackEntry]}
+ data Backtraces = ...
collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Types.IO Backtraces
displayBacktraces :: Backtraces -> GHC.Internal.Base.String
getBacktraceMechanismState :: BacktraceMechanism -> GHC.Types.IO GHC.Types.Bool
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1b256e6399c2453f18837a5b6e1efa4…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1b256e6399c2453f18837a5b6e1efa4…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 2 commits: level imports: Check the level of exported identifiers
by Marge Bot (@marge-bot) 07 Aug '25
by Marge Bot (@marge-bot) 07 Aug '25
07 Aug '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
467b2357 by Matthew Pickering at 2025-08-07T01:48:07-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
- - - - -
9988a241 by fendor at 2025-08-07T01:48:07-04:00
Bump GHC on darwin CI to 9.10.1
- - - - -
18 changed files:
- .gitlab/darwin/toolchain.nix
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Types/Name/Reader.hs
- + testsuite/tests/splice-imports/DodgyLevelExport.hs
- + testsuite/tests/splice-imports/DodgyLevelExport.stderr
- + testsuite/tests/splice-imports/DodgyLevelExportA.hs
- + testsuite/tests/splice-imports/LevelImportExports.hs
- + testsuite/tests/splice-imports/LevelImportExports.stdout
- + testsuite/tests/splice-imports/LevelImportExportsA.hs
- testsuite/tests/splice-imports/Makefile
- + testsuite/tests/splice-imports/ModuleExport.hs
- + testsuite/tests/splice-imports/ModuleExport.stderr
- + testsuite/tests/splice-imports/ModuleExportA.hs
- + testsuite/tests/splice-imports/ModuleExportB.hs
- + testsuite/tests/splice-imports/T26090.hs
- + testsuite/tests/splice-imports/T26090.stderr
- + testsuite/tests/splice-imports/T26090A.hs
- testsuite/tests/splice-imports/all.T
Changes:
=====================================
.gitlab/darwin/toolchain.nix
=====================================
@@ -16,18 +16,17 @@ let
ghcBindists = let version = ghc.version; in {
aarch64-darwin = hostPkgs.fetchurl {
url = "https://downloads.haskell.org/ghc/${version}/ghc-${version}-aarch64-apple-d…";
- sha256 = "sha256-c1GTMJf3/yiW/t4QL532EswD5JVlgA4getkfsxj4TaA=";
+ sha256 = "sha256-/6+DtdeossBJIMbjkJwL4h3eJ7rzgNCV+ifoQKOi6AQ=";
};
x86_64-darwin = hostPkgs.fetchurl {
url = "https://downloads.haskell.org/ghc/${version}/ghc-${version}-x86_64-apple-da…";
- sha256 = "sha256-LrYniMG0phsvyW6dhQC+3ompvzcxnwAe6GezEqqzoTQ=";
+ sha256 = "sha256-jPIhiJMOENesUnDUJeIaPatgavc6ZVSTY5NFIAxlC+k=";
};
};
ghc = pkgs.stdenv.mkDerivation rec {
- # Using 9.6.2 because of #24050
- version = "9.6.2";
+ version = "9.10.1";
name = "ghc";
src = ghcBindists.${pkgs.stdenv.hostPlatform.system};
configureFlags = [
=====================================
compiler/GHC/Tc/Gen/Export.hs
=====================================
@@ -23,6 +23,7 @@ import GHC.Rename.Module
import GHC.Rename.Names
import GHC.Rename.Env
import GHC.Rename.Unbound ( reportUnboundName )
+import GHC.Rename.Splice
import GHC.Unit.Module
import GHC.Unit.Module.Imported
import GHC.Unit.Module.Warnings
@@ -312,7 +313,7 @@ exports_from_avail Nothing rdr_env _imports _this_mod
; addDiagnostic
(TcRnMissingExportList $ moduleName _this_mod)
; let avails =
- map fix_faminst . gresToAvailInfo
+ map fix_faminst . gresToAvailInfo . mapMaybe pickLevelZeroGRE
. filter isLocalGRE . globalRdrEnvElts $ rdr_env
; return (Nothing, emptyDefaultEnv, avails, []) }
where
@@ -384,6 +385,7 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod
= do { let { exportValid = (mod `elem` imported_modules)
|| (moduleName this_mod == mod)
; gre_prs = pickGREsModExp mod (globalRdrEnvElts rdr_env)
+ -- NB: this filters out non level 0 exports
; new_gres = [ gre'
| (gre, _) <- gre_prs
, gre' <- expand_tyty_gre gre ]
@@ -451,6 +453,7 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod
let avail = availFromGRE gre
name = greName gre
+ checkThLocalNameNoLift (ieLWrappedUserRdrName l name)
occs' <- check_occs occs ie [gre]
(export_warn_spans', dont_warn_export', warn_txt_rn)
<- process_warning export_warn_spans
@@ -499,6 +502,7 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod
occs' <- check_occs occs ie [gre]
return (Just avail, occs', exp_dflts)
+ checkThLocalNameNoLift (ieLWrappedUserRdrName l name)
(export_warn_spans', dont_warn_export', warn_txt_rn)
<- process_warning export_warn_spans
dont_warn_export
@@ -526,6 +530,7 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod
all_gres = par : all_kids
all_names = map greName all_gres
+ checkThLocalNameNoLift (ieLWrappedUserRdrName l name)
occs' <- check_occs occs ie all_gres
(export_warn_spans', dont_warn_export', warn_txt_rn)
<- process_warning export_warn_spans
@@ -563,6 +568,7 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod
all_gres = par : all_kids
all_names = map greName all_gres
+ checkThLocalNameNoLift (ieLWrappedUserRdrName l name)
occs' <- check_occs occs ie all_gres
(export_warn_spans', dont_warn_export', warn_txt_rn)
<- process_warning export_warn_spans
@@ -589,17 +595,19 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod
lookup_ie_kids_all :: IE GhcPs -> LIEWrappedName GhcPs -> GlobalRdrElt
-> RnM [GlobalRdrElt]
- lookup_ie_kids_all ie (L _ rdr) gre =
+ lookup_ie_kids_all ie (L _loc rdr) gre =
do { let name = greName gre
gres = findChildren kids_env name
- ; addUsedKids (ieWrappedName rdr) gres
- ; when (null gres) $
+ -- We only choose level 0 exports when filling in part of an export list implicitly.
+ ; let kids_0 = mapMaybe pickLevelZeroGRE gres
+ ; addUsedKids (ieWrappedName rdr) kids_0
+ ; when (null kids_0) $
if isTyConName name
then addTcRnDiagnostic (TcRnDodgyExports gre)
else -- This occurs when you export T(..), but
-- only import T abstractly, or T is a synonym.
addErr (TcRnExportHiddenComponents ie)
- ; return gres }
+ ; return kids_0 }
-------------
@@ -696,6 +704,10 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod
addUsedKids parent_rdr kid_gres
= addUsedGREs ExportDeprecationWarnings (pickGREs parent_rdr kid_gres)
+
+ieLWrappedUserRdrName :: LIEWrappedName GhcPs -> Name -> LIdOccP GhcRn
+ieLWrappedUserRdrName l n = fmap (\rdr -> WithUserRdr rdr n) $ ieLWrappedName l
+
-- | In what namespaces should we go looking for an import/export item
-- that is out of scope, for suggestions in error messages?
ieWrappedNameWhatLooking :: IEWrappedName GhcPs -> WhatLooking
@@ -800,6 +812,7 @@ lookupChildrenExport parent_gre rdr_items = mapAndReportM doOne rdr_items
; return (L l (IEName noExtField (L (l2l l) ub)), gre)}
FoundChild child@(GRE { gre_name = child_nm, gre_par = par }) ->
do { checkPatSynParent spec_parent par child_nm
+ ; checkThLocalNameNoLift (ieLWrappedUserRdrName n child_nm)
; return (replaceLWrappedName n child_nm, child)
}
IncorrectParent p c gs -> failWithDcErr (parentGRE_name p) (greName c) gs
=====================================
compiler/GHC/Types/Name/Reader.hs
=====================================
@@ -69,7 +69,7 @@ module GHC.Types.Name.Reader (
lookupGRE_Name,
lookupGRE_FieldLabel,
getGRE_NameQualifier_maybes,
- transformGREs, pickGREs, pickGREsModExp,
+ transformGREs, pickGREs, pickGREsModExp, pickLevelZeroGRE,
-- * GlobalRdrElts
availFromGRE,
@@ -144,7 +144,7 @@ import GHC.Utils.Panic
import GHC.Utils.Binary
import Control.DeepSeq
-import Control.Monad ( guard )
+import Control.Monad ( guard , (>=>) )
import Data.Data
import Data.List ( sort )
import qualified Data.List.NonEmpty as NE
@@ -641,7 +641,7 @@ greParent = gre_par
greInfo :: GlobalRdrElt -> GREInfo
greInfo = gre_info
-greLevels :: GlobalRdrElt -> Set.Set ImportLevel
+greLevels :: GlobalRdrEltX info -> Set.Set ImportLevel
greLevels g =
if gre_lcl g then Set.singleton NormalLevel
else Set.fromList (bagToList (fmap (is_level . is_decl) (gre_imp g)))
@@ -1604,7 +1604,14 @@ pickGREsModExp :: ModuleName -> [GlobalRdrEltX info] -> [(GlobalRdrEltX info,Glo
--
-- Used only for the 'module M' item in export list;
-- see 'GHC.Tc.Gen.Export.exports_from_avail'
-pickGREsModExp mod gres = mapMaybe (pickBothGRE mod) gres
+-- This function also only chooses GREs which are at level zero.
+pickGREsModExp mod gres = mapMaybe (pickLevelZeroGRE >=> pickBothGRE mod) gres
+
+pickLevelZeroGRE :: GlobalRdrEltX info -> Maybe (GlobalRdrEltX info)
+pickLevelZeroGRE gre =
+ if NormalLevel `Set.member` greLevels gre
+ then Just gre
+ else Nothing
-- | isBuiltInSyntax filter out names for built-in syntax They
-- just clutter up the environment (esp tuples), and the
=====================================
testsuite/tests/splice-imports/DodgyLevelExport.hs
=====================================
@@ -0,0 +1,5 @@
+{-# LANGUAGE ExplicitLevelImports #-}
+module DodgyLevelExport ( T(..) ) where
+
+import quote DodgyLevelExportA
+import DodgyLevelExportA (T)
=====================================
testsuite/tests/splice-imports/DodgyLevelExport.stderr
=====================================
@@ -0,0 +1,4 @@
+DodgyLevelExport.hs:2:27: warning: [GHC-75356] [-Wdodgy-exports (in -Wextra)]
+ The export item ‘T(..)’ suggests that
+ ‘T’ has (in-scope) constructors or record fields, but it has none
+
=====================================
testsuite/tests/splice-imports/DodgyLevelExportA.hs
=====================================
@@ -0,0 +1,3 @@
+module DodgyLevelExportA where
+
+data T = T { a :: Int }
=====================================
testsuite/tests/splice-imports/LevelImportExports.hs
=====================================
@@ -0,0 +1,6 @@
+{-# LANGUAGE ExplicitLevelImports #-}
+module LevelImportExports ( module LevelImportExportsA, T(..) ) where
+
+import quote LevelImportExportsA
+import splice LevelImportExportsA
+import LevelImportExportsA(a, T)
=====================================
testsuite/tests/splice-imports/LevelImportExports.stdout
=====================================
@@ -0,0 +1,6 @@
+[1 of 2] Compiling LevelImportExportsA ( LevelImportExportsA.hs, LevelImportExportsA.o )
+[2 of 2] Compiling LevelImportExports ( LevelImportExports.hs, LevelImportExports.o )
+exports:
+ LevelImportExportsA.a
+ LevelImportExportsA.T
+defaults:
=====================================
testsuite/tests/splice-imports/LevelImportExportsA.hs
=====================================
@@ -0,0 +1,6 @@
+module LevelImportExportsA where
+
+a = 100
+b = 100
+
+data T = T { c :: Int }
=====================================
testsuite/tests/splice-imports/Makefile
=====================================
@@ -24,5 +24,9 @@ SI10_oneshot:
"$(TEST_HC)" $(TEST_HC_OPTS) -c InstanceA.hs
"$(TEST_HC)" $(TEST_HC_OPTS) -c SI10.hs
+LevelImportExports:
+ "$(TEST_HC)" $(TEST_HC_OPTS) -haddock LevelImportExports.hs
+ "$(TEST_HC)" --show-iface LevelImportExports.hi | grep -A3 "^exports:"
+
clean:
rm -f *.o *.hi
=====================================
testsuite/tests/splice-imports/ModuleExport.hs
=====================================
@@ -0,0 +1,4 @@
+module ModuleExport where
+
+-- Should fail
+import ModuleExportA (a)
=====================================
testsuite/tests/splice-imports/ModuleExport.stderr
=====================================
@@ -0,0 +1,3 @@
+ModuleExport.hs:4:23: error: [GHC-61689]
+ Module ‘ModuleExportA’ does not export ‘a’.
+
=====================================
testsuite/tests/splice-imports/ModuleExportA.hs
=====================================
@@ -0,0 +1,8 @@
+{-# LANGUAGE ExplicitLevelImports #-}
+-- Module export only exports level 0 things (b)
+module ModuleExportA (module ModuleExportB) where
+
+-- Everything at level 1
+import quote ModuleExportB
+-- Only b at level 0
+import ModuleExportB (b)
=====================================
testsuite/tests/splice-imports/ModuleExportB.hs
=====================================
@@ -0,0 +1,6 @@
+module ModuleExportB where
+
+a = ()
+b = ()
+
+
=====================================
testsuite/tests/splice-imports/T26090.hs
=====================================
@@ -0,0 +1,10 @@
+{-# LANGUAGE ExplicitLevelImports, TemplateHaskell #-}
+module T26090 ( a --varaible
+ , T(..) -- WithAll
+ , S(s) -- With
+ , R -- Abs
+ ) where
+
+import quote T26090A
+import T26090A (T(T), S)
+
=====================================
testsuite/tests/splice-imports/T26090.stderr
=====================================
@@ -0,0 +1,16 @@
+T26090.hs:2:17: error: [GHC-28914]
+ • Level error: ‘a’ is bound at level 1 but used at level 0
+ • Available from the imports:
+ • imported from ‘T26090A’ at 1 at T26090.hs:8:1-20
+
+T26090.hs:4:17: error: [GHC-28914]
+ • Level error: ‘s’ is bound at level 1 but used at level 0
+ • Available from the imports:
+ • imported from ‘T26090A’ at 1 at T26090.hs:8:1-20
+ • In the export: S(s)
+
+T26090.hs:5:17: error: [GHC-28914]
+ • Level error: ‘R’ is bound at level 1 but used at level 0
+ • Available from the imports:
+ • imported from ‘T26090A’ at 1 at T26090.hs:8:1-20
+
=====================================
testsuite/tests/splice-imports/T26090A.hs
=====================================
@@ -0,0 +1,14 @@
+{-# LANGUAGE ExplicitLevelImports, TemplateHaskell #-}
+module T26090A where
+
+import Language.Haskell.TH
+
+a :: Q Exp
+a = [| True |]
+
+data T = T { t :: () }
+
+data S = S { s :: () }
+
+data R = R { r :: () }
+
=====================================
testsuite/tests/splice-imports/all.T
=====================================
@@ -48,3 +48,7 @@ test('SI35',
test('SI36', [extra_files(["SI36_A.hs", "SI36_B1.hs", "SI36_B2.hs", "SI36_B3.hs", "SI36_C1.hs", "SI36_C2.hs", "SI36_C3.hs"])], multimod_compile_fail, ['SI36', '-v0'])
test('T26087', [], multimod_compile_fail, ['T26087A', ''])
test('T26088', [], multimod_compile_fail, ['T26088A', '-v0'])
+test('T26090', [], multimod_compile_fail, ['T26090', '-v0'])
+test('ModuleExport', [], multimod_compile_fail, ['ModuleExport', '-v0'])
+test('LevelImportExports', [], makefile_test, [])
+test('DodgyLevelExport', [], multimod_compile, ['DodgyLevelExport', '-v0 -Wdodgy-exports'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/61b099b69242dff7905e344f6f92a2…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/61b099b69242dff7905e344f6f92a2…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
07 Aug '25
Cheng Shao pushed new branch wip/romes/26227.bak at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/romes/26227.bak
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/bytecode-serialize-3] 2 commits: compiler: WIP GHC.ByteCode.Serialize
by Cheng Shao (@TerrorJack) 07 Aug '25
by Cheng Shao (@TerrorJack) 07 Aug '25
07 Aug '25
Cheng Shao pushed to branch wip/bytecode-serialize-3 at Glasgow Haskell Compiler / GHC
Commits:
636f8ce7 by Cheng Shao at 2025-08-07T03:38:16+00:00
compiler: WIP GHC.ByteCode.Serialize
- - - - -
b0b466a5 by Cheng Shao at 2025-08-07T03:38:39+00:00
driver: test bytecode roundtrip serialization
- - - - -
4 changed files:
- + compiler/GHC/ByteCode/Serialize.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Utils/Binary.hs
- compiler/ghc.cabal.in
Changes:
=====================================
compiler/GHC/ByteCode/Serialize.hs
=====================================
@@ -0,0 +1,296 @@
+{-# LANGUAGE MultiWayIf #-}
+{-# LANGUAGE RecordWildCards #-}
+{-# OPTIONS_GHC -Wno-orphans #-}
+
+module GHC.ByteCode.Serialize (testBinByteCode) where
+
+import GHC.Prelude
+import GHC.Utils.Binary
+import GHC.ByteCode.Breakpoints
+import GHC.ByteCode.Types
+import GHC.Utils.Exception
+import GHC.Data.FlatBag as FlatBag
+import GHCi.FFI
+import GHC.Builtin.PrimOps
+import GHC.Driver.Env
+import GHC.Types.Name
+import Data.Proxy
+import GHC.Data.FastString
+import Data.IORef
+import GHC.Types.Name.Cache
+import GHC.Types.SrcLoc
+import GHC.Types.SptEntry
+import GHC.Builtin.Types
+import GHC.Types.Id
+import Data.Word
+import qualified Data.ByteString.Lazy as LBS
+import qualified Data.Binary as Binary
+import GHCi.Message
+import Data.Foldable
+import Control.Monad
+import GHC.Iface.Binary
+import GHC.Utils.TmpFs
+import System.FilePath
+
+testBinByteCode :: HscEnv -> CompiledByteCode -> IO CompiledByteCode
+testBinByteCode hsc_env cbc = withSystemTempDirectory "ghc-bbc" $ \tmpdir -> do
+ let f = tmpdir </> "ghc-bbc"
+ roundtripBinByteCode hsc_env f cbc
+
+roundtripBinByteCode :: HscEnv -> FilePath -> CompiledByteCode -> IO CompiledByteCode
+roundtripBinByteCode hsc_env f cbc = do
+ writeBinByteCode f cbc
+ readBinByteCode hsc_env f
+
+readBinByteCode :: HscEnv -> FilePath -> IO CompiledByteCode
+readBinByteCode hsc_env f = do
+ bh' <- readBinMem f
+ bh <- addSerializableNameReader hsc_env bh'
+ getWithUserData (hsc_NC hsc_env) bh
+
+writeBinByteCode :: FilePath -> CompiledByteCode -> IO ()
+writeBinByteCode f cbc = do
+ bh' <- openBinMem (1024*1024)
+ bh <- addSerializableNameWriter bh'
+ putWithUserData QuietBinIFace NormalCompression bh cbc
+ writeBinMem bh f
+
+instance Binary CompiledByteCode where
+ get bh = do
+ bc_bcos <- get bh
+ bc_itbls_len <- get bh
+ bc_itbls <- replicateM bc_itbls_len $ do
+ nm <- getViaSerializableName bh
+ itbl <- get bh
+ pure (nm, itbl)
+ bc_strs_len <- get bh
+ bc_strs <-
+ replicateM bc_strs_len
+ $ (,)
+ <$> getViaSerializableName bh
+ <*> get bh
+ bc_breaks <- get bh
+ bc_spt_entries <- get bh
+ evaluate
+ CompiledByteCode
+ { bc_bcos,
+ bc_itbls,
+ bc_strs,
+ bc_breaks,
+ bc_spt_entries
+ }
+
+ put_ bh CompiledByteCode {..} = do
+ put_ bh bc_bcos
+ put_ bh $ length bc_itbls
+ for_ bc_itbls
+ $ \(nm, itbl) -> do
+ putViaSerializableName bh nm
+ put_ bh itbl
+ put_ bh $ length bc_strs
+ for_ bc_strs
+ $ \(nm, str) -> putViaSerializableName bh nm *> put_ bh str
+ put_ bh bc_breaks
+ put_ bh bc_spt_entries
+
+instance Binary InternalModBreaks where
+ get bh = InternalModBreaks <$> get bh <*> get bh
+
+ put_ bh InternalModBreaks {..} = put_ bh imodBreaks_breakInfo *> put_ bh imodBreaks_modBreaks
+
+instance Binary ModBreaks where
+ get bh = ModBreaks <$> get bh <*> get bh <*> get bh <*> get bh <*> get bh
+
+ put_ bh ModBreaks {..} = put_ bh modBreaks_locs *> put_ bh modBreaks_vars *> put_ bh modBreaks_decls *> put_ bh modBreaks_ccs *> put_ bh modBreaks_module
+
+instance Binary SrcSpan where
+ get bh = unBinSrcSpan <$> get bh
+
+ put_ bh = put_ bh . BinSrcSpan
+
+instance Binary CgBreakInfo where
+ put_ bh CgBreakInfo {..} = put_ bh cgb_tyvars *> put_ bh cgb_vars *> put_ bh cgb_resty *> put_ bh cgb_tick_id
+
+ get bh = CgBreakInfo <$> get bh <*> get bh <*> get bh <*> get bh
+
+instance Binary ConInfoTable where
+ get bh = Binary.decode . LBS.fromStrict <$> get bh
+
+ put_ bh = put_ bh . LBS.toStrict . Binary.encode
+
+
+instance Binary UnlinkedBCO where
+ get bh =
+ UnlinkedBCO
+ <$> getViaSerializableName bh
+ <*> get bh
+ <*> (Binary.decode . LBS.fromStrict <$> get bh)
+ <*> (Binary.decode . LBS.fromStrict <$> get bh)
+ <*> get bh
+ <*> get bh
+
+ put_ bh UnlinkedBCO {..} = do
+ putViaSerializableName bh unlinkedBCOName
+ put_ bh unlinkedBCOArity
+ put_ bh $ LBS.toStrict $ Binary.encode unlinkedBCOInstrs
+ put_ bh $ LBS.toStrict $ Binary.encode unlinkedBCOBitmap
+ put_ bh unlinkedBCOLits
+ put_ bh unlinkedBCOPtrs
+
+instance Binary BCOPtr where
+ get bh = do
+ t <- getByte bh
+ case t of
+ 0 -> BCOPtrName <$> getViaSerializableName bh
+ 1 -> BCOPtrPrimOp <$> get bh
+ 2 -> BCOPtrBCO <$> get bh
+ _ -> BCOPtrBreakArray <$> get bh
+
+ put_ bh ptr = case ptr of
+ BCOPtrName nm -> putByte bh 0 *> putViaSerializableName bh nm
+ BCOPtrPrimOp op -> putByte bh 1 *> put_ bh op
+ BCOPtrBCO bco -> putByte bh 2 *> put_ bh bco
+ BCOPtrBreakArray info_mod -> putByte bh 3 *> put_ bh info_mod
+
+instance Binary BCONPtr where
+ get bh = do
+ t <- getByte bh
+ case t of
+ 0 -> BCONPtrWord . fromIntegral <$> (get bh :: IO Word64)
+ 1 -> BCONPtrLbl <$> get bh
+ 2 -> BCONPtrItbl <$> getViaSerializableName bh
+ 3 -> BCONPtrAddr <$> getViaSerializableName bh
+ 4 -> BCONPtrStr <$> get bh
+ 5 -> BCONPtrFS <$> get bh
+ 6 -> BCONPtrFFIInfo <$> get bh
+ _ -> BCONPtrCostCentre <$> get bh
+
+ put_ bh ptr = case ptr of
+ BCONPtrWord lit -> putByte bh 0 *> put_ bh (fromIntegral lit :: Word64)
+ BCONPtrLbl sym -> putByte bh 1 *> put_ bh sym
+ BCONPtrItbl nm -> putByte bh 2 *> putViaSerializableName bh nm
+ BCONPtrAddr nm -> putByte bh 3 *> putViaSerializableName bh nm
+ BCONPtrStr str -> putByte bh 4 *> put_ bh str
+ BCONPtrFS fs -> putByte bh 5 *> put_ bh fs
+ BCONPtrFFIInfo ffi -> putByte bh 6 *> put_ bh ffi
+ BCONPtrCostCentre ibi -> putByte bh 7 *> put_ bh ibi
+
+instance Binary InternalBreakLoc where
+ get bh = InternalBreakLoc <$> get bh
+
+ put_ bh InternalBreakLoc {..} = put_ bh internalBreakLoc
+
+instance Binary BreakpointId where
+ get bh = BreakpointId <$> get bh <*> get bh
+
+ put_ bh BreakpointId {..} = put_ bh bi_tick_mod *> put_ bh bi_tick_index
+
+instance Binary InternalBreakpointId where
+ get bh = InternalBreakpointId <$> get bh <*> get bh
+
+ put_ bh InternalBreakpointId {..} = put_ bh ibi_info_mod *> put_ bh ibi_info_index
+
+instance Binary SptEntry where
+ get bh = do
+ nm <- getViaSerializableName bh
+ fp <- get bh
+ pure $ SptEntry (mkVanillaGlobal nm anyTy) fp
+
+ put_ bh (SptEntry nm fp) = putViaSerializableName bh (getName nm) *> put_ bh fp
+
+
+newtype SerializableName = SerializableName {unSerializableName :: Name}
+
+getViaSerializableName :: ReadBinHandle -> IO Name
+getViaSerializableName bh = case findUserDataReader Proxy bh of
+ BinaryReader f -> unSerializableName <$> f bh
+
+putViaSerializableName :: WriteBinHandle -> Name -> IO ()
+putViaSerializableName bh nm = case findUserDataWriter Proxy bh of
+ BinaryWriter f -> f bh $ SerializableName nm
+
+addSerializableNameWriter :: WriteBinHandle -> IO WriteBinHandle
+addSerializableNameWriter bh' =
+ evaluate
+ $ flip addWriterToUserData bh'
+ $ BinaryWriter
+ $ \bh
+ ( SerializableName
+ nm
+ ) ->
+ if
+ | isExternalName nm -> do
+ putByte bh 0
+ put_ bh nm
+ | otherwise -> do
+ putByte bh 1
+ put_ bh $ occNameFS (occName nm) `appendFS` mkFastString (show $ nameUnique nm)
+
+addSerializableNameReader :: HscEnv -> ReadBinHandle -> IO ReadBinHandle
+addSerializableNameReader HscEnv {..} bh' = do
+ nc <- evaluate hsc_NC
+ env_ref <- newIORef emptyOccEnv
+ evaluate $ flip addReaderToUserData bh' $ BinaryReader $ \bh -> do
+ t <- getByte bh
+ case t of
+ 0 -> do
+ nm <- get bh
+ evaluate $ SerializableName nm
+ _ -> do
+ occ <- mkVarOccFS <$> get bh
+ u <- takeUniqFromNameCache nc
+ nm' <- evaluate $ mkInternalName u occ noSrcSpan
+ fmap SerializableName
+ $ atomicModifyIORef' env_ref
+ $ \env -> case lookupOccEnv env occ of
+ Just nm -> (env, nm)
+ _ -> (extendOccEnv env occ nm', nm')
+
+instance Binary PrimOp where
+ get bh = (allThePrimOps !!) <$> get bh
+
+ put_ bh = put_ bh . primOpTag
+
+instance Binary FFIInfo where
+ get bh = FFIInfo <$> get bh <*> get bh
+
+ put_ bh FFIInfo {..} = put_ bh ffiInfoArgs *> put_ bh ffiInfoRet
+
+instance Binary FFIType where
+ get bh = do
+ t <- getByte bh
+ evaluate $ case t of
+ 0 -> FFIVoid
+ 1 -> FFIPointer
+ 2 -> FFIFloat
+ 3 -> FFIDouble
+ 4 -> FFISInt8
+ 5 -> FFISInt16
+ 6 -> FFISInt32
+ 7 -> FFISInt64
+ 8 -> FFIUInt8
+ 9 -> FFIUInt16
+ 10 -> FFIUInt32
+ _ -> FFIUInt64
+
+ put_ bh t = putByte bh $ case t of
+ FFIVoid -> 0
+ FFIPointer -> 1
+ FFIFloat -> 2
+ FFIDouble -> 3
+ FFISInt8 -> 4
+ FFISInt16 -> 5
+ FFISInt32 -> 6
+ FFISInt64 -> 7
+ FFIUInt8 -> 8
+ FFIUInt16 -> 9
+ FFIUInt32 -> 10
+ FFIUInt64 -> 11
+
+
+instance (Binary a) => Binary (FlatBag a) where
+ get bh = do
+ xs <- get bh
+ evaluate $ FlatBag.fromList (fromIntegral $ length xs) xs
+
+ put_ bh = put_ bh . FlatBag.elemsFlatBag
=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -305,6 +305,8 @@ import Data.Bifunctor
import qualified GHC.Unit.Home.Graph as HUG
import GHC.Unit.Home.PackageTable
+import GHC.ByteCode.Serialize
+
{- **********************************************************************
%* *
Initialisation
@@ -2169,7 +2171,8 @@ generateByteCode :: HscEnv
-> ModLocation
-> IO (CompiledByteCode, [FilePath])
generateByteCode hsc_env cgguts mod_location = do
- (hasStub, comp_bc) <- hscInteractive hsc_env cgguts mod_location
+ (hasStub, comp_bc') <- hscInteractive hsc_env cgguts mod_location
+ comp_bc <- testBinByteCode hsc_env comp_bc'
compile_for_interpreter hsc_env $ \ i_env -> do
stub_o <- traverse (compileForeign i_env LangC) hasStub
foreign_files_o <- traverse (uncurry (compileForeign i_env)) (cgi_foreign_files cgguts)
=====================================
compiler/GHC/Utils/Binary.hs
=====================================
@@ -929,6 +929,12 @@ instance Binary Char where
put_ bh c = put_ bh (fromIntegral (ord c) :: Word32)
get bh = do x <- get bh; return $! (chr (fromIntegral (x :: Word32)))
+instance Binary Word where
+ put_ bh i = put_ bh (fromIntegral i :: Word64)
+ get bh = do
+ x <- get bh
+ return $! (fromIntegral (x :: Word64))
+
instance Binary Int where
put_ bh i = put_ bh (fromIntegral i :: Int64)
get bh = do
=====================================
compiler/ghc.cabal.in
=====================================
@@ -228,6 +228,7 @@ Library
GHC.ByteCode.InfoTable
GHC.ByteCode.Instr
GHC.ByteCode.Linker
+ GHC.ByteCode.Serialize
GHC.ByteCode.Types
GHC.Cmm
GHC.Cmm.BlockId
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2e6004b419b0c451e9590b9d2a5545…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2e6004b419b0c451e9590b9d2a5545…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/fix-26109] Resolving issues #20645 and #26109
by recursion-ninja (@recursion-ninja) 07 Aug '25
by recursion-ninja (@recursion-ninja) 07 Aug '25
07 Aug '25
recursion-ninja pushed to branch wip/fix-26109 at Glasgow Haskell Compiler / GHC
Commits:
9fbadea8 by Recursion Ninja at 2025-08-06T21:10:52-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#
- - - - -
2 changed files:
- compiler/GHC/CmmToLlvm/CodeGen.hs
- testsuite/tests/numeric/should_run/foundation.hs
Changes:
=====================================
compiler/GHC/CmmToLlvm/CodeGen.hs
=====================================
@@ -230,23 +230,25 @@ genCall t@(PrimTarget (MO_Prefetch_Data localityInt)) [] args
statement $ Expr $ Call StdCall fptr (argVars' ++ argSuffix) []
| otherwise = panic $ "prefetch locality level integer must be between 0 and 3, given: " ++ (show localityInt)
--- Handle PopCnt, Clz, Ctz, and BSwap that need to only convert arg
--- and return types
-genCall t@(PrimTarget (MO_PopCnt w)) dsts args =
- genCallSimpleCast w t dsts args
-
-genCall t@(PrimTarget (MO_Pdep w)) dsts args =
- genCallSimpleCast2 w t dsts args
-genCall t@(PrimTarget (MO_Pext w)) dsts args =
- genCallSimpleCast2 w t dsts args
-genCall t@(PrimTarget (MO_Clz w)) dsts args =
- genCallSimpleCast w t dsts args
-genCall t@(PrimTarget (MO_Ctz w)) dsts args =
- genCallSimpleCast w t dsts args
-genCall t@(PrimTarget (MO_BSwap w)) dsts args =
- genCallSimpleCast w t dsts args
-genCall t@(PrimTarget (MO_BRev w)) dsts args =
- genCallSimpleCast w t dsts args
+-- Handle PopCnt, Clz, Ctz, BRev, and BSwap that need to only convert arg and return types
+genCall (PrimTarget op@(MO_PopCnt w)) [dst] args =
+ genCallSimpleCast w op dst args
+genCall (PrimTarget op@(MO_Clz w)) [dst] args =
+ genCallSimpleCast w op dst args
+genCall (PrimTarget op@(MO_Ctz w)) [dst] args =
+ genCallSimpleCast w op dst args
+genCall (PrimTarget op@(MO_BRev w)) [dst] args =
+ genCallSimpleCast w op dst args
+genCall (PrimTarget op@(MO_BSwap w)) [dst] args =
+ genCallSimpleCast w op dst args
+
+-- Handle Pdep and Pext that (may) require using a type with a larger bit-width
+-- than the specified but width. This register width-extension is particualarly
+-- necessary for W8 and W16.
+genCall (PrimTarget op@(MO_Pdep w)) [dst] args =
+ genCallCastWithMinWidthOf W32 w op dst args
+genCall (PrimTarget op@(MO_Pext w)) [dst] args =
+ genCallCastWithMinWidthOf W32 w op dst args
genCall (PrimTarget (MO_AtomicRMW width amop)) [dst] [addr, n] = runStmtsDecls $ do
addrVar <- exprToVarW addr
@@ -640,63 +642,35 @@ genCallExtract _ _ _ _ =
-- since GHC only really has i32 and i64 types and things like Word8 are backed
-- by an i32 and just present a logical i8 range. So we must handle conversions
-- from i32 to i8 explicitly as LLVM is strict about types.
-genCallSimpleCast :: Width -> ForeignTarget -> [CmmFormal] -> [CmmActual]
- -> LlvmM StmtData
-genCallSimpleCast w t@(PrimTarget op) [dst] args = do
- let width = widthToLlvmInt w
- dstTy = cmmToLlvmType $ localRegType dst
-
- fname <- cmmPrimOpFunctions op
- (fptr, _, top3) <- getInstrinct fname width [width]
-
- (dstV, _dst_ty) <- getCmmReg (CmmLocal dst)
-
- let (_, arg_hints) = foreignTargetHints t
- let args_hints = zip args arg_hints
- (argsV, stmts2, top2) <- arg_vars args_hints ([], nilOL, [])
- (argsV', stmts4) <- castVars Signed $ zip argsV [width]
- (retV, s1) <- doExpr width $ Call StdCall fptr argsV' []
- (retVs', stmts5) <- castVars (cmmPrimOpRetValSignage op) [(retV,dstTy)]
- let retV' = singletonPanic "genCallSimpleCast" retVs'
- let s2 = Store retV' dstV Nothing []
-
- let stmts = stmts2 `appOL` stmts4 `snocOL`
- s1 `appOL` stmts5 `snocOL` s2
- return (stmts, top2 ++ top3)
-genCallSimpleCast _ _ dsts _ =
- panic ("genCallSimpleCast: " ++ show (length dsts) ++ " dsts")
-
--- Handle simple function call that only need simple type casting, of the form:
--- truncate arg >>= \a -> call(a) >>= zext
---
--- since GHC only really has i32 and i64 types and things like Word8 are backed
--- by an i32 and just present a logical i8 range. So we must handle conversions
--- from i32 to i8 explicitly as LLVM is strict about types.
-genCallSimpleCast2 :: Width -> ForeignTarget -> [CmmFormal] -> [CmmActual]
- -> LlvmM StmtData
-genCallSimpleCast2 w t@(PrimTarget op) [dst] args = do
- let width = widthToLlvmInt w
- dstTy = cmmToLlvmType $ localRegType dst
-
- fname <- cmmPrimOpFunctions op
- (fptr, _, top3) <- getInstrinct fname width (const width <$> args)
-
- (dstV, _dst_ty) <- getCmmReg (CmmLocal dst)
-
- let (_, arg_hints) = foreignTargetHints t
- let args_hints = zip args arg_hints
- (argsV, stmts2, top2) <- arg_vars args_hints ([], nilOL, [])
- (argsV', stmts4) <- castVars Signed $ zip argsV (const width <$> argsV)
- (retV, s1) <- doExpr width $ Call StdCall fptr argsV' []
- (retVs', stmts5) <- castVars (cmmPrimOpRetValSignage op) [(retV,dstTy)]
- let retV' = singletonPanic "genCallSimpleCast2" retVs'
- let s2 = Store retV' dstV Nothing []
-
- let stmts = stmts2 `appOL` stmts4 `snocOL`
- s1 `appOL` stmts5 `snocOL` s2
+genCallSimpleCast :: Width -> CallishMachOp -> CmmFormal -> [CmmActual]
+ -> LlvmM StmtData
+genCallSimpleCast w = genCallCastWithMinWidthOf w w
+
+-- Handle extension case that the element should be extend to a larger bit-width
+-- for the operation and subsequently truncated, of the form:
+-- extend arg >>= \a -> call(a) >>= truncate
+genCallCastWithMinWidthOf :: Width -> Width -> CallishMachOp -> CmmFormal
+ -> [CmmActual] -> LlvmM StmtData
+genCallCastWithMinWidthOf minW specW op dst args = do
+ let width = widthToLlvmInt $ max minW specW
+ argsW = const width <$> args
+ dstType = cmmToLlvmType $ localRegType dst
+ signage = cmmPrimOpRetValSignage op
+
+ fname <- cmmPrimOpFunctions op
+ (fptr, _, top3) <- getInstrinct fname width argsW
+ (dstV, _dst_ty) <- getCmmReg (CmmLocal dst)
+ let (_, arg_hints) = foreignTargetHints $ PrimTarget op
+ let args_hints = zip args arg_hints
+ (argsV, stmts2, top2) <- arg_vars args_hints ([], nilOL, [])
+ (argsV', stmts4) <- castVars signage $ zip argsV argsW
+ (retV, s1) <- doExpr width $ Call StdCall fptr argsV' []
+ (retV', stmts5) <- castVar signage retV dstType
+ let s2 = Store retV' dstV Nothing []
+
+ let stmts = stmts2 `appOL` stmts4 `snocOL` s1 `snocOL`
+ stmts5 `snocOL` s2
return (stmts, top2 ++ top3)
-genCallSimpleCast2 _ _ dsts _ =
- panic ("genCallSimpleCast2: " ++ show (length dsts) ++ " dsts")
-- | Create a function pointer from a target.
getFunPtrW :: (LMString -> LlvmType) -> ForeignTarget
@@ -811,11 +785,39 @@ castVar signage v t | getVarType v == t
Signed -> LM_Sext
Unsigned -> LM_Zext
-
cmmPrimOpRetValSignage :: CallishMachOp -> Signage
cmmPrimOpRetValSignage mop = case mop of
MO_Pdep _ -> Unsigned
MO_Pext _ -> Unsigned
+ -- If the result of a Bit-Reverse is treated as signed,
+ -- an positive input can result in an negative output, i.e.:
+ --
+ -- identity(0x03) = 0x03 = 00000011
+ -- breverse(0x03) = 0xC0 = 11000000
+ --
+ -- Now if an extension is performed after the operation to
+ -- promote a smaller bit-width value into a larger bit-width
+ -- type, it is expected that the /bit-wise/ operations will
+ -- not be treated /numerically/ as signed.
+ --
+ -- To illustrate the difference, consider how a signed extension
+ -- for the type i16 to i32 differs for out values above:
+ -- ext_zeroed(i32, breverse(0x03)) = 0x00C0 = 0000000011000000
+ -- ext_signed(i32, breverse(0x03)) = 0xFFC0 = 1111111111000000
+ --
+ -- Here we can see that the former output is the expected result
+ -- of a bit-wise operation which needs to be promoted to a larger
+ -- bit-width type. The latter output is not desirable when we must
+ -- constraining a value into a range of i16 within an i32 type.
+ --
+ -- Hence we always treat the "signage" as unsigned for Bit-Reverse!
+ MO_BRev _ -> Unsigned
+
+ -- The same reasoning applied to Bit-Reverse above applies to Byte-Swap;
+ -- we do not want to sign extend a number whose sign may have changed!
+ MO_BSwap _ -> Unsigned
+
+ -- All other cases, default to preserving the numeric sign when extending.
_ -> Signed
-- | Decide what C function to use to implement a CallishMachOp
@@ -954,8 +956,8 @@ cmmPrimOpFunctions mop = do
W256 -> fsLit "llvm.x86.bmi.pdep.256"
W512 -> fsLit "llvm.x86.bmi.pdep.512"
| otherwise -> case w of
- W8 -> fsLit "hs_pdep8"
- W16 -> fsLit "hs_pdep16"
+ W8 -> fsLit "hs_pdep32"
+ W16 -> fsLit "hs_pdep32"
W32 -> fsLit "hs_pdep32"
W64 -> fsLit "hs_pdep64"
W128 -> fsLit "hs_pdep128"
@@ -971,8 +973,8 @@ cmmPrimOpFunctions mop = do
W256 -> fsLit "llvm.x86.bmi.pext.256"
W512 -> fsLit "llvm.x86.bmi.pext.512"
| otherwise -> case w of
- W8 -> fsLit "hs_pext8"
- W16 -> fsLit "hs_pext16"
+ W8 -> fsLit "hs_pext32"
+ W16 -> fsLit "hs_pext32"
W32 -> fsLit "hs_pext32"
W64 -> fsLit "hs_pext64"
W128 -> fsLit "hs_pext128"
=====================================
testsuite/tests/numeric/should_run/foundation.hs
=====================================
@@ -24,6 +24,7 @@ module Main
( main
) where
+import Data.Bits (Bits((.&.), bit))
import Data.Word
import Data.Int
import GHC.Natural
@@ -655,8 +656,8 @@ testPrimops = Group "primop"
, testPrimop "ctz32#" Primop.ctz32# Wrapper.ctz32#
, testPrimop "ctz64#" Primop.ctz64# Wrapper.ctz64#
, testPrimop "ctz#" Primop.ctz# Wrapper.ctz#
- , testPrimop "byteSwap16#" Primop.byteSwap16# Wrapper.byteSwap16#
- , testPrimop "byteSwap32#" Primop.byteSwap32# Wrapper.byteSwap32#
+ , testPrimop "byteSwap16#" (16 `LowerBitsAreDefined` Primop.byteSwap16#) (16 `LowerBitsAreDefined` Wrapper.byteSwap16#)
+ , testPrimop "byteSwap32#" (32 `LowerBitsAreDefined` Primop.byteSwap32#) (32 `LowerBitsAreDefined` Wrapper.byteSwap32#)
, testPrimop "byteSwap64#" Primop.byteSwap64# Wrapper.byteSwap64#
, testPrimop "byteSwap#" Primop.byteSwap# Wrapper.byteSwap#
, testPrimop "bitReverse8#" Primop.bitReverse8# Wrapper.bitReverse8#
@@ -672,6 +673,34 @@ testPrimops = Group "primop"
, testPrimop "narrow32Word#" Primop.narrow32Word# Wrapper.narrow32Word#
]
+-- | A special data-type for representing functions where,
+-- since only some number of the lower bits are defined,
+-- testing for strict equality in the undefined upper bits is not appropriate!
+-- Without using this data-type, false-positive failures will be reported
+-- when the undefined bit regions do not match, even though the equality of bits
+-- in this undefined region has no bearing on correctness.
+data LowerBitsAreDefined =
+ LowerBitsAreDefined
+ { definedLowerWidth :: Word
+ -- ^ The (strictly-non-negative) number of least-significant bits
+ -- for which the attached function is defined.
+ , undefinedBehavior :: (Word# -> Word#)
+ -- ^ Function with undefined behavior for some of its most significant bits.
+ }
+
+instance TestPrimop LowerBitsAreDefined where
+ testPrimop s l r = Property s $ \ (uWord#-> x0) ->
+ let -- Create a mask to unset all bits in the undefined area,
+ -- leaving set bits only in the area of defined behavior.
+ -- Since the upper bits are undefined,
+ -- if the function defines behavior for the lower N bits,
+ -- then /only/ the lower N bits are preserved,
+ -- and the upper WORDSIZE - N bits are discarded.
+ mask = bit (fromEnum (definedLowerWidth r)) - 1
+ valL = wWord# (undefinedBehavior l x0) .&. mask
+ valR = wWord# (undefinedBehavior r x0) .&. mask
+ in valL === valR
+
instance TestPrimop (Char# -> Char# -> Int#) where
testPrimop s l r = Property s $ \ (uChar#-> x0) (uChar#-> x1) -> wInt# (l x0 x1) === wInt# (r x0 x1)
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9fbadea8fb900c08c812a29716c3c40…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9fbadea8fb900c08c812a29716c3c40…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/bytecode-serialize-3] 76 commits: Specialise: Improve specialisation by refactoring interestingDict
by Cheng Shao (@TerrorJack) 07 Aug '25
by Cheng Shao (@TerrorJack) 07 Aug '25
07 Aug '25
Cheng Shao pushed to branch wip/bytecode-serialize-3 at Glasgow Haskell Compiler / GHC
Commits:
f707bab4 by Andreas Klebinger at 2025-07-12T14:56:16+01:00
Specialise: Improve specialisation by refactoring interestingDict
This MR addresses #26051, which concerns missed type-class specialisation.
The main payload of the MR is to completely refactor the key function
`interestingDict` in GHC.Core.Opt.Specialise
The main change is that we now also look at the structure of the
dictionary we consider specializing on, rather than only the type.
See the big `Note [Interesting dictionary arguments]`
- - - - -
ca7a9d42 by Simon Peyton Jones at 2025-07-12T14:56:16+01:00
Treat tuple dictionaries uniformly; don't unbox them
See `Note [Do not unbox class dictionaries]` in DmdAnal.hs,
sep (DNB1).
This MR reverses the plan in #23398, which suggested a special case to
unbox tuple dictionaries in worker/wrapper. But:
- This was the cause of a pile of complexity in the specialiser (#26158)
- Even with that complexity, specialision was still bad, very bad
See https://gitlab.haskell.org/ghc/ghc/-/issues/19747#note_626297
And it's entirely unnecessary! Specialision works fine without
unboxing tuple dictionaries.
- - - - -
be7296c9 by Andreas Klebinger at 2025-07-12T14:56:16+01:00
Remove complex special case from the type-class specialiser
There was a pretty tricky special case in Specialise which is no
longer necessary.
* Historical Note [Floating dictionaries out of cases]
* #26158
* #19747 https://gitlab.haskell.org/ghc/ghc/-/issues/19747#note_626297
This MR removes it. Hooray.
- - - - -
4acf3a86 by Ben Gamari at 2025-07-15T05:46:32-04:00
configure: bump version to 9.15
- - - - -
45efaf71 by Teo Camarasu at 2025-07-15T05:47:13-04:00
rts/nonmovingGC: remove n_free
We remove the nonmovingHeap.n_free variable.
We wanted this to track the length of nonmovingHeap.free.
But this isn't possible to do atomically.
When this isn't accurate we can get a segfault by going past the end of
the list.
Instead, we just count the length of the list when we grab it in
nonmovingPruneFreeSegment.
Resolves #26186
- - - - -
c635f164 by Ben Gamari at 2025-07-15T14:05:54-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
- - - - -
637bb538 by Ben Gamari at 2025-07-15T14:05:55-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.
- - - - -
d3cd4ec8 by Wen Kokke at 2025-07-15T14:06:39-04:00
Fix documentation for heap profile ID
- - - - -
73082769 by Ben Gamari at 2025-07-15T16:56:38-04:00
Bump win32-tarballs to v0.9
- - - - -
3b63b254 by Ben Gamari at 2025-07-15T16:56:39-04:00
rts/LoadArchive: Handle null terminated string tables
As of `llvm-ar` now emits filename tables terminated with null
characters instead of the usual POSIX `/\n` sequence.
Fixes #26150.
- - - - -
195f6527 by Tamar Christina at 2025-07-15T16:56:39-04:00
rts: rename label so name doesn't conflict with param
- - - - -
63373b95 by Tamar Christina at 2025-07-15T16:56:39-04:00
rts: Handle API set symbol versioning conflicts
- - - - -
48e9aa3e by Tamar Christina at 2025-07-15T16:56:39-04:00
rts: Mark API set symbols as HIDDEN and correct symbol type
- - - - -
959e827a by Tamar Christina at 2025-07-15T16:56:39-04:00
rts: Implement WEAK EXTERNAL undef redirection by target symbol name
- - - - -
65f19293 by Ben Gamari at 2025-07-15T16:56:39-04:00
rts/LoadArchive: Handle string table entries terminated with /
llvm-ar appears to terminate string table entries with `/\n` [1]. This
matters in the case of thin archives, since the filename is used. In the
past this worked since `llvm-ar` would produce archives with "small"
filenames when possible. However, now it appears to always use the
string table.
[1] https://github.com/llvm/llvm-project/blob/bfb686bb5ba503e9386dc899e1ebbe248…
- - - - -
9cbb3ef5 by Ben Gamari at 2025-07-15T16:56:39-04:00
testsuite: Mark T12497 as fixed
Thanks to the LLVM toolchain update.
Closes #22694.
- - - - -
2854407e by Ben Gamari at 2025-07-15T16:56:39-04:00
testsuite: Accept new output of T11223_link_order_a_b_2_fail on Windows
The archive member number changed due to the fact that llvm-ar now uses a
string table.
- - - - -
28439593 by Ben Gamari at 2025-07-15T16:56:39-04:00
rts/linker/PEi386: Implement IMAGE_REL_AMD64_SECREL
This appears to now be used by libc++ as distributed by msys2.
- - - - -
2b053755 by Tamar Christina at 2025-07-15T16:56:39-04:00
rts: Cleanup merge resolution residue in lookupSymbolInDLL_PEi386 and make safe without dependent
- - - - -
e8acd2e7 by Wen Kokke at 2025-07-16T08:37:04-04:00
Remove the `profile_id` parameter from various RTS functions.
Various RTS functions took a `profile_id` parameter, intended to be used to
distinguish parallel heap profile breakdowns (e.g., `-hT` and `-hi`). However,
this feature was never implemented and the `profile_id` parameter was set to 0
throughout the RTS. This commit removes the parameter but leaves the hardcoded
profile ID in the functions that emit the encoded eventlog events as to not
change the protocol.
The affected functions are `traceHeapProfBegin`, `postHeapProfBegin`,
`traceHeapProfSampleString`, `postHeapProfSampleString`,
`traceHeapProfSampleCostCentre`, and `postHeapProfSampleCostCentre`.
- - - - -
76d392a2 by Wen Kokke at 2025-07-16T08:37:04-04:00
Make `traceHeapProfBegin` an init event.
- - - - -
bbaa44a7 by Peng Fan at 2025-07-16T16:50:42-04:00
NCG/LA64: Support finer-grained DBAR hints
For LA664 and newer uarchs, they have made finer granularity hints
available:
Bit4: ordering or completion (0: completion, 1: ordering)
Bit3: barrier for previous read (0: true, 1: false)
Bit2: barrier for previous write (0: true, 1: false)
Bit1: barrier for succeeding read (0: true, 1: false)
Bit0: barrier for succeeding write (0: true, 1: false)
And not affect the existing models because other hints are treated
as 'dbar 0' there.
- - - - -
7da86e16 by Andreas Klebinger at 2025-07-16T16:51:25-04:00
Disable -fprof-late-overloaded-calls for join points.
Currently GHC considers cost centres as destructive to
join contexts. Or in other words this is not considered valid:
join f x = ...
in
... -> scc<tick> jmp
This makes the functionality of `-fprof-late-overloaded-calls` not feasible
for join points in general. We used to try to work around this by putting the
ticks on the rhs of the join point rather than around the jump. However beyond
the loss of accuracy this was broken for recursive join points as we ended up
with something like:
rec-join f x = scc<tick> ... jmp f x
Which similarly is not valid as the tick once again destroys the tail call.
One might think we could limit ourselves to non-recursive tail calls and do
something clever like:
join f x = scc<tick> ...
in ... jmp f x
And sometimes this works! But sometimes the full rhs would look something like:
join g x = ....
join f x = scc<tick> ... -> jmp g x
Which, would again no longer be valid. I believe in the long run we can make
cost centre ticks non-destructive to join points. Or we could keep track of
where we are/are not allowed to insert a cost centre. But in the short term I will
simply disable the annotation of join calls under this flag.
- - - - -
7ee22fd5 by ARATA Mizuki at 2025-07-17T06:05:30-04:00
x86 NCG: Better lowering for shuffleFloatX4# and shuffleDoubleX2#
The new implementation
* make use of specialized instructions like (V)UNPCK{L,H}{PS,PD}, and
* do not require -mavx.
Close #26096
Co-authored-by: sheaf <sam.derbyshire(a)gmail.com>
- - - - -
c6cd2da1 by Jappie Klooster at 2025-07-17T06:06:20-04:00
Update interact docs to explain about buffering
We need to tell the user to set to the
appropriate buffer format.
Otherwise, this function may get randomly stuck,
or just behave confusingly.
issue: https://gitlab.haskell.org/ghc/ghc/-/issues/26131
NB, I'm running this with cabal *NOT* ghci. ghci messes with buffering anyway.
```haskell
interaction :: String -> String
interaction "jappie" = "hi"
interaction "jakob" = "hello"
interaction x = "unkown input: " <> x
main :: IO ()
main = interact interaction
```
so in my input (prefixed by `>`) I get:
```
> jappie
unkown input: jappie
```
we confirmed later this was due to lack of \n matching.
Anyway movnig on to more unexpected stuff:
```haskell
main :: IO ()
main = do
interact (concatMap interaction . lines)
```
get's stuck forever.
actually `^D` (ctrl+d) unstucks it and runs all input as expected.
for example you can get:
```
> sdfkds
> fakdsf
unkown input: sdfkdsunkown input: fakdsf
```
This program works!
```haskell
interaction :: String -> String
interaction "jappie" = "hi \n"
interaction "jakob" = "hello \n"
interaction x = "unkown input: " <> x <> "\n"
main :: IO ()
main = do
interact (concatMap interaction . lines)
```
the reason is that linebuffering is set for both in and output by default.
so lines eats the input lines, and all the \n postfixes make sure the buffer
is put out.
- - - - -
9fa590a6 by Zubin Duggal at 2025-07-17T06:07:03-04:00
fetch_gitlab: Ensure we copy users_guide.pdf and Haddock.pdf to the release docs directory
Fixes #24093
- - - - -
cc650b4b by Andrew Lelechenko at 2025-07-17T12:30:24-04:00
Add Data.List.NonEmpty.mapMaybe
As per https://github.com/haskell/core-libraries-committee/issues/337
- - - - -
360fa82c by Duncan Coutts at 2025-07-17T12:31:14-04:00
base: Deprecate GHC.Weak.Finalize.runFinalizerBatch
https://github.com/haskell/core-libraries-committee/issues/342
- - - - -
f4e8466c by Alan Zimmerman at 2025-07-17T12:31:55-04:00
EPA: Update exact printing based on GHC 9.14 tests
As a result of migrating the GHC ghc-9.14 branch tests to
ghc-exactprint in
https://github.com/alanz/ghc-exactprint/tree/ghc-9.14, a couple of
discrepancies were picked up
- The opening paren for a DefaultDecl was printed in the wrong place
- The import declaration level specifiers were not printed.
This commit adds those fixes, and some tests for them.
The tests brought to light that the ImportDecl ppr instance had not
been updated for level specifiers, so it updates that too.
- - - - -
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.
- - - - -
19cbb1b6 by Rodrigo Mesquita at 2025-08-06T20:31:22+00:00
cleanup: Move dehydrateCgBreakInfo to Stg2Bc
This no longer has anything to do with Core.
- - - - -
37d490ea by Rodrigo Mesquita at 2025-08-06T20:31:22+00:00
rts/Disassembler: Fix spacing of BRK_FUN
- - - - -
89c4244a by Rodrigo Mesquita at 2025-08-06T20:31:22+00:00
debugger: Fix bciPtr in Step-out
We need to use `BCO_NEXT` to move bciPtr to ix=1, because ix=0 points to
the instruction itself!
I do not understand how this didn't crash before.
- - - - -
d30850ac by Rodrigo Mesquita at 2025-08-06T20:31:23+00:00
debugger: Allow BRK_FUNs to head case continuation BCOs
When we start executing a BCO, we may want to yield to the scheduler:
this may be triggered by a heap/stack check, context switch, or a
breakpoint. To yield, we need to put the stack in a state such that
when execution is resumed we are back to where we yielded from.
Previously, a BKR_FUN could only head a function BCO because we only
knew how to construct a valid stack for yielding from one -- simply add
`apply_interp_info` + the BCO to resume executing. This is valid because
the stack at the start of run_BCO is headed by that BCO's arguments.
However, in case continuation BCOs (as per Note [Case continuation BCOs]),
we couldn't easily reconstruct a valid stack that could be resumed
because we dropped too soon the stack frames regarding the value
returned (stg_ret) and received (stg_ctoi) by that continuation.
This is especially tricky because of the variable type and size return
frames (e.g. pointer ret_p/ctoi_R1p vs a tuple ret_t/ctoi_t2).
The trick to being able to yield from a BRK_FUN at the start of a case
cont BCO is to stop removing the ret frame headers eagerly and instead
keep them until the BCO starts executing. The new layout at the start of
a case cont. BCO is described by the new Note [Stack layout when entering run_BCO].
Now, we keep the ret_* and ctoi_* frames when entering run_BCO.
A BRK_FUN is then executed if found, and the stack is yielded as-is with
the preserved ret and ctoi frames.
Then, a case cont BCO's instructions always SLIDE off the headers of the
ret and ctoi frames, in StgToByteCode.doCase, turning a stack like
| .... |
+---------------+
| fv2 |
+---------------+
| fv1 |
+---------------+
| BCO |
+---------------+
| stg_ctoi_ret_ |
+---------------+
| retval |
+---------------+
| stg_ret_..... |
+---------------+
into
| .... |
+---------------+
| fv2 |
+---------------+
| fv1 |
+---------------+
| retval |
+---------------+
for the remainder of the BCO.
Moreover, this more uniform approach of keeping the ret and ctoi frames
means we need less ad-hoc logic concerning the variable size of
ret_tuple vs ret_p/np frames in the code generator and interpreter:
Always keep the return to cont. stack intact at the start of run_BCO,
and the statically generated instructions will take care of adjusting
it.
Unlocks BRK_FUNs at the start of case cont. BCOs which will enable a
better user-facing step-out (#26042) which is free of the bugs the
current BRK_ALTS implementation suffers from (namely, using BRK_FUN
rather than BRK_ALTS in a case cont. means we'll never accidentally end
up in a breakpoint "deeper" than the continuation, because we stop at
the case cont itself rather than on the first breakpoint we evaluate
after it).
- - - - -
76bf3c30 by Rodrigo Mesquita at 2025-08-06T20:31:23+00:00
BRK_FUN with InternalBreakLocs for code-generation time breakpoints
At the start of a case continuation BCO, place a BRK_FUN.
This BRK_FUN uses the new "internal breakpoint location" -- allowing us
to come up with a valid source location for this breakpoint that is not associated with a source-level tick.
For case continuation BCOs, we use the last tick seen before it as the
source location. The reasoning is described in Note [Debugger: Stepout internal break locs].
Note how T26042c, which was broken because it displayed the incorrect
behavior of the previous step out when we'd end up at a deeper level
than the one from which we initiated step-out, is now fixed.
As of this commit, BRK_ALTS is now dead code and is thus dropped.
Note [Debugger: Stepout internal break locs]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Step-out tells the interpreter to run until the current function
returns to where it was called from, and stop there.
This is achieved by enabling the BRK_FUN found on the first RET_BCO
frame on the stack (See [Note Debugger: Step-out]).
Case continuation BCOs (which select an alternative branch) must
therefore be headed by a BRK_FUN. An example:
f x = case g x of <--- end up here
1 -> ...
2 -> ...
g y = ... <--- step out from here
- `g` will return a value to the case continuation BCO in `f`
- The case continuation BCO will receive the value returned from g
- Match on it and push the alternative continuation for that branch
- And then enter that alternative.
If we step-out of `g`, the first RET_BCO on the stack is the case
continuation of `f` -- execution should stop at its start, before
selecting an alternative. (One might ask, "why not enable the breakpoint
in the alternative instead?", because the alternative continuation is
only pushed to the stack *after* it is selected by the case cont. BCO)
However, the case cont. BCO is not associated with any source-level
tick, it is merely the glue code which selects alternatives which do
have source level ticks. Therefore, we have to come up at code
generation time with a breakpoint location ('InternalBreakLoc') to
display to the user when it is stopped there.
Our solution is to use the last tick seen just before reaching the case
continuation. This is robust because a case continuation will thus
always have a relevant breakpoint location:
- The source location will be the last source-relevant expression
executed before the continuation is pushed
- So the source location will point to the thing you've just stepped
out of
- Doing :step-local from there will put you on the selected
alternative (which at the source level may also be the e.g. next
line in a do-block)
Examples, using angle brackets (<<...>>) to denote the breakpoint span:
f x = case <<g x>> {- step in here -} of
1 -> ...
2 -> ...>
g y = <<...>> <--- step out from here
...
f x = <<case g x of <--- end up here, whole case highlighted
1 -> ...
2 -> ...>>
doing :step-local ...
f x = case g x of
1 -> <<...>> <--- stop in the alternative
2 -> ...
A second example based on T26042d2, where the source is a do-block IO
action, optimised to a chain of `case expressions`.
main = do
putStrLn "hello1"
<<f>> <--- step-in here
putStrLn "hello3"
putStrLn "hello4"
f = do
<<putStrLn "hello2.1">> <--- step-out from here
putStrLn "hello2.2"
...
main = do
putStrLn "hello1"
<<f>> <--- end up here again, the previously executed expression
putStrLn "hello3"
putStrLn "hello4"
doing step/step-local ...
main = do
putStrLn "hello1"
f
<<putStrLn "hello3">> <--- straight to the next line
putStrLn "hello4"
Finishes #26042
- - - - -
99fe54b5 by Rodrigo Mesquita at 2025-08-06T20:31:23+00:00
debugger: Re-use the last BreakpointId whole in step-out
Previously, to come up with a location to stop at for `:stepout`, we
would store the location of the last BreakpointId surrounding the
continuation, as described by Note [Debugger: Stepout internal break locs].
However, re-using just the location from the last source breakpoint
isn't sufficient to provide the necessary information in the break
location. Specifically, it wouldn't bind any variables at that location.
Really, there is no reason not to re-use the last breakpoint wholesale,
and re-use all the information we had there. Step-out should behave just
as if we had stopped at the call, but s.t. continuing will not
re-execute the call.
This commit updates the CgBreakInfo to always store a BreakpointId, be
it the original one or the one we're emulating (for step-out).
It makes variable bindings on :stepout work
- - - - -
2e6004b4 by Cheng Shao at 2025-08-07T00:20:10+00:00
WIP GHC.ByteCode.Serialize
- - - - -
247 changed files:
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- CODEOWNERS
- README.md
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/Breakpoints.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Linker.hs
- + compiler/GHC/ByteCode/Serialize.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/CmmToAsm/LA64/CodeGen.hs
- compiler/GHC/CmmToAsm/LA64/Instr.hs
- compiler/GHC/CmmToAsm/LA64/Ppr.hs
- compiler/GHC/CmmToAsm/X86/CodeGen.hs
- compiler/GHC/CmmToAsm/X86/Instr.hs
- compiler/GHC/CmmToAsm/X86/Ppr.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Make.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.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/Hs/ImpExp.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/Parser.y
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/StgToByteCode.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/Expr.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/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/Name/Cache.hs
- compiler/GHC/Types/Var.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Utils/Binary.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/diagnostics-as-json-schema-1_2.json
- docs/users_guide/eventlog-formats.rst
- docs/users_guide/exts/linear_types.rst
- docs/users_guide/exts/strict.rst
- docs/users_guide/profiling.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
- hadrian/stack.yaml
- hadrian/stack.yaml.lock
- libraries/base/changelog.md
- libraries/base/src/Control/Exception/Backtrace.hs
- libraries/base/src/Data/List/NonEmpty.hs
- libraries/base/src/GHC/Generics.hs
- libraries/base/src/GHC/Weak/Finalize.hs
- libraries/base/src/System/Console/GetOpt.hs
- libraries/ghc-internal/src/GHC/Internal/Data/OldList.hs
- libraries/ghc-internal/src/GHC/Internal/Float.hs
- libraries/ghc-internal/src/GHC/Internal/Real.hs
- libraries/ghc-internal/src/GHC/Internal/System/IO.hs
- libraries/ghci/GHCi/Debugger.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/Run.hs
- libraries/text
- m4/find_ld.m4
- mk/get-win32-tarballs.py
- rts/Disassembler.c
- rts/Exception.cmm
- rts/Interpreter.c
- rts/PrimOps.cmm
- rts/ProfHeap.c
- rts/Profiling.c
- rts/RaiseAsync.c
- rts/RetainerSet.c
- rts/RtsFlags.c
- rts/STM.c
- rts/Timer.c
- rts/Trace.c
- rts/Trace.h
- rts/eventlog/EventLog.c
- rts/eventlog/EventLog.h
- rts/include/rts/Bytecodes.h
- rts/include/rts/Flags.h
- rts/linker/LoadArchive.c
- rts/linker/PEi386.c
- rts/sm/NonMoving.c
- rts/sm/NonMoving.h
- rts/sm/NonMovingAllocate.c
- rts/sm/Sanity.c
- testsuite/tests/corelint/T21115b.stderr
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- + 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/dmdanal/should_compile/T23398.hs
- testsuite/tests/dmdanal/should_compile/T23398.stderr
- testsuite/tests/driver/json.stderr
- testsuite/tests/driver/json_warn.stderr
- testsuite/tests/driver/recomp015/all.T
- testsuite/tests/ghci.debugger/scripts/T26042b.script
- testsuite/tests/ghci.debugger/scripts/T26042b.stdout
- testsuite/tests/ghci.debugger/scripts/T26042c.script
- testsuite/tests/ghci.debugger/scripts/T26042c.stdout
- + testsuite/tests/ghci.debugger/scripts/T26042d2.hs
- + testsuite/tests/ghci.debugger/scripts/T26042d2.script
- + testsuite/tests/ghci.debugger/scripts/T26042d2.stdout
- testsuite/tests/ghci.debugger/scripts/T26042e.stdout
- testsuite/tests/ghci.debugger/scripts/T26042f.script
- testsuite/tests/ghci.debugger/scripts/T26042f1.stdout
- testsuite/tests/ghci.debugger/scripts/T26042f2.stdout
- testsuite/tests/ghci.debugger/scripts/T26042g.stdout
- testsuite/tests/ghci.debugger/scripts/all.T
- 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/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/lib/stm/T26028.hs
- + testsuite/tests/lib/stm/T26028.stdout
- + testsuite/tests/lib/stm/all.T
- testsuite/tests/numeric/should_run/T9810.stdout
- + testsuite/tests/perf/should_run/SpecTyFamRun.hs
- + testsuite/tests/perf/should_run/SpecTyFamRun.stdout
- + testsuite/tests/perf/should_run/SpecTyFam_Import.hs
- testsuite/tests/perf/should_run/all.T
- testsuite/tests/printer/Makefile
- + testsuite/tests/printer/TestLevelImports.hs
- + testsuite/tests/printer/TestNamedDefaults.hs
- testsuite/tests/printer/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/roles/should_fail/RolesIArray.stderr
- testsuite/tests/rts/all.T
- testsuite/tests/rts/flags/all.T
- testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-32-mingw32
- testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-64-mingw32
- testsuite/tests/simd/should_run/all.T
- + testsuite/tests/simd/should_run/doublex2_shuffle.hs
- + testsuite/tests/simd/should_run/doublex2_shuffle.stdout
- + testsuite/tests/simd/should_run/doublex2_shuffle_baseline.hs
- + testsuite/tests/simd/should_run/doublex2_shuffle_baseline.stdout
- + testsuite/tests/simd/should_run/floatx4_shuffle.hs
- + testsuite/tests/simd/should_run/floatx4_shuffle.stdout
- + testsuite/tests/simd/should_run/floatx4_shuffle_baseline.hs
- + testsuite/tests/simd/should_run/floatx4_shuffle_baseline.stdout
- + testsuite/tests/simplCore/should_compile/T26051.hs
- + testsuite/tests/simplCore/should_compile/T26051.stderr
- + testsuite/tests/simplCore/should_compile/T26051_Import.hs
- + 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/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/all.T
- testsuite/tests/typecheck/should_compile/T12427a.stderr
- testsuite/tests/typecheck/should_compile/T23171.hs
- testsuite/tests/typecheck/should_compile/TcSpecPragmas.stderr
- testsuite/tests/typecheck/should_fail/T14605.hs
- testsuite/tests/typecheck/should_fail/T14605.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/tcfail174.stderr
- utils/check-exact/ExactPrint.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs
- utils/haddock/haddock-api/haddock-api.cabal
- 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/6586920fd22e5bf2f6e6ba3158ed96…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6586920fd22e5bf2f6e6ba3158ed96…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: README: Add note on ghc.nix
by Marge Bot (@marge-bot) 06 Aug '25
by Marge Bot (@marge-bot) 06 Aug '25
06 Aug '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
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.
- - - - -
6666fb41 by Matthew Pickering at 2025-08-06T16:24:56-04: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
- - - - -
39beb40b by Matthew Pickering at 2025-08-06T16:24:56-04: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
- - - - -
30094971 by Matthew Pickering at 2025-08-06T16:24:56-04: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
- - - - -
61b099b6 by fendor at 2025-08-06T16:24:57-04:00
Bump GHC on darwin CI to 9.10.1
- - - - -
16 changed files:
- .gitlab/darwin/toolchain.nix
- README.md
- compiler/GHC/Cmm.hs
- compiler/GHC/CmmToAsm/PPC/Ppr.hs
- compiler/GHC/CmmToAsm/Ppr.hs
- compiler/GHC/CmmToLlvm/Data.hs
- compiler/GHC/StgToCmm/InfoTableProv.hs
- docs/users_guide/debug-info.rst
- docs/users_guide/exts/linear_types.rst
- docs/users_guide/exts/strict.rst
- rts/IPE.c
- rts/ProfHeap.c
- rts/eventlog/EventLog.c
- rts/include/rts/IPE.h
- testsuite/tests/rts/ipe/ipeMap.c
- testsuite/tests/rts/ipe/ipe_lib.c
Changes:
=====================================
.gitlab/darwin/toolchain.nix
=====================================
@@ -16,18 +16,17 @@ let
ghcBindists = let version = ghc.version; in {
aarch64-darwin = hostPkgs.fetchurl {
url = "https://downloads.haskell.org/ghc/${version}/ghc-${version}-aarch64-apple-d…";
- sha256 = "sha256-c1GTMJf3/yiW/t4QL532EswD5JVlgA4getkfsxj4TaA=";
+ sha256 = "sha256-/6+DtdeossBJIMbjkJwL4h3eJ7rzgNCV+ifoQKOi6AQ=";
};
x86_64-darwin = hostPkgs.fetchurl {
url = "https://downloads.haskell.org/ghc/${version}/ghc-${version}-x86_64-apple-da…";
- sha256 = "sha256-LrYniMG0phsvyW6dhQC+3ompvzcxnwAe6GezEqqzoTQ=";
+ sha256 = "sha256-jPIhiJMOENesUnDUJeIaPatgavc6ZVSTY5NFIAxlC+k=";
};
};
ghc = pkgs.stdenv.mkDerivation rec {
- # Using 9.6.2 because of #24050
- version = "9.6.2";
+ version = "9.10.1";
name = "ghc";
src = ghcBindists.${pkgs.stdenv.hostPlatform.system};
configureFlags = [
=====================================
README.md
=====================================
@@ -81,6 +81,10 @@ These steps give you the default build, which includes everything
optimised and built in various ways (eg. profiling libs are built).
It can take a long time. To customise the build, see the file `HACKING.md`.
+## Nix
+
+If you are looking to use nix to develop on GHC, [check out the wiki for instructions](https://gitlab.haskell.org/ghc/ghc/-/wikis/building/preparati….
+
Filing bugs and feature requests
================================
=====================================
compiler/GHC/Cmm.hs
=====================================
@@ -278,6 +278,7 @@ data SectionType
| InitArray -- .init_array on ELF, .ctor on Windows
| FiniArray -- .fini_array on ELF, .dtor on Windows
| CString
+ | IPE
| OtherSection String
deriving (Show)
@@ -298,6 +299,7 @@ sectionProtection (Section t _) = case t of
CString -> ReadOnlySection
Data -> ReadWriteSection
UninitialisedData -> ReadWriteSection
+ IPE -> ReadWriteSection
(OtherSection _) -> ReadWriteSection
{-
@@ -557,4 +559,5 @@ pprSectionType s = doubleQuotes $ case s of
InitArray -> text "initarray"
FiniArray -> text "finiarray"
CString -> text "cstring"
+ IPE -> text "ipe"
OtherSection s' -> text s'
=====================================
compiler/GHC/CmmToAsm/PPC/Ppr.hs
=====================================
@@ -285,6 +285,9 @@ pprAlignForSection platform seg = line $
Data
| ppc64 -> text ".align 3"
| otherwise -> text ".align 2"
+ IPE
+ | ppc64 -> text ".align 3"
+ | otherwise -> text ".align 2"
ReadOnlyData
| ppc64 -> text ".align 3"
| otherwise -> text ".align 2"
=====================================
compiler/GHC/CmmToAsm/Ppr.hs
=====================================
@@ -236,6 +236,10 @@ pprGNUSectionHeader config t suffix =
| OSMinGW32 <- platformOS platform
-> text ".rdata"
| otherwise -> text ".rodata.str"
+ IPE
+ | OSMinGW32 <- platformOS platform
+ -> text ".rdata"
+ | otherwise -> text ".ipe"
OtherSection _ ->
panic "PprBase.pprGNUSectionHeader: unknown section type"
flags = case t of
@@ -248,6 +252,10 @@ pprGNUSectionHeader config t suffix =
| OSMinGW32 <- platformOS platform
-> empty
| otherwise -> text ",\"aMS\"," <> sectionType platform "progbits" <> text ",1"
+ IPE
+ | OSMinGW32 <- platformOS platform
+ -> empty
+ | otherwise -> text ",\"a\"," <> sectionType platform "progbits"
_ -> empty
{-# SPECIALIZE pprGNUSectionHeader :: NCGConfig -> SectionType -> CLabel -> SDoc #-}
{-# SPECIALIZE pprGNUSectionHeader :: NCGConfig -> SectionType -> CLabel -> HLine #-} -- see Note [SPECIALIZE to HDoc] in GHC.Utils.Outputable
@@ -262,6 +270,7 @@ pprXcoffSectionHeader t = case t of
RelocatableReadOnlyData -> text ".csect .text[PR] # RelocatableReadOnlyData"
CString -> text ".csect .text[PR] # CString"
UninitialisedData -> text ".csect .data[BS]"
+ IPE -> text ".csect .text[PR] #IPE"
_ -> panic "pprXcoffSectionHeader: unknown section type"
{-# SPECIALIZE pprXcoffSectionHeader :: SectionType -> SDoc #-}
{-# SPECIALIZE pprXcoffSectionHeader :: SectionType -> HLine #-} -- see Note [SPECIALIZE to HDoc] in GHC.Utils.Outputable
@@ -276,6 +285,7 @@ pprDarwinSectionHeader t = case t of
InitArray -> text ".section\t__DATA,__mod_init_func,mod_init_funcs"
FiniArray -> panic "pprDarwinSectionHeader: fini not supported"
CString -> text ".section\t__TEXT,__cstring,cstring_literals"
+ IPE -> text ".const"
OtherSection _ -> panic "pprDarwinSectionHeader: unknown section type"
{-# SPECIALIZE pprDarwinSectionHeader :: SectionType -> SDoc #-}
{-# SPECIALIZE pprDarwinSectionHeader :: SectionType -> HLine #-} -- see Note [SPECIALIZE to HDoc] in GHC.Utils.Outputable
=====================================
compiler/GHC/CmmToLlvm/Data.hs
=====================================
@@ -145,7 +145,7 @@ llvmSectionType p t = case t of
CString -> case platformOS p of
OSMinGW32 -> fsLit ".rdata$str"
_ -> fsLit ".rodata.str"
-
+ IPE -> fsLit ".ipe"
InitArray -> panic "llvmSectionType: InitArray"
FiniArray -> panic "llvmSectionType: FiniArray"
OtherSection _ -> panic "llvmSectionType: unknown section type"
=====================================
compiler/GHC/StgToCmm/InfoTableProv.hs
=====================================
@@ -66,6 +66,28 @@ construction, the 'compressed' field of each IPE buffer list node is examined.
If the field indicates that the data has been compressed, the entry data and
strings table are decompressed before continuing with the normal IPE map
construction.
+
+Note [IPE Stripping and magic words]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+For systems which support ELF executables:
+
+The metadata part of IPE info is placed into a separate ELF section (.ipe).
+This can then be stripped afterwards if you don't require the metadata
+
+```
+-- Remove the section
+objcopy --remove-section .ipe <your-exe>
+-- Repack and compress the executable
+upx <your-exe>
+```
+
+The .ipe section starts with a magic 64-bit word "IPE\nIPE\n`, encoded as ascii.
+
+The RTS checks to see if the .ipe section starts with the magic word. If the
+section has been stripped then it won't start with the magic word and the
+metadata won't be accessible for the info tables.
+
-}
emitIpeBufferListNode ::
@@ -124,11 +146,21 @@ emitIpeBufferListNode this_mod ents dus0 = do
ipe_buffer_lbl :: CLabel
ipe_buffer_lbl = mkIPELabel this_mod
+ -- A magic word we can use to see if the IPE information has been stripped
+ -- or not
+ -- See Note [IPE Stripping and magic words]
+ -- "IPE\nIPE\n", null terminated.
+ ipe_header :: CmmStatic
+ ipe_header = CmmStaticLit (CmmInt 0x4950450049504500 W64)
+
ipe_buffer_node :: [CmmStatic]
ipe_buffer_node = map CmmStaticLit
[ -- 'next' field
zeroCLit platform
+ -- 'node_id' field
+ , zeroCLit platform
+
-- 'compressed' field
, int do_compress
@@ -164,13 +196,13 @@ emitIpeBufferListNode this_mod ents dus0 = do
-- Emit the strings table
emitDecl $ CmmData
- (Section Data strings_lbl)
- (CmmStaticsRaw strings_lbl strings)
+ (Section IPE strings_lbl)
+ (CmmStaticsRaw strings_lbl (ipe_header : strings))
-- Emit the list of IPE buffer entries
emitDecl $ CmmData
- (Section Data entries_lbl)
- (CmmStaticsRaw entries_lbl entries)
+ (Section IPE entries_lbl)
+ (CmmStaticsRaw entries_lbl (ipe_header : entries))
-- Emit the IPE buffer list node
emitDecl $ CmmData
=====================================
docs/users_guide/debug-info.rst
=====================================
@@ -391,6 +391,17 @@ to a source location. This lookup table is generated by using the ``-finfo-table
In a test compiling GHC itself, the size of the :ghc-flag:`-finfo-table-map`
enabled build results was reduced by over 20% when compression was enabled.
+ The metadata for ``-finfo-table-map`` is stored in the ``.ipe`` section on
+ ELF platforms. The ``.ipe`` section can be removed from the binary after compilation::
+
+ objcopy --remove-section .ipe <binary>
+ upx <binary>
+
+ You can first compile your application with ``-finfo-table-map``, extract
+ the contents of the map (by using the eventlog), strip the ``.ipe`` section
+ and then use the extracted data to interpret a ``-hi`` profile from the stripped
+ binary.
+
:since: 9.10
:implies: :ghc-flag:`-finfo-table-map-with-stack`
:implies: :ghc-flag:`-finfo-table-map-with-fallback`
=====================================
docs/users_guide/exts/linear_types.rst
=====================================
@@ -213,6 +213,8 @@ With ``-XStrict``::
-- inferred unrestricted
let ~(x, y) = u in …
+(See :ref:`strict-bindings`).
+
Data types
----------
By default, all fields in algebraic data types are linear (even if
=====================================
docs/users_guide/exts/strict.rst
=====================================
@@ -103,6 +103,9 @@ Note the following points:
See `GHC Proposal #229 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0229-w…>`__
for the precise rules.
+
+.. _strict-bindings:
+
Strict bindings
~~~~~~~~~~~~~~~
=====================================
rts/IPE.c
=====================================
@@ -62,6 +62,22 @@ entry's containing IpeBufferListNode and its index in that node.
When the user looks up an IPE entry, we convert it to the user-facing
InfoProvEnt representation.
+Note [Stable identifiers for IPE entries]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+Each IPE entry is given a stable identifier which remains the same across
+different runs of the executable (unlike the address of the info table).
+
+The identifier is a 64-bit word which consists of two parts.
+
+* The high 32-bits are a per-node identifier.
+* The low 32-bits are the index of the entry in the node.
+
+When a node is queued in the pending list by `registerInfoProvList` it is
+given a unique identifier from an incrementing global variable.
+
+The unique key can be computed by using the `IPE_ENTRY_KEY` macro.
+
*/
typedef struct {
@@ -69,6 +85,13 @@ typedef struct {
uint32_t idx;
} IpeMapEntry;
+// See Note [Stable identifiers for IPE entries]
+#define IPE_ENTRY_KEY(entry) \
+ MAKE_IPE_KEY((entry).node->node_id, (entry).idx)
+
+#define MAKE_IPE_KEY(module_id, idx) \
+ ((((uint64_t)(module_id)) << 32) | ((uint64_t)(idx)))
+
#if defined(THREADED_RTS)
static Mutex ipeMapLock;
#endif
@@ -78,9 +101,22 @@ static HashTable *ipeMap = NULL;
// Accessed atomically
static IpeBufferListNode *ipeBufferList = NULL;
+// A global counter which is used to give an IPE entry a unique value across runs.
+static StgWord next_module_id = 1; // Start at 1 to reserve 0 as "invalid"
+
static void decompressIPEBufferListNodeIfCompressed(IpeBufferListNode*);
static void updateIpeMap(void);
+// Check whether the IpeBufferListNode has the relevant magic words.
+// See Note [IPE Stripping and magic words]
+static inline bool ipe_node_valid(const IpeBufferListNode *node) {
+ return node &&
+ node->entries_block &&
+ node->string_table_block &&
+ node->entries_block->magic == IPE_MAGIC_WORD &&
+ node->string_table_block->magic == IPE_MAGIC_WORD;
+}
+
#if defined(THREADED_RTS)
void initIpe(void) { initMutex(&ipeMapLock); }
@@ -99,11 +135,12 @@ static InfoProvEnt ipeBufferEntryToIpe(const IpeBufferListNode *node, uint32_t i
{
CHECK(idx < node->count);
CHECK(!node->compressed);
- const char *strings = node->string_table;
- const IpeBufferEntry *ent = &node->entries[idx];
+ const char *strings = node->string_table_block->string_table;
+ const IpeBufferEntry *ent = &node->entries_block->entries[idx];
return (InfoProvEnt) {
.info = node->tables[idx],
.prov = {
+ .info_prov_id = MAKE_IPE_KEY(node->node_id, idx),
.table_name = &strings[ent->table_name],
.closure_desc = ent->closure_desc,
.ty_desc = &strings[ent->ty_desc],
@@ -121,19 +158,23 @@ static InfoProvEnt ipeBufferEntryToIpe(const IpeBufferListNode *node, uint32_t i
static void traceIPEFromHashTable(void *data STG_UNUSED, StgWord key STG_UNUSED,
const void *value) {
const IpeMapEntry *map_ent = (const IpeMapEntry *)value;
- const InfoProvEnt ipe = ipeBufferEntryToIpe(map_ent->node, map_ent->idx);
- traceIPE(&ipe);
+ if (ipe_node_valid(map_ent->node)){
+ const InfoProvEnt ipe = ipeBufferEntryToIpe(map_ent->node, map_ent->idx);
+ traceIPE(&ipe);
+ }
}
void dumpIPEToEventLog(void) {
// Dump pending entries
IpeBufferListNode *node = RELAXED_LOAD(&ipeBufferList);
while (node != NULL) {
- decompressIPEBufferListNodeIfCompressed(node);
+ if (ipe_node_valid(node)){
+ decompressIPEBufferListNodeIfCompressed(node);
- for (uint32_t i = 0; i < node->count; i++) {
- const InfoProvEnt ent = ipeBufferEntryToIpe(node, i);
- traceIPE(&ent);
+ for (uint32_t i = 0; i < node->count; i++) {
+ const InfoProvEnt ent = ipeBufferEntryToIpe(node, i);
+ traceIPE(&ent);
+ }
}
node = node->next;
}
@@ -165,11 +206,30 @@ ipeMapLock; we instead use atomic CAS operations to add to the list.
A performance test for IPE registration and lookup can be found here:
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/5724#note_370806
+
+Note that IPEs are still regiestered even if the .ipe section is stripped. That's
+because you may still want to query what the unique identifier for an info table is
+so it can be reconciled with previously extracted metadata information. For example,
+when `-hi` profiling or using `whereFrom`.
+
*/
void registerInfoProvList(IpeBufferListNode *node) {
+
+ // Grab a fresh module_id
+ uint32_t module_id;
+ StgWord temp_module_id;
+ while (true) {
+ temp_module_id = next_module_id;
+ if (cas(&next_module_id, temp_module_id, temp_module_id+1) == temp_module_id) {
+ module_id = (uint32_t) temp_module_id;
+ break;
+ }
+
+ }
while (true) {
IpeBufferListNode *old = RELAXED_LOAD(&ipeBufferList);
node->next = old;
+ node->node_id = module_id;
if (cas_ptr((volatile void **) &ipeBufferList, old, node) == (void *) old) {
return;
}
@@ -183,7 +243,7 @@ void formatClosureDescIpe(const InfoProvEnt *ipe_buf, char *str_buf) {
bool lookupIPE(const StgInfoTable *info, InfoProvEnt *out) {
updateIpeMap();
IpeMapEntry *map_ent = (IpeMapEntry *) lookupHashTable(ipeMap, (StgWord)info);
- if (map_ent) {
+ if (map_ent && ipe_node_valid(map_ent->node)) {
*out = ipeBufferEntryToIpe(map_ent->node, map_ent->idx);
return true;
} else {
@@ -191,6 +251,18 @@ bool lookupIPE(const StgInfoTable *info, InfoProvEnt *out) {
}
}
+// Returns 0 when the info table is not present in the info table map.
+// See Note [Stable identifiers for IPE entries]
+uint64_t lookupIPEId(const StgInfoTable *info) {
+ updateIpeMap();
+ IpeMapEntry *map_ent = (IpeMapEntry *) lookupHashTable(ipeMap, (StgWord)(info));
+ if (map_ent){
+ return IPE_ENTRY_KEY(*map_ent);
+ } else {
+ return 0;
+ }
+}
+
void updateIpeMap(void) {
// Check if there's any work at all. If not so, we can circumvent locking,
// which decreases performance.
=====================================
rts/ProfHeap.c
=====================================
@@ -23,6 +23,7 @@
#include "Printer.h"
#include "Trace.h"
#include "sm/GCThread.h"
+#include "IPE.h"
#include <fs_rts.h>
#include <string.h>
@@ -230,9 +231,10 @@ closureIdentity( const StgClosure *p )
return closure_type_names[info->type];
}
}
- case HEAP_BY_INFO_TABLE: {
- return get_itbl(p);
- }
+ case HEAP_BY_INFO_TABLE:
+ {
+ return (void *) (p->header.info);
+ }
default:
barf("closureIdentity");
@@ -853,6 +855,20 @@ aggregateCensusInfo( void )
}
#endif
+static void
+recordIPEHeapSample(FILE *hp_file, uint64_t table_id, size_t count)
+{
+ // Print to heap profile file
+ fprintf(hp_file, "0x%" PRIx64, table_id);
+
+ // Create label string for tracing
+ char str[100];
+ sprintf(str, "0x%" PRIx64, table_id);
+
+ // Emit the profiling sample (convert count to bytes)
+ traceHeapProfSampleString(str, count * sizeof(W_));
+}
+
/* -----------------------------------------------------------------------------
* Print out the results of a heap census.
* -------------------------------------------------------------------------- */
@@ -915,6 +931,11 @@ dumpCensus( Census *census )
}
#endif
+ // Census entries which we need to group together.
+ // Used by IPE profiling to group together bands which don't have IPE information.
+ // Printing at the end in the 0 band
+ uint64_t uncategorised_count = 0;
+
for (ctr = census->ctrs; ctr != NULL; ctr = ctr->next) {
#if defined(PROFILING)
@@ -945,11 +966,15 @@ dumpCensus( Census *census )
count * sizeof(W_));
break;
case HEAP_BY_INFO_TABLE:
- fprintf(hp_file, "%p", ctr->identity);
- char str[100];
- sprintf(str, "%p", ctr->identity);
- traceHeapProfSampleString(str, count * sizeof(W_));
+ {
+ uint64_t table_id = lookupIPEId(ctr->identity);
+ if (! table_id) {
+ uncategorised_count += count;
+ continue;
+ }
+ recordIPEHeapSample(hp_file, table_id, count);
break;
+ }
#if defined(PROFILING)
case HEAP_BY_CCS:
fprint_ccs(hp_file, (CostCentreStack *)ctr->identity,
@@ -1002,6 +1027,16 @@ dumpCensus( Census *census )
fprintf(hp_file, "\t%" FMT_Word "\n", (W_)count * sizeof(W_));
}
+ // Print the unallocated data into the 0 band for info table profiling.
+ switch (RtsFlags.ProfFlags.doHeapProfile) {
+ case HEAP_BY_INFO_TABLE:
+ recordIPEHeapSample(hp_file, 0, uncategorised_count);
+ break;
+ default:
+ ASSERT(uncategorised_count == 0);
+ break;
+ }
+
traceHeapProfSampleEnd(era);
printSample(false, census->time);
=====================================
rts/eventlog/EventLog.c
=====================================
@@ -1480,7 +1480,7 @@ void postIPE(const InfoProvEnt *ipe)
CHECK(!ensureRoomForVariableEvent(&eventBuf, len));
postEventHeader(&eventBuf, EVENT_IPE);
postPayloadSize(&eventBuf, len);
- postWord64(&eventBuf, (StgWord) INFO_PTR_TO_STRUCT(ipe->info));
+ postWord64(&eventBuf, (StgWord) (ipe->prov.info_prov_id));
postStringLen(&eventBuf, ipe->prov.table_name, table_name_len);
postStringLen(&eventBuf, closure_desc_buf, closure_desc_len);
postStringLen(&eventBuf, ipe->prov.ty_desc, ty_desc_len);
=====================================
rts/include/rts/IPE.h
=====================================
@@ -14,6 +14,7 @@
#pragma once
typedef struct InfoProv_ {
+ uint64_t info_prov_id;
const char *table_name;
uint32_t closure_desc; // closure type
const char *ty_desc;
@@ -63,9 +64,37 @@ typedef struct {
GHC_STATIC_ASSERT(sizeof(IpeBufferEntry) % (WORD_SIZE_IN_BITS / 8) == 0, "sizeof(IpeBufferEntry) must be a multiple of the word size");
+// The magic word is IPE\nIPE\n, which occupies the full 64 bit width of a word.
+// See Note [IPE Stripping and magic words]
+#define IPE_MAGIC_WORD 0x4950450049504500UL
+
+// Heap profiling currently requires a 32 bit pointer.. so for now just truncate
+// the key to fit. It should still be big enough.
+#if SIZEOF_VOID_P == 4
+// On 32-bit systems: keep lower 16 bits of module_id and idx
+#define IPE_PROF_KEY(key64) \
+ (uint32_t)((((key64) >> 16) & 0xFFFF0000) | ((key64) & 0x0000FFFF))
+#else
+// On 64-bit systems: use full key
+#define IPE_PROF_KEY(key64) (key64)
+#endif
+
+typedef struct {
+ StgWord64 magic; // Must be IPE_MAGIC_WORD
+ IpeBufferEntry entries[]; // Flexible array member
+} IpeBufferEntryBlock;
+
+typedef struct {
+ StgWord64 magic; // Must be IPE_MAGIC_WORD
+ char string_table[]; // Flexible array member for string table
+} IpeStringTableBlock;
+
typedef struct IpeBufferListNode_ {
struct IpeBufferListNode_ *next;
+ // This field is filled in when the node is registered.
+ uint32_t node_id;
+
// Everything below is read-only and generated by the codegen
// This flag should be treated as a boolean
@@ -76,10 +105,10 @@ typedef struct IpeBufferListNode_ {
// When TNTC is enabled, these will point to the entry code
// not the info table itself.
const StgInfoTable **tables;
- IpeBufferEntry *entries;
+ IpeBufferEntryBlock *entries_block;
StgWord entries_size; // decompressed size
- const char *string_table;
+ const IpeStringTableBlock *string_table_block;
StgWord string_table_size; // decompressed size
// Shared by all entries
@@ -98,6 +127,8 @@ void formatClosureDescIpe(const InfoProvEnt *ipe_buf, char *str_buf);
// Returns true on success, initializes `out`.
bool lookupIPE(const StgInfoTable *info, InfoProvEnt *out);
+uint64_t lookupIPEId(const StgInfoTable *info);
+
#if defined(DEBUG)
void printIPE(const StgInfoTable *info);
#endif
=====================================
testsuite/tests/rts/ipe/ipeMap.c
=====================================
@@ -48,7 +48,8 @@ HaskellObj shouldFindOneIfItHasBeenRegistered(Capability *cap) {
// Allocate buffers for IPE buffer list node
IpeBufferListNode *node = malloc(sizeof(IpeBufferListNode));
node->tables = malloc(sizeof(StgInfoTable *));
- node->entries = malloc(sizeof(IpeBufferEntry));
+ node->entries_block = malloc(sizeof(StgWord64) + sizeof(IpeBufferEntry));
+ node->entries_block->magic = IPE_MAGIC_WORD;
StringTable st;
init_string_table(&st);
@@ -61,9 +62,13 @@ HaskellObj shouldFindOneIfItHasBeenRegistered(Capability *cap) {
node->compressed = 0;
node->count = 1;
node->tables[0] = get_itbl(fortyTwo);
- node->entries[0] = makeAnyProvEntry(cap, &st, 42);
+ node->entries_block->entries[0] = makeAnyProvEntry(cap, &st, 42);
node->entries_size = sizeof(IpeBufferEntry);
- node->string_table = st.buffer;
+
+ IpeStringTableBlock *string_table_block = malloc(sizeof(StgWord64) + st.size);
+ string_table_block->magic = IPE_MAGIC_WORD;
+ memcpy(string_table_block->string_table, st.buffer, st.size);
+ node->string_table_block = string_table_block;
node->string_table_size = st.size;
registerInfoProvList(node);
@@ -90,7 +95,8 @@ void shouldFindTwoIfTwoHaveBeenRegistered(Capability *cap,
// Allocate buffers for IPE buffer list node
IpeBufferListNode *node = malloc(sizeof(IpeBufferListNode));
node->tables = malloc(sizeof(StgInfoTable *));
- node->entries = malloc(sizeof(IpeBufferEntry));
+ node->entries_block = malloc(sizeof(StgWord64) + sizeof(IpeBufferEntry));
+ node->entries_block->magic = IPE_MAGIC_WORD;
StringTable st;
init_string_table(&st);
@@ -103,9 +109,12 @@ void shouldFindTwoIfTwoHaveBeenRegistered(Capability *cap,
node->compressed = 0;
node->count = 1;
node->tables[0] = get_itbl(twentyThree);
- node->entries[0] = makeAnyProvEntry(cap, &st, 23);
+ node->entries_block->entries[0] = makeAnyProvEntry(cap, &st, 23);
node->entries_size = sizeof(IpeBufferEntry);
- node->string_table = st.buffer;
+ IpeStringTableBlock *string_table_block = malloc(sizeof(StgWord64) + st.size);
+ string_table_block->magic = IPE_MAGIC_WORD;
+ memcpy(string_table_block->string_table, st.buffer, st.size);
+ node->string_table_block = string_table_block;
node->string_table_size = st.size;
registerInfoProvList(node);
@@ -121,7 +130,8 @@ void shouldFindTwoFromTheSameList(Capability *cap) {
// Allocate buffers for IPE buffer list node
IpeBufferListNode *node = malloc(sizeof(IpeBufferListNode));
node->tables = malloc(sizeof(StgInfoTable *) * 2);
- node->entries = malloc(sizeof(IpeBufferEntry) * 2);
+ node->entries_block = malloc(sizeof(StgWord64) + sizeof(IpeBufferEntry) * 2);
+ node->entries_block->magic = IPE_MAGIC_WORD;
StringTable st;
init_string_table(&st);
@@ -133,10 +143,13 @@ void shouldFindTwoFromTheSameList(Capability *cap) {
node->count = 2;
node->tables[0] = get_itbl(one);
node->tables[1] = get_itbl(two);
- node->entries[0] = makeAnyProvEntry(cap, &st, 1);
- node->entries[1] = makeAnyProvEntry(cap, &st, 2);
+ node->entries_block->entries[0] = makeAnyProvEntry(cap, &st, 1);
+ node->entries_block->entries[1] = makeAnyProvEntry(cap, &st, 2);
node->entries_size = sizeof(IpeBufferEntry) * 2;
- node->string_table = st.buffer;
+ IpeStringTableBlock *string_table_block = malloc(sizeof(StgWord64) + st.size);
+ string_table_block->magic = IPE_MAGIC_WORD;
+ memcpy(string_table_block->string_table, st.buffer, st.size);
+ node->string_table_block = string_table_block;
node->string_table_size = st.size;
registerInfoProvList(node);
@@ -152,7 +165,11 @@ void shouldDealWithAnEmptyList(Capability *cap, HaskellObj fortyTwo) {
IpeBufferListNode *node = malloc(sizeof(IpeBufferListNode));
node->count = 0;
node->next = NULL;
- node->string_table = "";
+ IpeStringTableBlock *string_table_block = malloc(sizeof(StgWord64));
+ string_table_block->magic = IPE_MAGIC_WORD;
+
+ node->entries_block = malloc(sizeof(StgWord64));
+ node->entries_block->magic = IPE_MAGIC_WORD;
registerInfoProvList(node);
=====================================
testsuite/tests/rts/ipe/ipe_lib.c
=====================================
@@ -64,7 +64,8 @@ IpeBufferListNode *makeAnyProvEntries(Capability *cap, int start, int end) {
// Allocate buffers for IpeBufferListNode
IpeBufferListNode *node = malloc(sizeof(IpeBufferListNode));
node->tables = malloc(sizeof(StgInfoTable *) * n);
- node->entries = malloc(sizeof(IpeBufferEntry) * n);
+ node->entries_block = malloc(sizeof(StgWord64) + sizeof(IpeBufferEntry) * n);
+ node->entries_block->magic = IPE_MAGIC_WORD;
StringTable st;
init_string_table(&st);
@@ -83,14 +84,19 @@ IpeBufferListNode *makeAnyProvEntries(Capability *cap, int start, int end) {
for (int i=start; i < end; i++) {
HaskellObj closure = rts_mkInt(cap, 42);
node->tables[i] = get_itbl(closure);
- node->entries[i] = makeAnyProvEntry(cap, &st, i);
+ node->entries_block->entries[i] = makeAnyProvEntry(cap, &st, i);
}
// Set the rest of the fields
node->next = NULL;
node->compressed = 0;
node->count = n;
- node->string_table = st.buffer;
+
+ IpeStringTableBlock *string_table_block =
+ malloc(sizeof(StgWord64) + st.size);
+ string_table_block->magic = IPE_MAGIC_WORD;
+ memcpy(string_table_block->string_table, st.buffer, st.size);
+ node->string_table_block = string_table_block;
return node;
}
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/70ea20a7d17b441ee8b025d3ff1b8a…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/70ea20a7d17b441ee8b025d3ff1b8a…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/romes/26227] 18 commits: configure: Allow override of CrossCompiling
by Cheng Shao (@TerrorJack) 06 Aug '25
by Cheng Shao (@TerrorJack) 06 Aug '25
06 Aug '25
Cheng Shao pushed to branch wip/romes/26227 at Glasgow Haskell Compiler / GHC
Commits:
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.
- - - - -
6efcfab0 by Rodrigo Mesquita at 2025-08-06T20:04:03+00:00
ghc-toolchain: Use ByteOrder rather than new Endianness
Don't introduce a duplicate datatype when the previous one is equivalent
and already used elsewhere. This avoids unnecessary translation between
the two.
- - - - -
a5bed777 by Rodrigo Mesquita at 2025-08-06T20:04:04+00:00
Read Toolchain.Target files rather than 'settings'
This commit makes GHC read `lib/targets/default.target`, a file with a
serialized value of `ghc-toolchain`'s `GHC.Toolchain.Target`.
Moreover, it removes all the now-redundant entries from `lib/settings`
that are configured as part of a `Target` but were being written into
`settings`.
This makes it easier to support multiple targets from the same compiler
(aka runtime retargetability). `ghc-toolchain` can be re-run many times
standalone to produce a `Target` description for different targets, and,
in the future, GHC will be able to pick at runtime amongst different
`Target` files.
This commit only makes it read the default `Target` configured in-tree
or configured when installing the bindist.
The remaining bits of `settings` need to be moved to `Target` in follow
up commits, but ultimately they all should be moved since they are
per-target relevant.
Fixes #24212
On Windows, the constant overhead of parsing a slightly more complex
data structure causes some small-allocation tests to wiggle around 1 to
2 extra MB (1-2% in these cases).
-------------------------
Metric Increase:
MultiLayerModulesTH_OneShot
T10421
T10547
T12234
T12425
T13035
T18140
T18923
T9198
TcPlugin_RewritePerf
-------------------------
- - - - -
2098014f by Rodrigo Mesquita at 2025-08-06T20:04:04+00:00
ghc-toolchain: Move TgtHasLibm to per-Target file
TargetHasLibm is now part of the per-target configuration
Towards #26227
- - - - -
f3ee631d by Rodrigo Mesquita at 2025-08-06T20:04:04+00:00
ghc-toolchain: Move UseLibdw to per-Target file
To support DWARF unwinding, the RTS must be built with the -f+libdw flag
and with the -DUSE_LIBDW macro definition. These flags are passed on
build by Hadrian when --enable-dwarf-unwinding is specified at configure
time.
Whether the RTS was built with support for DWARF is a per-target
property, and as such, it was moved to the per-target
GHC.Toolchain.Target.Target file.
Additionally, we keep in the target file the include and library paths
for finding libdw, since libdw should be checked at configure time (be
it by configure, or ghc-toolchain, that libdw is properly available).
Preserving the user-given include paths for libdw facilitates in the
future building the RTS on demand for a given target (if we didn't keep
that user input, we couldn't)
Towards #26227
- - - - -
1742a44f by Rodrigo Mesquita at 2025-08-06T20:04:04+00:00
ghc-toolchain: Make "Support SMP" a query on a Toolchain.Target
"Support SMP" is merely a function of target, so we can represent it as
such in `ghc-toolchain`.
Hadrian queries the Target using this predicate to determine how to
build GHC, and GHC queries the Target similarly to report under --info
whether it "Support SMP"
Towards #26227
- - - - -
82c6fcd0 by Rodrigo Mesquita at 2025-08-06T20:04:04+00:00
ghc-toolchain: Make "tgt rts linker only supports shared libs" function on Target
Just like with "Support SMP", "target RTS linker only supports shared
libraries" is a predicate on a `Target` so we can just compute it when
necessary from the given `Target`.
Towards #26227
- - - - -
62 changed files:
- CODEOWNERS
- README.md
- compiler/GHC/CmmToAsm/LA64/CodeGen.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Settings.hs
- compiler/GHC/Settings/IO.hs
- compiler/GHC/SysTools/BaseDir.hs
- compiler/GHC/Types/Name/Cache.hs
- compiler/ghc.cabal.in
- configure.ac
- distrib/configure.ac.in
- docs/users_guide/exts/linear_types.rst
- docs/users_guide/exts/strict.rst
- hadrian/bindist/Makefile
- hadrian/bindist/config.mk.in
- hadrian/cfg/default.host.target.in
- hadrian/cfg/default.target.in
- hadrian/cfg/system.config.in
- hadrian/src/Base.hs
- hadrian/src/Oracles/Flag.hs
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Settings/Packages.hs
- hadrian/stack.yaml
- hadrian/stack.yaml.lock
- libraries/base/changelog.md
- libraries/base/src/Control/Exception/Backtrace.hs
- libraries/base/src/Data/List/NonEmpty.hs
- libraries/base/src/System/Console/GetOpt.hs
- libraries/ghc-boot/GHC/Settings/Utils.hs
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghc-internal/src/GHC/Internal/Data/OldList.hs
- libraries/ghc-internal/src/GHC/Internal/ResponseFile.hs
- libraries/text
- m4/fp_find_libdw.m4
- − m4/fp_settings.m4
- m4/fp_setup_windows_toolchain.m4
- m4/ghc_toolchain.m4
- m4/prep_target_file.m4
- + m4/subst_tooldir.m4
- mk/hsc2hs.in
- rts/linker/LoadArchive.c
- testsuite/tests/ghc-api/T20757.hs
- testsuite/tests/ghc-api/settings-escape/T24265.hs
- testsuite/tests/ghc-api/settings-escape/T24265.stderr
- + testsuite/tests/ghc-api/settings-escape/ghc-install-folder/lib with spaces/targets/.gitkeep
- 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
- utils/ghc-pkg/Main.hs
- utils/ghc-pkg/ghc-pkg.cabal.in
- utils/ghc-toolchain/exe/Main.hs
- utils/ghc-toolchain/ghc-toolchain.cabal
- + utils/ghc-toolchain/src/GHC/Toolchain/Library.hs
- utils/ghc-toolchain/src/GHC/Toolchain/PlatformDetails.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Target.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cpp.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cxx.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ac859b36f0b67f56ca4a09f2500c18…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ac859b36f0b67f56ca4a09f2500c18…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] Link to the "Strict Bindings" docs from the linear types docs
by Marge Bot (@marge-bot) 06 Aug '25
by Marge Bot (@marge-bot) 06 Aug '25
06 Aug '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
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.
- - - - -
2 changed files:
- docs/users_guide/exts/linear_types.rst
- docs/users_guide/exts/strict.rst
Changes:
=====================================
docs/users_guide/exts/linear_types.rst
=====================================
@@ -213,6 +213,8 @@ With ``-XStrict``::
-- inferred unrestricted
let ~(x, y) = u in …
+(See :ref:`strict-bindings`).
+
Data types
----------
By default, all fields in algebraic data types are linear (even if
=====================================
docs/users_guide/exts/strict.rst
=====================================
@@ -103,6 +103,9 @@ Note the following points:
See `GHC Proposal #229 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0229-w…>`__
for the precise rules.
+
+.. _strict-bindings:
+
Strict bindings
~~~~~~~~~~~~~~~
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/93a2f450d48622c492e4fded47ddaf1…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/93a2f450d48622c492e4fded47ddaf1…
You're receiving this email because of your account on gitlab.haskell.org.
1
0