{-# OPTIONS_GHC -optc-DPROFILING #-}
{-# LINE 1 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module GHC.Internal.Stack.ConstantsProf where
import GHC.Internal.Base
import GHC.Internal.Enum
import GHC.Internal.Num
import GHC.Internal.Show
import GHC.Internal.Real
newtype ByteOffset = ByteOffset { ByteOffset -> Int
offsetInBytes :: Int }
  deriving newtype (ByteOffset -> ByteOffset -> Bool
(ByteOffset -> ByteOffset -> Bool)
-> (ByteOffset -> ByteOffset -> Bool) -> Eq ByteOffset
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ByteOffset -> ByteOffset -> Bool
== :: ByteOffset -> ByteOffset -> Bool
$c/= :: ByteOffset -> ByteOffset -> Bool
/= :: ByteOffset -> ByteOffset -> Bool
Eq, Int -> ByteOffset -> ShowS
[ByteOffset] -> ShowS
ByteOffset -> String
(Int -> ByteOffset -> ShowS)
-> (ByteOffset -> String)
-> ([ByteOffset] -> ShowS)
-> Show ByteOffset
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ByteOffset -> ShowS
showsPrec :: Int -> ByteOffset -> ShowS
$cshow :: ByteOffset -> String
show :: ByteOffset -> String
$cshowList :: [ByteOffset] -> ShowS
showList :: [ByteOffset] -> ShowS
Show, Enum ByteOffset
Real ByteOffset
(Real ByteOffset, Enum ByteOffset) =>
(ByteOffset -> ByteOffset -> ByteOffset)
-> (ByteOffset -> ByteOffset -> ByteOffset)
-> (ByteOffset -> ByteOffset -> ByteOffset)
-> (ByteOffset -> ByteOffset -> ByteOffset)
-> (ByteOffset -> ByteOffset -> (ByteOffset, ByteOffset))
-> (ByteOffset -> ByteOffset -> (ByteOffset, ByteOffset))
-> (ByteOffset -> Integer)
-> Integral ByteOffset
ByteOffset -> Integer
ByteOffset -> ByteOffset -> (ByteOffset, ByteOffset)
ByteOffset -> ByteOffset -> ByteOffset
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: ByteOffset -> ByteOffset -> ByteOffset
quot :: ByteOffset -> ByteOffset -> ByteOffset
$crem :: ByteOffset -> ByteOffset -> ByteOffset
rem :: ByteOffset -> ByteOffset -> ByteOffset
$cdiv :: ByteOffset -> ByteOffset -> ByteOffset
div :: ByteOffset -> ByteOffset -> ByteOffset
$cmod :: ByteOffset -> ByteOffset -> ByteOffset
mod :: ByteOffset -> ByteOffset -> ByteOffset
$cquotRem :: ByteOffset -> ByteOffset -> (ByteOffset, ByteOffset)
quotRem :: ByteOffset -> ByteOffset -> (ByteOffset, ByteOffset)
$cdivMod :: ByteOffset -> ByteOffset -> (ByteOffset, ByteOffset)
divMod :: ByteOffset -> ByteOffset -> (ByteOffset, ByteOffset)
$ctoInteger :: ByteOffset -> Integer
toInteger :: ByteOffset -> Integer
Integral, Num ByteOffset
Ord ByteOffset
(Num ByteOffset, Ord ByteOffset) =>
(ByteOffset -> Rational) -> Real ByteOffset
ByteOffset -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: ByteOffset -> Rational
toRational :: ByteOffset -> Rational
Real, Integer -> ByteOffset
ByteOffset -> ByteOffset
ByteOffset -> ByteOffset -> ByteOffset
(ByteOffset -> ByteOffset -> ByteOffset)
-> (ByteOffset -> ByteOffset -> ByteOffset)
-> (ByteOffset -> ByteOffset -> ByteOffset)
-> (ByteOffset -> ByteOffset)
-> (ByteOffset -> ByteOffset)
-> (ByteOffset -> ByteOffset)
-> (Integer -> ByteOffset)
-> Num ByteOffset
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: ByteOffset -> ByteOffset -> ByteOffset
+ :: ByteOffset -> ByteOffset -> ByteOffset
$c- :: ByteOffset -> ByteOffset -> ByteOffset
- :: ByteOffset -> ByteOffset -> ByteOffset
$c* :: ByteOffset -> ByteOffset -> ByteOffset
* :: ByteOffset -> ByteOffset -> ByteOffset
$cnegate :: ByteOffset -> ByteOffset
negate :: ByteOffset -> ByteOffset
$cabs :: ByteOffset -> ByteOffset
abs :: ByteOffset -> ByteOffset
$csignum :: ByteOffset -> ByteOffset
signum :: ByteOffset -> ByteOffset
$cfromInteger :: Integer -> ByteOffset
fromInteger :: Integer -> ByteOffset
Num, Int -> ByteOffset
ByteOffset -> Int
ByteOffset -> [ByteOffset]
ByteOffset -> ByteOffset
ByteOffset -> ByteOffset -> [ByteOffset]
ByteOffset -> ByteOffset -> ByteOffset -> [ByteOffset]
(ByteOffset -> ByteOffset)
-> (ByteOffset -> ByteOffset)
-> (Int -> ByteOffset)
-> (ByteOffset -> Int)
-> (ByteOffset -> [ByteOffset])
-> (ByteOffset -> ByteOffset -> [ByteOffset])
-> (ByteOffset -> ByteOffset -> [ByteOffset])
-> (ByteOffset -> ByteOffset -> ByteOffset -> [ByteOffset])
-> Enum ByteOffset
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: ByteOffset -> ByteOffset
succ :: ByteOffset -> ByteOffset
$cpred :: ByteOffset -> ByteOffset
pred :: ByteOffset -> ByteOffset
$ctoEnum :: Int -> ByteOffset
toEnum :: Int -> ByteOffset
$cfromEnum :: ByteOffset -> Int
fromEnum :: ByteOffset -> Int
$cenumFrom :: ByteOffset -> [ByteOffset]
enumFrom :: ByteOffset -> [ByteOffset]
$cenumFromThen :: ByteOffset -> ByteOffset -> [ByteOffset]
enumFromThen :: ByteOffset -> ByteOffset -> [ByteOffset]
$cenumFromTo :: ByteOffset -> ByteOffset -> [ByteOffset]
enumFromTo :: ByteOffset -> ByteOffset -> [ByteOffset]
$cenumFromThenTo :: ByteOffset -> ByteOffset -> ByteOffset -> [ByteOffset]
enumFromThenTo :: ByteOffset -> ByteOffset -> ByteOffset -> [ByteOffset]
Enum, Eq ByteOffset
Eq ByteOffset =>
(ByteOffset -> ByteOffset -> Ordering)
-> (ByteOffset -> ByteOffset -> Bool)
-> (ByteOffset -> ByteOffset -> Bool)
-> (ByteOffset -> ByteOffset -> Bool)
-> (ByteOffset -> ByteOffset -> Bool)
-> (ByteOffset -> ByteOffset -> ByteOffset)
-> (ByteOffset -> ByteOffset -> ByteOffset)
-> Ord ByteOffset
ByteOffset -> ByteOffset -> Bool
ByteOffset -> ByteOffset -> Ordering
ByteOffset -> ByteOffset -> ByteOffset
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ByteOffset -> ByteOffset -> Ordering
compare :: ByteOffset -> ByteOffset -> Ordering
$c< :: ByteOffset -> ByteOffset -> Bool
< :: ByteOffset -> ByteOffset -> Bool
$c<= :: ByteOffset -> ByteOffset -> Bool
<= :: ByteOffset -> ByteOffset -> Bool
$c> :: ByteOffset -> ByteOffset -> Bool
> :: ByteOffset -> ByteOffset -> Bool
$c>= :: ByteOffset -> ByteOffset -> Bool
>= :: ByteOffset -> ByteOffset -> Bool
$cmax :: ByteOffset -> ByteOffset -> ByteOffset
max :: ByteOffset -> ByteOffset -> ByteOffset
$cmin :: ByteOffset -> ByteOffset -> ByteOffset
min :: ByteOffset -> ByteOffset -> ByteOffset
Ord)
newtype WordOffset = WordOffset { WordOffset -> Int
offsetInWords :: Int }
  deriving newtype (WordOffset -> WordOffset -> Bool
(WordOffset -> WordOffset -> Bool)
-> (WordOffset -> WordOffset -> Bool) -> Eq WordOffset
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WordOffset -> WordOffset -> Bool
== :: WordOffset -> WordOffset -> Bool
$c/= :: WordOffset -> WordOffset -> Bool
/= :: WordOffset -> WordOffset -> Bool
Eq, Int -> WordOffset -> ShowS
[WordOffset] -> ShowS
WordOffset -> String
(Int -> WordOffset -> ShowS)
-> (WordOffset -> String)
-> ([WordOffset] -> ShowS)
-> Show WordOffset
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> WordOffset -> ShowS
showsPrec :: Int -> WordOffset -> ShowS
$cshow :: WordOffset -> String
show :: WordOffset -> String
$cshowList :: [WordOffset] -> ShowS
showList :: [WordOffset] -> ShowS
Show, Enum WordOffset
Real WordOffset
(Real WordOffset, Enum WordOffset) =>
(WordOffset -> WordOffset -> WordOffset)
-> (WordOffset -> WordOffset -> WordOffset)
-> (WordOffset -> WordOffset -> WordOffset)
-> (WordOffset -> WordOffset -> WordOffset)
-> (WordOffset -> WordOffset -> (WordOffset, WordOffset))
-> (WordOffset -> WordOffset -> (WordOffset, WordOffset))
-> (WordOffset -> Integer)
-> Integral WordOffset
WordOffset -> Integer
WordOffset -> WordOffset -> (WordOffset, WordOffset)
WordOffset -> WordOffset -> WordOffset
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: WordOffset -> WordOffset -> WordOffset
quot :: WordOffset -> WordOffset -> WordOffset
$crem :: WordOffset -> WordOffset -> WordOffset
rem :: WordOffset -> WordOffset -> WordOffset
$cdiv :: WordOffset -> WordOffset -> WordOffset
div :: WordOffset -> WordOffset -> WordOffset
$cmod :: WordOffset -> WordOffset -> WordOffset
mod :: WordOffset -> WordOffset -> WordOffset
$cquotRem :: WordOffset -> WordOffset -> (WordOffset, WordOffset)
quotRem :: WordOffset -> WordOffset -> (WordOffset, WordOffset)
$cdivMod :: WordOffset -> WordOffset -> (WordOffset, WordOffset)
divMod :: WordOffset -> WordOffset -> (WordOffset, WordOffset)
$ctoInteger :: WordOffset -> Integer
toInteger :: WordOffset -> Integer
Integral, Num WordOffset
Ord WordOffset
(Num WordOffset, Ord WordOffset) =>
(WordOffset -> Rational) -> Real WordOffset
WordOffset -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: WordOffset -> Rational
toRational :: WordOffset -> Rational
Real, Integer -> WordOffset
WordOffset -> WordOffset
WordOffset -> WordOffset -> WordOffset
(WordOffset -> WordOffset -> WordOffset)
-> (WordOffset -> WordOffset -> WordOffset)
-> (WordOffset -> WordOffset -> WordOffset)
-> (WordOffset -> WordOffset)
-> (WordOffset -> WordOffset)
-> (WordOffset -> WordOffset)
-> (Integer -> WordOffset)
-> Num WordOffset
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: WordOffset -> WordOffset -> WordOffset
+ :: WordOffset -> WordOffset -> WordOffset
$c- :: WordOffset -> WordOffset -> WordOffset
- :: WordOffset -> WordOffset -> WordOffset
$c* :: WordOffset -> WordOffset -> WordOffset
* :: WordOffset -> WordOffset -> WordOffset
$cnegate :: WordOffset -> WordOffset
negate :: WordOffset -> WordOffset
$cabs :: WordOffset -> WordOffset
abs :: WordOffset -> WordOffset
$csignum :: WordOffset -> WordOffset
signum :: WordOffset -> WordOffset
$cfromInteger :: Integer -> WordOffset
fromInteger :: Integer -> WordOffset
Num, Int -> WordOffset
WordOffset -> Int
WordOffset -> [WordOffset]
WordOffset -> WordOffset
WordOffset -> WordOffset -> [WordOffset]
WordOffset -> WordOffset -> WordOffset -> [WordOffset]
(WordOffset -> WordOffset)
-> (WordOffset -> WordOffset)
-> (Int -> WordOffset)
-> (WordOffset -> Int)
-> (WordOffset -> [WordOffset])
-> (WordOffset -> WordOffset -> [WordOffset])
-> (WordOffset -> WordOffset -> [WordOffset])
-> (WordOffset -> WordOffset -> WordOffset -> [WordOffset])
-> Enum WordOffset
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: WordOffset -> WordOffset
succ :: WordOffset -> WordOffset
$cpred :: WordOffset -> WordOffset
pred :: WordOffset -> WordOffset
$ctoEnum :: Int -> WordOffset
toEnum :: Int -> WordOffset
$cfromEnum :: WordOffset -> Int
fromEnum :: WordOffset -> Int
$cenumFrom :: WordOffset -> [WordOffset]
enumFrom :: WordOffset -> [WordOffset]
$cenumFromThen :: WordOffset -> WordOffset -> [WordOffset]
enumFromThen :: WordOffset -> WordOffset -> [WordOffset]
$cenumFromTo :: WordOffset -> WordOffset -> [WordOffset]
enumFromTo :: WordOffset -> WordOffset -> [WordOffset]
$cenumFromThenTo :: WordOffset -> WordOffset -> WordOffset -> [WordOffset]
enumFromThenTo :: WordOffset -> WordOffset -> WordOffset -> [WordOffset]
Enum, Eq WordOffset
Eq WordOffset =>
(WordOffset -> WordOffset -> Ordering)
-> (WordOffset -> WordOffset -> Bool)
-> (WordOffset -> WordOffset -> Bool)
-> (WordOffset -> WordOffset -> Bool)
-> (WordOffset -> WordOffset -> Bool)
-> (WordOffset -> WordOffset -> WordOffset)
-> (WordOffset -> WordOffset -> WordOffset)
-> Ord WordOffset
WordOffset -> WordOffset -> Bool
WordOffset -> WordOffset -> Ordering
WordOffset -> WordOffset -> WordOffset
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: WordOffset -> WordOffset -> Ordering
compare :: WordOffset -> WordOffset -> Ordering
$c< :: WordOffset -> WordOffset -> Bool
< :: WordOffset -> WordOffset -> Bool
$c<= :: WordOffset -> WordOffset -> Bool
<= :: WordOffset -> WordOffset -> Bool
$c> :: WordOffset -> WordOffset -> Bool
> :: WordOffset -> WordOffset -> Bool
$c>= :: WordOffset -> WordOffset -> Bool
>= :: WordOffset -> WordOffset -> Bool
$cmax :: WordOffset -> WordOffset -> WordOffset
max :: WordOffset -> WordOffset -> WordOffset
$cmin :: WordOffset -> WordOffset -> WordOffset
min :: WordOffset -> WordOffset -> WordOffset
Ord)
offsetStgCatchFrameHandler :: WordOffset
offsetStgCatchFrameHandler :: WordOffset
offsetStgCatchFrameHandler = ByteOffset -> WordOffset
byteOffsetToWordOffset (ByteOffset -> WordOffset) -> ByteOffset -> WordOffset
forall a b. (a -> b) -> a -> b
$
  (ByteOffset
0) ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ ((ByteOffset
24))
{-# LINE 32 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
sizeStgCatchFrame :: Int
sizeStgCatchFrame :: Int
sizeStgCatchFrame = Int -> Int
bytesToWords (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$
  (Int
8) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ((Int
24))
{-# LINE 36 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
offsetStgCatchSTMFrameCode :: WordOffset
offsetStgCatchSTMFrameCode :: WordOffset
offsetStgCatchSTMFrameCode = ByteOffset -> WordOffset
byteOffsetToWordOffset (ByteOffset -> WordOffset) -> ByteOffset -> WordOffset
forall a b. (a -> b) -> a -> b
$
  (ByteOffset
0) ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ ((ByteOffset
24))
{-# LINE 40 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
offsetStgCatchSTMFrameHandler :: WordOffset
offsetStgCatchSTMFrameHandler :: WordOffset
offsetStgCatchSTMFrameHandler = ByteOffset -> WordOffset
byteOffsetToWordOffset (ByteOffset -> WordOffset) -> ByteOffset -> WordOffset
forall a b. (a -> b) -> a -> b
$
  (ByteOffset
8) ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ ((ByteOffset
24))
{-# LINE 44 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
sizeStgCatchSTMFrame :: Int
sizeStgCatchSTMFrame :: Int
sizeStgCatchSTMFrame = Int -> Int
bytesToWords (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$
  (Int
16) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ((Int
24))
{-# LINE 48 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
offsetStgUpdateFrameUpdatee :: WordOffset
offsetStgUpdateFrameUpdatee :: WordOffset
offsetStgUpdateFrameUpdatee = ByteOffset -> WordOffset
byteOffsetToWordOffset (ByteOffset -> WordOffset) -> ByteOffset -> WordOffset
forall a b. (a -> b) -> a -> b
$
  (ByteOffset
0) ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ ((ByteOffset
24))
{-# LINE 52 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
sizeStgUpdateFrame :: Int
sizeStgUpdateFrame :: Int
sizeStgUpdateFrame = Int -> Int
bytesToWords (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$
  (Int
8) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ((Int
24))
{-# LINE 56 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
offsetStgAtomicallyFrameCode :: WordOffset
offsetStgAtomicallyFrameCode :: WordOffset
offsetStgAtomicallyFrameCode = ByteOffset -> WordOffset
byteOffsetToWordOffset (ByteOffset -> WordOffset) -> ByteOffset -> WordOffset
forall a b. (a -> b) -> a -> b
$
  (ByteOffset
0) ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ ((ByteOffset
24))
{-# LINE 60 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
offsetStgAtomicallyFrameResult :: WordOffset
offsetStgAtomicallyFrameResult :: WordOffset
offsetStgAtomicallyFrameResult = ByteOffset -> WordOffset
byteOffsetToWordOffset (ByteOffset -> WordOffset) -> ByteOffset -> WordOffset
forall a b. (a -> b) -> a -> b
$
  (ByteOffset
8) ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ ((ByteOffset
24))
{-# LINE 64 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
sizeStgAtomicallyFrame :: Int
sizeStgAtomicallyFrame :: Int
sizeStgAtomicallyFrame = Int -> Int
bytesToWords (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$
  (Int
16) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ((Int
24))
{-# LINE 68 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
offsetStgCatchRetryFrameRunningAltCode :: WordOffset
offsetStgCatchRetryFrameRunningAltCode :: WordOffset
offsetStgCatchRetryFrameRunningAltCode = ByteOffset -> WordOffset
byteOffsetToWordOffset (ByteOffset -> WordOffset) -> ByteOffset -> WordOffset
forall a b. (a -> b) -> a -> b
$
  (ByteOffset
0) ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ ((ByteOffset
24))
{-# LINE 72 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
offsetStgCatchRetryFrameRunningFirstCode :: WordOffset
offsetStgCatchRetryFrameRunningFirstCode :: WordOffset
offsetStgCatchRetryFrameRunningFirstCode = ByteOffset -> WordOffset
byteOffsetToWordOffset (ByteOffset -> WordOffset) -> ByteOffset -> WordOffset
forall a b. (a -> b) -> a -> b
$
  (ByteOffset
8) ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ ((ByteOffset
24))
{-# LINE 76 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
offsetStgCatchRetryFrameAltCode :: WordOffset
offsetStgCatchRetryFrameAltCode :: WordOffset
offsetStgCatchRetryFrameAltCode = ByteOffset -> WordOffset
byteOffsetToWordOffset (ByteOffset -> WordOffset) -> ByteOffset -> WordOffset
forall a b. (a -> b) -> a -> b
$
  (ByteOffset
16) ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ ((ByteOffset
24))
{-# LINE 80 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
sizeStgCatchRetryFrame :: Int
sizeStgCatchRetryFrame :: Int
sizeStgCatchRetryFrame = Int -> Int
bytesToWords (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$
  (Int
24) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ((Int
24))
{-# LINE 84 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
offsetStgRetFunFrameSize :: WordOffset
offsetStgRetFunFrameSize :: WordOffset
offsetStgRetFunFrameSize = ByteOffset -> WordOffset
byteOffsetToWordOffset (ByteOffset
8)
{-# LINE 88 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
offsetStgRetFunFrameFun :: WordOffset
offsetStgRetFunFrameFun :: WordOffset
offsetStgRetFunFrameFun = ByteOffset -> WordOffset
byteOffsetToWordOffset (ByteOffset
16)
{-# LINE 91 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
offsetStgRetFunFramePayload :: WordOffset
offsetStgRetFunFramePayload :: WordOffset
offsetStgRetFunFramePayload = ByteOffset -> WordOffset
byteOffsetToWordOffset (ByteOffset
24)
{-# LINE 94 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
sizeStgRetFunFrame :: Int
sizeStgRetFunFrame :: Int
sizeStgRetFunFrame = Int -> Int
bytesToWords (Int
24)
{-# LINE 97 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
sizeStgAnnFrame :: Int
sizeStgAnnFrame :: Int
sizeStgAnnFrame = Int -> Int
bytesToWords (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$
  (Int
8) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ((Int
24))
{-# LINE 101 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
offsetStgAnnFrameAnn :: WordOffset
offsetStgAnnFrameAnn :: WordOffset
offsetStgAnnFrameAnn = ByteOffset -> WordOffset
byteOffsetToWordOffset (ByteOffset -> WordOffset) -> ByteOffset -> WordOffset
forall a b. (a -> b) -> a -> b
$
  (ByteOffset
0) ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ ((ByteOffset
24))
{-# LINE 105 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
offsetStgBCOFrameInstrs :: ByteOffset
offsetStgBCOFrameInstrs :: ByteOffset
offsetStgBCOFrameInstrs = (ByteOffset
0) ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ ((ByteOffset
24))
{-# LINE 108 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
offsetStgBCOFrameLiterals :: ByteOffset
offsetStgBCOFrameLiterals :: ByteOffset
offsetStgBCOFrameLiterals = (ByteOffset
8) ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ ((ByteOffset
24))
{-# LINE 111 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
offsetStgBCOFramePtrs :: ByteOffset
offsetStgBCOFramePtrs :: ByteOffset
offsetStgBCOFramePtrs = (ByteOffset
16) ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ ((ByteOffset
24))
{-# LINE 114 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
offsetStgBCOFrameArity :: ByteOffset
offsetStgBCOFrameArity :: ByteOffset
offsetStgBCOFrameArity = (ByteOffset
24) ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ ((ByteOffset
24))
{-# LINE 117 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
offsetStgBCOFrameSize :: ByteOffset
offsetStgBCOFrameSize :: ByteOffset
offsetStgBCOFrameSize = (ByteOffset
28) ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ ((ByteOffset
24))
{-# LINE 120 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
offsetStgClosurePayload :: WordOffset
offsetStgClosurePayload :: WordOffset
offsetStgClosurePayload = ByteOffset -> WordOffset
byteOffsetToWordOffset (ByteOffset -> WordOffset) -> ByteOffset -> WordOffset
forall a b. (a -> b) -> a -> b
$
  (ByteOffset
0) ByteOffset -> ByteOffset -> ByteOffset
forall a. Num a => a -> a -> a
+ ((ByteOffset
24))
{-# LINE 124 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
sizeStgClosure :: Int
sizeStgClosure :: Int
sizeStgClosure = Int -> Int
bytesToWords ((Int
24))
{-# LINE 127 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}
byteOffsetToWordOffset :: ByteOffset -> WordOffset
byteOffsetToWordOffset :: ByteOffset -> WordOffset
byteOffsetToWordOffset = Int -> WordOffset
WordOffset (Int -> WordOffset)
-> (ByteOffset -> Int) -> ByteOffset -> WordOffset
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int
bytesToWords (Int -> Int) -> (ByteOffset -> Int) -> ByteOffset -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Integer -> Int) -> (ByteOffset -> Integer) -> ByteOffset -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteOffset -> Integer
forall a. Integral a => a -> Integer
toInteger
bytesToWords :: Int -> Int
bytesToWords :: Int -> Int
bytesToWords Int
b =
  if Int
b Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
bytesInWord Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then
      Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int
b Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
bytesInWord
    else
      String -> Int
forall a. HasCallStack => String -> a
error String
"Unexpected struct alignment!"
bytesInWord :: Int
bytesInWord :: Int
bytesInWord = (Int
8)
{-# LINE 140 "libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc" #-}