Matthew Pickering pushed to branch wip/fix-ghc-experimental at Glasgow Haskell Compiler / GHC
Commits:
-
2e618759
by Matthew Pickering at 2026-01-21T18:21:50+00:00
4 changed files:
- libraries/ghc-experimental/ghc-experimental.cabal.in
- libraries/ghc-experimental/src/GHC/Exception/Backtrace/Experimental.hs
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
Changes:
| ... | ... | @@ -44,6 +44,7 @@ library |
| 44 | 44 | GHC.Stats.Experimental
|
| 45 | 45 | Prelude.Experimental
|
| 46 | 46 | System.Mem.Experimental
|
| 47 | + GHC.Exception.Backtrace.Experimental
|
|
| 47 | 48 | if arch(wasm32)
|
| 48 | 49 | exposed-modules: GHC.Wasm.Prim
|
| 49 | 50 | other-extensions:
|
| ... | ... | @@ -15,7 +15,7 @@ module GHC.Exception.Backtrace.Experimental |
| 15 | 15 | , getBacktraceMechanismState
|
| 16 | 16 | , setBacktraceMechanismState
|
| 17 | 17 | -- * Collecting backtraces
|
| 18 | - , Backtraces(..),
|
|
| 18 | + , Backtraces(..)
|
|
| 19 | 19 | , displayBacktraces
|
| 20 | 20 | , collectBacktraces
|
| 21 | 21 | -- * Collecting exception annotations on throwing 'Exception's
|
| ... | ... | @@ -4454,6 +4454,22 @@ module Data.Tuple.Experimental where |
| 4454 | 4454 | data Unit# = ...
|
| 4455 | 4455 | getSolo :: forall a. Solo a -> a
|
| 4456 | 4456 | |
| 4457 | +module GHC.Exception.Backtrace.Experimental where
|
|
| 4458 | + -- Safety: None
|
|
| 4459 | + type BacktraceMechanism :: *
|
|
| 4460 | + data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
|
|
| 4461 | + type Backtraces :: *
|
|
| 4462 | + 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.StackTrace, btrIpe :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.CloneStack.StackSnapshot}
|
|
| 4463 | + type CollectExceptionAnnotationMechanism :: *
|
|
| 4464 | + data CollectExceptionAnnotationMechanism = ...
|
|
| 4465 | + collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
|
|
| 4466 | + collectExceptionAnnotation :: GHC.Internal.Stack.Types.HasCallStack => GHC.Internal.Types.IO GHC.Internal.Exception.Context.SomeExceptionAnnotation
|
|
| 4467 | + displayBacktraces :: Backtraces -> GHC.Internal.Base.String
|
|
| 4468 | + getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
|
|
| 4469 | + getCollectExceptionAnnotationMechanism :: GHC.Internal.Types.IO CollectExceptionAnnotationMechanism
|
|
| 4470 | + setBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.Bool -> GHC.Internal.Types.IO ()
|
|
| 4471 | + setCollectExceptionAnnotation :: forall a. GHC.Internal.Exception.Context.ExceptionAnnotation a => (GHC.Internal.Stack.Types.HasCallStack => GHC.Internal.Types.IO a) -> GHC.Internal.Types.IO ()
|
|
| 4472 | + |
|
| 4457 | 4473 | module GHC.PrimOps where
|
| 4458 | 4474 | -- Safety: Unsafe
|
| 4459 | 4475 | (*#) :: Int# -> Int# -> Int#
|
| ... | ... | @@ -11182,6 +11198,7 @@ instance GHC.Internal.Enum.Enum GHC.Internal.RTS.Flags.DoTrace -- Defined in ‘ |
| 11182 | 11198 | instance GHC.Internal.Enum.Enum GHC.Internal.RTS.Flags.GiveGCStats -- Defined in ‘GHC.Internal.RTS.Flags’
|
| 11183 | 11199 | instance GHC.Internal.Enum.Enum GHC.Internal.RTS.Flags.IoManagerFlag -- Defined in ‘GHC.Internal.RTS.Flags’
|
| 11184 | 11200 | instance GHC.Internal.Enum.Enum GHC.Internal.IO.SubSystem.IoSubSystem -- Defined in ‘GHC.Internal.IO.SubSystem’
|
| 11201 | +instance GHC.Internal.Exception.Context.ExceptionAnnotation GHC.Internal.Exception.Backtrace.Backtraces -- Defined in ‘GHC.Internal.Exception.Backtrace’
|
|
| 11185 | 11202 | instance forall a. GHC.Internal.Float.Floating a => GHC.Internal.Float.Floating (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
|
| 11186 | 11203 | instance forall a. GHC.Internal.Float.RealFloat a => GHC.Internal.Float.RealFloat (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
|
| 11187 | 11204 | instance forall a. GHC.Internal.Foreign.Storable.Storable a => GHC.Internal.Foreign.Storable.Storable (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
|
| ... | ... | @@ -4454,6 +4454,22 @@ module Data.Tuple.Experimental where |
| 4454 | 4454 | data Unit# = ...
|
| 4455 | 4455 | getSolo :: forall a. Solo a -> a
|
| 4456 | 4456 | |
| 4457 | +module GHC.Exception.Backtrace.Experimental where
|
|
| 4458 | + -- Safety: None
|
|
| 4459 | + type BacktraceMechanism :: *
|
|
| 4460 | + data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
|
|
| 4461 | + type Backtraces :: *
|
|
| 4462 | + 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.StackTrace, btrIpe :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.CloneStack.StackSnapshot}
|
|
| 4463 | + type CollectExceptionAnnotationMechanism :: *
|
|
| 4464 | + data CollectExceptionAnnotationMechanism = ...
|
|
| 4465 | + collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
|
|
| 4466 | + collectExceptionAnnotation :: GHC.Internal.Stack.Types.HasCallStack => GHC.Internal.Types.IO GHC.Internal.Exception.Context.SomeExceptionAnnotation
|
|
| 4467 | + displayBacktraces :: Backtraces -> GHC.Internal.Base.String
|
|
| 4468 | + getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
|
|
| 4469 | + getCollectExceptionAnnotationMechanism :: GHC.Internal.Types.IO CollectExceptionAnnotationMechanism
|
|
| 4470 | + setBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.Bool -> GHC.Internal.Types.IO ()
|
|
| 4471 | + setCollectExceptionAnnotation :: forall a. GHC.Internal.Exception.Context.ExceptionAnnotation a => (GHC.Internal.Stack.Types.HasCallStack => GHC.Internal.Types.IO a) -> GHC.Internal.Types.IO ()
|
|
| 4472 | + |
|
| 4457 | 4473 | module GHC.PrimOps where
|
| 4458 | 4474 | -- Safety: Unsafe
|
| 4459 | 4475 | (*#) :: Int# -> Int# -> Int#
|
| ... | ... | @@ -11185,6 +11201,7 @@ instance GHC.Internal.Enum.Enum GHC.Internal.RTS.Flags.DoTrace -- Defined in ‘ |
| 11185 | 11201 | instance GHC.Internal.Enum.Enum GHC.Internal.RTS.Flags.GiveGCStats -- Defined in ‘GHC.Internal.RTS.Flags’
|
| 11186 | 11202 | instance GHC.Internal.Enum.Enum GHC.Internal.RTS.Flags.IoManagerFlag -- Defined in ‘GHC.Internal.RTS.Flags’
|
| 11187 | 11203 | instance GHC.Internal.Enum.Enum GHC.Internal.IO.SubSystem.IoSubSystem -- Defined in ‘GHC.Internal.IO.SubSystem’
|
| 11204 | +instance GHC.Internal.Exception.Context.ExceptionAnnotation GHC.Internal.Exception.Backtrace.Backtraces -- Defined in ‘GHC.Internal.Exception.Backtrace’
|
|
| 11188 | 11205 | instance forall a. GHC.Internal.Float.Floating a => GHC.Internal.Float.Floating (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
|
| 11189 | 11206 | instance forall a. GHC.Internal.Float.RealFloat a => GHC.Internal.Float.RealFloat (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
|
| 11190 | 11207 | instance forall a. GHC.Internal.Foreign.Storable.Storable a => GHC.Internal.Foreign.Storable.Storable (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
|