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

Commits:

8 changed files:

Changes:

  • libraries/ghc-internal/cbits/Stack_c.c
    ... ... @@ -9,13 +9,13 @@
    9 9
     #include "rts/storage/InfoTables.h"
    
    10 10
     
    
    11 11
     StgWord stackFrameSize(StgStack *stack, StgWord offset) {
    
    12
    -  StgClosure *c = (StgClosure *)stack->sp + offset;
    
    12
    +  StgClosure *c = (StgClosure *)(stack->sp + offset);
    
    13 13
       ASSERT(LOOKS_LIKE_CLOSURE_PTR(c));
    
    14 14
       return stack_frame_sizeW(c);
    
    15 15
     }
    
    16 16
     
    
    17 17
     StgStack *getUnderflowFrameStack(StgStack *stack, StgWord offset) {
    
    18
    -  StgClosure *frame = (StgClosure *)stack->sp + offset;
    
    18
    +  StgClosure *frame = (StgClosure *)(stack->sp + offset);
    
    19 19
       ASSERT(LOOKS_LIKE_CLOSURE_PTR(frame));
    
    20 20
       const StgRetInfoTable *info = get_ret_itbl((StgClosure *)frame);
    
    21 21
     
    

  • libraries/ghc-internal/ghc-internal.cabal.in
    ... ... @@ -300,6 +300,7 @@ Library
    300 300
             GHC.Internal.Stack.CCS
    
    301 301
             GHC.Internal.Stack.CloneStack
    
    302 302
             GHC.Internal.Stack.Constants
    
    303
    +        GHC.Internal.Stack.ConstantsProf
    
    303 304
             GHC.Internal.Stack.Decode
    
    304 305
             GHC.Internal.Stack.Types
    
    305 306
             GHC.Internal.Stats
    

  • libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc
    1
    +{-# LANGUAGE CPP #-}
    
    2
    +{-# LANGUAGE DerivingStrategies #-}
    
    3
    +{-# LANGUAGE GeneralizedNewtypeDeriving #-}
    
    4
    +module GHC.Internal.Stack.ConstantsProf where
    
    5
    +
    
    6
    +import GHC.Internal.Base
    
    7
    +import GHC.Internal.Enum
    
    8
    +import GHC.Internal.Num
    
    9
    +import GHC.Internal.Show
    
    10
    +import GHC.Internal.Real
    
    11
    +
    
    12
    +-- This file is a copy of GHC.Internal.Stack.Constants, but compiled with PROFILING
    
    13
    +-- defined, since hsc is only invoked once per build in the vanilla way.
    
    14
    +--
    
    15
    +-- Also see GHC.Internal.Heap.InfoTable{Prof}
    
    16
    +#define PROFILING
    
    17
    +#include "Rts.h"
    
    18
    +#undef BLOCK_SIZE
    
    19
    +#undef MBLOCK_SIZE
    
    20
    +#undef BLOCKS_PER_MBLOCK
    
    21
    +#include "DerivedConstants.h"
    
    22
    +
    
    23
    +newtype ByteOffset = ByteOffset { offsetInBytes :: Int }
    
    24
    +  deriving newtype (Eq, Show, Integral, Real, Num, Enum, Ord)
    
    25
    +
    
    26
    +newtype WordOffset = WordOffset { offsetInWords :: Int }
    
    27
    +  deriving newtype (Eq, Show, Integral, Real, Num, Enum, Ord)
    
    28
    +
    
    29
    +offsetStgCatchFrameHandler :: WordOffset
    
    30
    +offsetStgCatchFrameHandler = byteOffsetToWordOffset $
    
    31
    +  (#const OFFSET_StgCatchFrame_handler) + (#size StgHeader)
    
    32
    +
    
    33
    +sizeStgCatchFrame :: Int
    
    34
    +sizeStgCatchFrame = bytesToWords $
    
    35
    +  (#const SIZEOF_StgCatchFrame_NoHdr) + (#size StgHeader)
    
    36
    +
    
    37
    +offsetStgCatchSTMFrameCode :: WordOffset
    
    38
    +offsetStgCatchSTMFrameCode = byteOffsetToWordOffset $
    
    39
    +  (#const OFFSET_StgCatchSTMFrame_code) + (#size StgHeader)
    
    40
    +
    
    41
    +offsetStgCatchSTMFrameHandler :: WordOffset
    
    42
    +offsetStgCatchSTMFrameHandler = byteOffsetToWordOffset $
    
    43
    +  (#const OFFSET_StgCatchSTMFrame_handler) + (#size StgHeader)
    
    44
    +
    
    45
    +sizeStgCatchSTMFrame :: Int
    
    46
    +sizeStgCatchSTMFrame = bytesToWords $
    
    47
    +  (#const SIZEOF_StgCatchSTMFrame_NoHdr) + (#size StgHeader)
    
    48
    +
    
    49
    +offsetStgUpdateFrameUpdatee :: WordOffset
    
    50
    +offsetStgUpdateFrameUpdatee = byteOffsetToWordOffset $
    
    51
    +  (#const OFFSET_StgUpdateFrame_updatee) + (#size StgHeader)
    
    52
    +
    
    53
    +sizeStgUpdateFrame :: Int
    
    54
    +sizeStgUpdateFrame = bytesToWords $
    
    55
    +  (#const SIZEOF_StgUpdateFrame_NoHdr) + (#size StgHeader)
    
    56
    +
    
    57
    +offsetStgAtomicallyFrameCode :: WordOffset
    
    58
    +offsetStgAtomicallyFrameCode = byteOffsetToWordOffset $
    
    59
    +  (#const OFFSET_StgAtomicallyFrame_code) + (#size StgHeader)
    
    60
    +
    
    61
    +offsetStgAtomicallyFrameResult :: WordOffset
    
    62
    +offsetStgAtomicallyFrameResult = byteOffsetToWordOffset $
    
    63
    +  (#const OFFSET_StgAtomicallyFrame_result) + (#size StgHeader)
    
    64
    +
    
    65
    +sizeStgAtomicallyFrame :: Int
    
    66
    +sizeStgAtomicallyFrame = bytesToWords $
    
    67
    +  (#const SIZEOF_StgAtomicallyFrame_NoHdr) + (#size StgHeader)
    
    68
    +
    
    69
    +offsetStgCatchRetryFrameRunningAltCode :: WordOffset
    
    70
    +offsetStgCatchRetryFrameRunningAltCode = byteOffsetToWordOffset $
    
    71
    +  (#const OFFSET_StgCatchRetryFrame_running_alt_code) + (#size StgHeader)
    
    72
    +
    
    73
    +offsetStgCatchRetryFrameRunningFirstCode :: WordOffset
    
    74
    +offsetStgCatchRetryFrameRunningFirstCode = byteOffsetToWordOffset $
    
    75
    +  (#const OFFSET_StgCatchRetryFrame_first_code) + (#size StgHeader)
    
    76
    +
    
    77
    +offsetStgCatchRetryFrameAltCode :: WordOffset
    
    78
    +offsetStgCatchRetryFrameAltCode = byteOffsetToWordOffset $
    
    79
    +  (#const OFFSET_StgCatchRetryFrame_alt_code) + (#size StgHeader)
    
    80
    +
    
    81
    +sizeStgCatchRetryFrame :: Int
    
    82
    +sizeStgCatchRetryFrame = bytesToWords $
    
    83
    +  (#const SIZEOF_StgCatchRetryFrame_NoHdr) + (#size StgHeader)
    
    84
    +
    
    85
    +offsetStgRetFunFrameSize :: WordOffset
    
    86
    +-- StgRetFun has no header, but only a pointer to the info table at the beginning.
    
    87
    +offsetStgRetFunFrameSize = byteOffsetToWordOffset (#const OFFSET_StgRetFun_size)
    
    88
    +
    
    89
    +offsetStgRetFunFrameFun :: WordOffset
    
    90
    +offsetStgRetFunFrameFun = byteOffsetToWordOffset (#const OFFSET_StgRetFun_fun)
    
    91
    +
    
    92
    +offsetStgRetFunFramePayload :: WordOffset
    
    93
    +offsetStgRetFunFramePayload = byteOffsetToWordOffset (#const OFFSET_StgRetFun_payload)
    
    94
    +
    
    95
    +sizeStgRetFunFrame :: Int
    
    96
    +sizeStgRetFunFrame = bytesToWords (#const SIZEOF_StgRetFun)
    
    97
    +
    
    98
    +sizeStgAnnFrame :: Int
    
    99
    +sizeStgAnnFrame = bytesToWords $
    
    100
    +  (#const SIZEOF_StgAnnFrame_NoHdr) + (#size StgHeader)
    
    101
    +
    
    102
    +offsetStgAnnFrameAnn :: WordOffset
    
    103
    +offsetStgAnnFrameAnn = byteOffsetToWordOffset $
    
    104
    +  (#const OFFSET_StgAnnFrame_ann) + (#size StgHeader)
    
    105
    +
    
    106
    +offsetStgBCOFrameInstrs :: ByteOffset
    
    107
    +offsetStgBCOFrameInstrs = (#const OFFSET_StgBCO_instrs) + (#size StgHeader)
    
    108
    +
    
    109
    +offsetStgBCOFrameLiterals :: ByteOffset
    
    110
    +offsetStgBCOFrameLiterals = (#const OFFSET_StgBCO_literals) + (#size StgHeader)
    
    111
    +
    
    112
    +offsetStgBCOFramePtrs :: ByteOffset
    
    113
    +offsetStgBCOFramePtrs = (#const OFFSET_StgBCO_ptrs) + (#size StgHeader)
    
    114
    +
    
    115
    +offsetStgBCOFrameArity :: ByteOffset
    
    116
    +offsetStgBCOFrameArity = (#const OFFSET_StgBCO_arity) + (#size StgHeader)
    
    117
    +
    
    118
    +offsetStgBCOFrameSize :: ByteOffset
    
    119
    +offsetStgBCOFrameSize = (#const OFFSET_StgBCO_size) + (#size StgHeader)
    
    120
    +
    
    121
    +offsetStgClosurePayload :: WordOffset
    
    122
    +offsetStgClosurePayload = byteOffsetToWordOffset $
    
    123
    +  (#const OFFSET_StgClosure_payload) + (#size StgHeader)
    
    124
    +
    
    125
    +sizeStgClosure :: Int
    
    126
    +sizeStgClosure = bytesToWords (#size StgHeader)
    
    127
    +
    
    128
    +byteOffsetToWordOffset :: ByteOffset -> WordOffset
    
    129
    +byteOffsetToWordOffset = WordOffset . bytesToWords . fromInteger . toInteger
    
    130
    +
    
    131
    +bytesToWords :: Int -> Int
    
    132
    +bytesToWords b =
    
    133
    +  if b `mod` bytesInWord == 0 then
    
    134
    +      fromIntegral $ b `div` bytesInWord
    
    135
    +    else
    
    136
    +      error "Unexpected struct alignment!"
    
    137
    +
    
    138
    +bytesInWord :: Int
    
    139
    +bytesInWord = (#const SIZEOF_VOID_P)
    
    140
    +

  • libraries/ghc-internal/src/GHC/Internal/Stack/Decode.hs
    ... ... @@ -54,9 +54,19 @@ import GHC.Internal.Heap.Closures
    54 54
         GenStackField(..)
    
    55 55
       )
    
    56 56
     import GHC.Internal.Heap.Constants (wORD_SIZE_IN_BITS)
    
    57
    -import GHC.Internal.Heap.InfoTable
    
    58 57
     import GHC.Internal.Stack.Annotation
    
    58
    +-- See Note [No way-dependent imports]
    
    59
    +#if defined(PROFILING)
    
    60
    +import GHC.Internal.Stack.Constants ()
    
    61
    +import GHC.Internal.Stack.ConstantsProf
    
    62
    +import GHC.Internal.Heap.InfoTable ()
    
    63
    +import GHC.Internal.Heap.InfoTableProf
    
    64
    +#else
    
    65
    +import GHC.Internal.Heap.InfoTable
    
    66
    +import GHC.Internal.Heap.InfoTableProf ()
    
    59 67
     import GHC.Internal.Stack.Constants
    
    68
    +import GHC.Internal.Stack.ConstantsProf ()
    
    69
    +#endif
    
    60 70
     import GHC.Internal.Stack.CloneStack
    
    61 71
     import GHC.Internal.InfoProv.Types (InfoProv (..), ipLoc, lookupIPE)
    
    62 72
     
    

  • libraries/ghc-internal/tests/backtraces/T26507.hs
    1
    +import GHC.Internal.Control.Exception
    
    2
    +import GHC.Internal.Exception.Backtrace
    
    3
    +
    
    4
    +main :: IO ()
    
    5
    +main = do
    
    6
    +  setBacktraceMechanismState IPEBacktrace True
    
    7
    +  throwIO $ ErrorCall "Throw error"

  • libraries/ghc-internal/tests/backtraces/T26507.stderr
    1
    +T26507: Uncaught exception ghc-internal:GHC.Internal.Exception.ErrorCall:
    
    2
    +
    
    3
    +Throw error
    
    4
    +
    
    5
    +IPE backtrace:
    
    6
    +HasCallStack backtrace:
    
    7
    +  throwIO, called at T26507.hs:7:3 in main:Main
    
    8
    +

  • libraries/ghc-internal/tests/backtraces/all.T
    1 1
     test('T14532a', [], compile_and_run, [''])
    
    2 2
     test('T14532b', [], compile_and_run, [''])
    
    3
    +test('T26507', [ when(have_profiling(), extra_ways(['prof']))
    
    4
    +               , when(js_arch(), skip)
    
    5
    +	       , exit_code(1)], compile_and_run, [''])
    
    6
    +

  • libraries/ghc-internal/tests/stack-annotation/all.T
    1 1
     # Javascript backend don't support annotation frames, yet
    
    2
    -setTestOpts(when(js_arch(), skip))
    
    2
    +# and test with profiling way if available (#26507)
    
    3
    +ann_frame_opts = [ when(js_arch(), skip)
    
    4
    +                 , when(have_profiling(), extra_ways(['prof']))
    
    5
    +		 , extra_files(['TestUtils.hs'])]
    
    3 6
     
    
    4
    -test('ann_frame001', [extra_files(['TestUtils.hs'])], compile_and_run, [''])
    
    5
    -test('ann_frame002', [extra_files(['TestUtils.hs'])], compile_and_run, [''])
    
    6
    -test('ann_frame003', [extra_files(['TestUtils.hs'])], compile_and_run, [''])
    
    7
    -test('ann_frame004', [extra_files(['TestUtils.hs'])], compile_and_run, [''])
    7
    +test('ann_frame001', ann_frame_opts, compile_and_run, [''])
    
    8
    +test('ann_frame002', ann_frame_opts, compile_and_run, [''])
    
    9
    +test('ann_frame003', ann_frame_opts, compile_and_run, [''])
    
    10
    +test('ann_frame004', ann_frame_opts, compile_and_run, [''])