Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC

Commits:

7 changed files:

Changes:

  • libraries/base/changelog.md
    ... ... @@ -22,6 +22,7 @@
    22 22
           * `GHC.TypeNats.Internal`
    
    23 23
           * `GHC.ExecutionStack.Internal`.
    
    24 24
       * Deprecate `GHC.JS.Prim.Internal.Build`, as per [CLC #329](https://github.com/haskell/core-libraries-committee/issues/329)
    
    25
    +  * 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)
    
    25 26
     
    
    26 27
       * 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)).
    
    27 28
     
    

  • libraries/base/src/Control/Exception/Backtrace.hs
    ... ... @@ -51,7 +51,7 @@ module Control.Exception.Backtrace
    51 51
         , getBacktraceMechanismState
    
    52 52
         , setBacktraceMechanismState
    
    53 53
           -- * Collecting backtraces
    
    54
    -    , Backtraces
    
    54
    +    , Backtraces(..)
    
    55 55
         , displayBacktraces
    
    56 56
         , collectBacktraces
    
    57 57
         ) where
    

  • libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
    ... ... @@ -9,7 +9,7 @@ module GHC.Internal.Exception.Backtrace
    9 9
         , getBacktraceMechanismState
    
    10 10
         , setBacktraceMechanismState
    
    11 11
           -- * Collecting backtraces
    
    12
    -    , Backtraces
    
    12
    +    , Backtraces(..)
    
    13 13
         , displayBacktraces
    
    14 14
         , collectBacktraces
    
    15 15
         ) where
    

  • testsuite/tests/interface-stability/base-exports.stdout
    ... ... @@ -322,7 +322,7 @@ module Control.Exception.Backtrace where
    322 322
       type BacktraceMechanism :: *
    
    323 323
       data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
    
    324 324
       type Backtraces :: *
    
    325
    -  data Backtraces = ...
    
    325
    +  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]}
    
    326 326
       collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
    
    327 327
       displayBacktraces :: Backtraces -> GHC.Internal.Base.String
    
    328 328
       getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
    

  • testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
    ... ... @@ -322,7 +322,7 @@ module Control.Exception.Backtrace where
    322 322
       type BacktraceMechanism :: *
    
    323 323
       data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
    
    324 324
       type Backtraces :: *
    
    325
    -  data Backtraces = ...
    
    325
    +  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]}
    
    326 326
       collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
    
    327 327
       displayBacktraces :: Backtraces -> GHC.Internal.Base.String
    
    328 328
       getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
    

  • testsuite/tests/interface-stability/base-exports.stdout-mingw32
    ... ... @@ -322,7 +322,7 @@ module Control.Exception.Backtrace where
    322 322
       type BacktraceMechanism :: *
    
    323 323
       data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
    
    324 324
       type Backtraces :: *
    
    325
    -  data Backtraces = ...
    
    325
    +  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]}
    
    326 326
       collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
    
    327 327
       displayBacktraces :: Backtraces -> GHC.Internal.Base.String
    
    328 328
       getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
    

  • testsuite/tests/interface-stability/base-exports.stdout-ws-32
    ... ... @@ -322,7 +322,7 @@ module Control.Exception.Backtrace where
    322 322
       type BacktraceMechanism :: *
    
    323 323
       data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
    
    324 324
       type Backtraces :: *
    
    325
    -  data Backtraces = ...
    
    325
    +  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]}
    
    326 326
       collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
    
    327 327
       displayBacktraces :: Backtraces -> GHC.Internal.Base.String
    
    328 328
       getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool