{-# OPTIONS_GHC -optc-DPROFILING #-}
{-# LINE 1 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE MagicHash #-}

module GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingEnabled(
    peekStgTSOProfInfo
    , peekTopCCS
) where


{-# LINE 10 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}

-- See [hsc and CPP workaround]









import           Data.IntSet (IntSet)
import qualified Data.IntSet as IntSet
import           Data.IntMap.Strict (IntMap)
import qualified Data.IntMap.Strict as IntMap
import           Data.IORef (IORef, newIORef, readIORef, writeIORef)
import           Foreign
import           Foreign.C.String
import           GHC.Exts
import           GHC.Exts.Heap.ProfInfo.Types
import           Prelude

-- Use Int based containers for pointers (addresses) for better performance.
-- These will be queried a lot!
type AddressSet = IntSet
type AddressMap = IntMap

peekStgTSOProfInfo :: (Ptr b -> IO (Maybe CostCentreStack)) -> Ptr a -> IO (Maybe StgTSOProfInfo)
peekStgTSOProfInfo :: forall b a.
(Ptr b -> IO (Maybe CostCentreStack))
-> Ptr a -> IO (Maybe StgTSOProfInfo)
peekStgTSOProfInfo Ptr b -> IO (Maybe CostCentreStack)
decodeCCS Ptr a
tsoPtr = do
    Ptr b
cccs_ptr <- Ptr a -> Int -> IO (Ptr b)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr a
tsoPtr Int
cccsOffset
    Maybe CostCentreStack
cccs' <- Ptr b -> IO (Maybe CostCentreStack)
decodeCCS Ptr b
cccs_ptr

    Maybe StgTSOProfInfo -> IO (Maybe StgTSOProfInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe StgTSOProfInfo -> IO (Maybe StgTSOProfInfo))
-> Maybe StgTSOProfInfo -> IO (Maybe StgTSOProfInfo)
forall a b. (a -> b) -> a -> b
$ StgTSOProfInfo -> Maybe StgTSOProfInfo
forall a. a -> Maybe a
Just StgTSOProfInfo {
        cccs :: Maybe CostCentreStack
cccs = Maybe CostCentreStack
cccs'
    }

peekTopCCS :: Ptr b -> IO (Maybe CostCentreStack)
peekTopCCS :: forall b. Ptr b -> IO (Maybe CostCentreStack)
peekTopCCS Ptr b
cccs_ptr = do
  IORef (IntMap CostCentre)
costCenterCacheRef <- IntMap CostCentre -> IO (IORef (IntMap CostCentre))
forall a. a -> IO (IORef a)
newIORef IntMap CostCentre
forall a. IntMap a
IntMap.empty
  AddressSet
-> IORef (IntMap CostCentre) -> Ptr b -> IO (Maybe CostCentreStack)
forall costCentreStack.
AddressSet
-> IORef (IntMap CostCentre)
-> Ptr costCentreStack
-> IO (Maybe CostCentreStack)
peekCostCentreStack AddressSet
IntSet.empty IORef (IntMap CostCentre)
costCenterCacheRef Ptr b
cccs_ptr

cccsOffset :: Int
cccsOffset :: Int
cccsOffset = (Int
112) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ((Int
24))
{-# LINE 53 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}

peekCostCentreStack
    :: AddressSet
    -> IORef (AddressMap CostCentre)
    -> Ptr costCentreStack
    -> IO (Maybe CostCentreStack)
peekCostCentreStack :: forall costCentreStack.
AddressSet
-> IORef (IntMap CostCentre)
-> Ptr costCentreStack
-> IO (Maybe CostCentreStack)
peekCostCentreStack AddressSet
_ IORef (IntMap CostCentre)
_ Ptr costCentreStack
ptr | Ptr costCentreStack
ptr Ptr costCentreStack -> Ptr costCentreStack -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr costCentreStack
forall a. Ptr a
nullPtr = Maybe CostCentreStack -> IO (Maybe CostCentreStack)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe CostCentreStack
forall a. Maybe a
Nothing
peekCostCentreStack AddressSet
loopBreakers IORef (IntMap CostCentre)
_ Ptr costCentreStack
ptr | Int -> AddressSet -> Bool
IntSet.member (Ptr costCentreStack -> Int
forall a. Ptr a -> Int
ptrToInt Ptr costCentreStack
ptr) AddressSet
loopBreakers = Maybe CostCentreStack -> IO (Maybe CostCentreStack)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe CostCentreStack
forall a. Maybe a
Nothing
peekCostCentreStack AddressSet
loopBreakers IORef (IntMap CostCentre)
costCenterCacheRef Ptr costCentreStack
ptr = do
        Int
ccs_ccsID' <- ((\Ptr costCentreStack
hsc_ptr -> Ptr costCentreStack -> Int -> IO Int
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr costCentreStack
hsc_ptr Int
0)) Ptr costCentreStack
ptr
{-# LINE 63 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}
        Ptr Any
ccs_cc_ptr <- ((\Ptr costCentreStack
hsc_ptr -> Ptr costCentreStack -> Int -> IO (Ptr Any)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr costCentreStack
hsc_ptr Int
8)) Ptr costCentreStack
ptr
{-# LINE 64 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}
        CostCentre
ccs_cc' <- IORef (IntMap CostCentre) -> Ptr Any -> IO CostCentre
forall costCentre.
IORef (IntMap CostCentre) -> Ptr costCentre -> IO CostCentre
peekCostCentre IORef (IntMap CostCentre)
costCenterCacheRef Ptr Any
ccs_cc_ptr
        Ptr Any
ccs_prevStack_ptr <- ((\Ptr costCentreStack
hsc_ptr -> Ptr costCentreStack -> Int -> IO (Ptr Any)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr costCentreStack
hsc_ptr Int
16)) Ptr costCentreStack
ptr
{-# LINE 66 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}
        let loopBreakers' :: AddressSet
loopBreakers' = (Int -> AddressSet -> AddressSet
IntSet.insert Int
ptrAsInt AddressSet
loopBreakers)
        Maybe CostCentreStack
ccs_prevStack' <- AddressSet
-> IORef (IntMap CostCentre)
-> Ptr Any
-> IO (Maybe CostCentreStack)
forall costCentreStack.
AddressSet
-> IORef (IntMap CostCentre)
-> Ptr costCentreStack
-> IO (Maybe CostCentreStack)
peekCostCentreStack AddressSet
loopBreakers' IORef (IntMap CostCentre)
costCenterCacheRef Ptr Any
ccs_prevStack_ptr
        Ptr Any
ccs_indexTable_ptr <- ((\Ptr costCentreStack
hsc_ptr -> Ptr costCentreStack -> Int -> IO (Ptr Any)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr costCentreStack
hsc_ptr Int
24)) Ptr costCentreStack
ptr
{-# LINE 69 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}
        Maybe IndexTable
ccs_indexTable' <- AddressSet
-> IORef (IntMap CostCentre) -> Ptr Any -> IO (Maybe IndexTable)
forall indexTable.
AddressSet
-> IORef (IntMap CostCentre)
-> Ptr indexTable
-> IO (Maybe IndexTable)
peekIndexTable AddressSet
loopBreakers' IORef (IntMap CostCentre)
costCenterCacheRef Ptr Any
ccs_indexTable_ptr
        Ptr Any
ccs_root_ptr <- ((\Ptr costCentreStack
hsc_ptr -> Ptr costCentreStack -> Int -> IO (Ptr Any)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr costCentreStack
hsc_ptr Int
32)) Ptr costCentreStack
ptr
{-# LINE 71 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}
        Maybe CostCentreStack
ccs_root' <- AddressSet
-> IORef (IntMap CostCentre)
-> Ptr Any
-> IO (Maybe CostCentreStack)
forall costCentreStack.
AddressSet
-> IORef (IntMap CostCentre)
-> Ptr costCentreStack
-> IO (Maybe CostCentreStack)
peekCostCentreStack AddressSet
loopBreakers' IORef (IntMap CostCentre)
costCenterCacheRef Ptr Any
ccs_root_ptr
        Word
ccs_depth' <- ((\Ptr costCentreStack
hsc_ptr -> Ptr costCentreStack -> Int -> IO Word
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr costCentreStack
hsc_ptr Int
40)) Ptr costCentreStack
ptr
{-# LINE 73 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}
        Word64
ccs_scc_count' <- ((\Ptr costCentreStack
hsc_ptr -> Ptr costCentreStack -> Int -> IO Word64
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr costCentreStack
hsc_ptr Int
48)) Ptr costCentreStack
ptr
{-# LINE 74 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}
        Word
ccs_selected' <- ((\Ptr costCentreStack
hsc_ptr -> Ptr costCentreStack -> Int -> IO Word
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr costCentreStack
hsc_ptr Int
56)) Ptr costCentreStack
ptr
{-# LINE 75 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}
        Word
ccs_time_ticks' <- ((\Ptr costCentreStack
hsc_ptr -> Ptr costCentreStack -> Int -> IO Word
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr costCentreStack
hsc_ptr Int
64)) Ptr costCentreStack
ptr
{-# LINE 76 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}
        Word64
ccs_mem_alloc' <- ((\Ptr costCentreStack
hsc_ptr -> Ptr costCentreStack -> Int -> IO Word64
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr costCentreStack
hsc_ptr Int
72)) Ptr costCentreStack
ptr
{-# LINE 77 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}
        Word64
ccs_inherited_alloc' <- ((\Ptr costCentreStack
hsc_ptr -> Ptr costCentreStack -> Int -> IO Word64
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr costCentreStack
hsc_ptr Int
80)) Ptr costCentreStack
ptr
{-# LINE 78 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}
        Word
ccs_inherited_ticks' <- ((\Ptr costCentreStack
hsc_ptr -> Ptr costCentreStack -> Int -> IO Word
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr costCentreStack
hsc_ptr Int
88)) Ptr costCentreStack
ptr
{-# LINE 79 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}

        Maybe CostCentreStack -> IO (Maybe CostCentreStack)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe CostCentreStack -> IO (Maybe CostCentreStack))
-> Maybe CostCentreStack -> IO (Maybe CostCentreStack)
forall a b. (a -> b) -> a -> b
$ CostCentreStack -> Maybe CostCentreStack
forall a. a -> Maybe a
Just CostCentreStack {
            ccs_ccsID :: Int
ccs_ccsID = Int
ccs_ccsID',
            ccs_cc :: CostCentre
ccs_cc = CostCentre
ccs_cc',
            ccs_prevStack :: Maybe CostCentreStack
ccs_prevStack = Maybe CostCentreStack
ccs_prevStack',
            ccs_indexTable :: Maybe IndexTable
ccs_indexTable = Maybe IndexTable
ccs_indexTable',
            ccs_root :: Maybe CostCentreStack
ccs_root = Maybe CostCentreStack
ccs_root',
            ccs_depth :: Word
ccs_depth = Word
ccs_depth',
            ccs_scc_count :: Word64
ccs_scc_count = Word64
ccs_scc_count',
            ccs_selected :: Word
ccs_selected = Word
ccs_selected',
            ccs_time_ticks :: Word
ccs_time_ticks = Word
ccs_time_ticks',
            ccs_mem_alloc :: Word64
ccs_mem_alloc = Word64
ccs_mem_alloc',
            ccs_inherited_alloc :: Word64
ccs_inherited_alloc = Word64
ccs_inherited_alloc',
            ccs_inherited_ticks :: Word
ccs_inherited_ticks = Word
ccs_inherited_ticks'
        }
    where
        ptrAsInt :: Int
ptrAsInt = Ptr costCentreStack -> Int
forall a. Ptr a -> Int
ptrToInt Ptr costCentreStack
ptr

peekCostCentre :: IORef (AddressMap CostCentre) -> Ptr costCentre -> IO CostCentre
peekCostCentre :: forall costCentre.
IORef (IntMap CostCentre) -> Ptr costCentre -> IO CostCentre
peekCostCentre IORef (IntMap CostCentre)
costCenterCacheRef Ptr costCentre
ptr = do
    IntMap CostCentre
costCenterCache <- IORef (IntMap CostCentre) -> IO (IntMap CostCentre)
forall a. IORef a -> IO a
readIORef IORef (IntMap CostCentre)
costCenterCacheRef
    case Int -> IntMap CostCentre -> Maybe CostCentre
forall a. Int -> IntMap a -> Maybe a
IntMap.lookup Int
ptrAsInt IntMap CostCentre
costCenterCache of
        (Just CostCentre
a) -> CostCentre -> IO CostCentre
forall (m :: * -> *) a. Monad m => a -> m a
return CostCentre
a
        Maybe CostCentre
Nothing -> do
                    Int
cc_ccID' <- ((\Ptr costCentre
hsc_ptr -> Ptr costCentre -> Int -> IO Int
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr costCentre
hsc_ptr Int
0)) Ptr costCentre
ptr
{-# LINE 104 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}
                    CString
cc_label_ptr <- ((\Ptr costCentre
hsc_ptr -> Ptr costCentre -> Int -> IO CString
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr costCentre
hsc_ptr Int
8)) Ptr costCentre
ptr
{-# LINE 105 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}
                    String
cc_label' <- CString -> IO String
peekCString CString
cc_label_ptr
                    CString
cc_module_ptr <- ((\Ptr costCentre
hsc_ptr -> Ptr costCentre -> Int -> IO CString
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr costCentre
hsc_ptr Int
16)) Ptr costCentre
ptr
{-# LINE 107 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}
                    String
cc_module' <- CString -> IO String
peekCString CString
cc_module_ptr
                    CString
cc_srcloc_ptr <- ((\Ptr costCentre
hsc_ptr -> Ptr costCentre -> Int -> IO CString
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr costCentre
hsc_ptr Int
24)) Ptr costCentre
ptr
{-# LINE 109 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}
                    Maybe String
cc_srcloc' <- do
                        if CString
cc_srcloc_ptr CString -> CString -> Bool
forall a. Eq a => a -> a -> Bool
== CString
forall a. Ptr a
nullPtr then
                            Maybe String -> IO (Maybe String)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
forall a. Maybe a
Nothing
                        else
                            (String -> Maybe String) -> IO String -> IO (Maybe String)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Maybe String
forall a. a -> Maybe a
Just (CString -> IO String
peekCString CString
cc_srcloc_ptr)
                    Word64
cc_mem_alloc' <- ((\Ptr costCentre
hsc_ptr -> Ptr costCentre -> Int -> IO Word64
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr costCentre
hsc_ptr Int
32)) Ptr costCentre
ptr
{-# LINE 115 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}
                    Word
cc_time_ticks' <- ((\Ptr costCentre
hsc_ptr -> Ptr costCentre -> Int -> IO Word
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr costCentre
hsc_ptr Int
40)) Ptr costCentre
ptr
{-# LINE 116 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}
                    Bool
cc_is_caf' <- ((\Ptr costCentre
hsc_ptr -> Ptr costCentre -> Int -> IO Bool
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr costCentre
hsc_ptr Int
48)) Ptr costCentre
ptr
{-# LINE 117 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}
                    Ptr Any
cc_link_ptr <- ((\Ptr costCentre
hsc_ptr -> Ptr costCentre -> Int -> IO (Ptr Any)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr costCentre
hsc_ptr Int
56)) Ptr costCentre
ptr
{-# LINE 118 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}
                    Maybe CostCentre
cc_link' <- if Ptr Any
cc_link_ptr Ptr Any -> Ptr Any -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr Any
forall a. Ptr a
nullPtr then
                        Maybe CostCentre -> IO (Maybe CostCentre)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe CostCentre
forall a. Maybe a
Nothing
                    else
                        (CostCentre -> Maybe CostCentre)
-> IO CostCentre -> IO (Maybe CostCentre)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CostCentre -> Maybe CostCentre
forall a. a -> Maybe a
Just (IORef (IntMap CostCentre) -> Ptr Any -> IO CostCentre
forall costCentre.
IORef (IntMap CostCentre) -> Ptr costCentre -> IO CostCentre
peekCostCentre IORef (IntMap CostCentre)
costCenterCacheRef Ptr Any
cc_link_ptr)

                    let result :: CostCentre
result = CostCentre {
                        cc_ccID :: Int
cc_ccID = Int
cc_ccID',
                        cc_label :: String
cc_label = String
cc_label',
                        cc_module :: String
cc_module = String
cc_module',
                        cc_srcloc :: Maybe String
cc_srcloc = Maybe String
cc_srcloc',
                        cc_mem_alloc :: Word64
cc_mem_alloc = Word64
cc_mem_alloc',
                        cc_time_ticks :: Word
cc_time_ticks = Word
cc_time_ticks',
                        cc_is_caf :: Bool
cc_is_caf = Bool
cc_is_caf',
                        cc_link :: Maybe CostCentre
cc_link = Maybe CostCentre
cc_link'
                    }

                    IORef (IntMap CostCentre) -> IntMap CostCentre -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (IntMap CostCentre)
costCenterCacheRef (Int -> CostCentre -> IntMap CostCentre -> IntMap CostCentre
forall a. Int -> a -> IntMap a -> IntMap a
IntMap.insert Int
ptrAsInt CostCentre
result IntMap CostCentre
costCenterCache)

                    CostCentre -> IO CostCentre
forall (m :: * -> *) a. Monad m => a -> m a
return CostCentre
result
    where
        ptrAsInt :: Int
ptrAsInt = Ptr costCentre -> Int
forall a. Ptr a -> Int
ptrToInt Ptr costCentre
ptr

peekIndexTable :: AddressSet -> IORef (AddressMap CostCentre) -> Ptr indexTable -> IO (Maybe IndexTable)
peekIndexTable :: forall indexTable.
AddressSet
-> IORef (IntMap CostCentre)
-> Ptr indexTable
-> IO (Maybe IndexTable)
peekIndexTable AddressSet
_ IORef (IntMap CostCentre)
_ Ptr indexTable
ptr | Ptr indexTable
ptr Ptr indexTable -> Ptr indexTable -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr indexTable
forall a. Ptr a
nullPtr = Maybe IndexTable -> IO (Maybe IndexTable)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe IndexTable
forall a. Maybe a
Nothing
peekIndexTable AddressSet
loopBreakers IORef (IntMap CostCentre)
costCenterCacheRef Ptr indexTable
ptr = do
        Ptr Any
it_cc_ptr <- ((\Ptr indexTable
hsc_ptr -> Ptr indexTable -> Int -> IO (Ptr Any)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr indexTable
hsc_ptr Int
0)) Ptr indexTable
ptr
{-# LINE 144 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}
        CostCentre
it_cc' <- IORef (IntMap CostCentre) -> Ptr Any -> IO CostCentre
forall costCentre.
IORef (IntMap CostCentre) -> Ptr costCentre -> IO CostCentre
peekCostCentre IORef (IntMap CostCentre)
costCenterCacheRef Ptr Any
it_cc_ptr
        Ptr Any
it_ccs_ptr <- ((\Ptr indexTable
hsc_ptr -> Ptr indexTable -> Int -> IO (Ptr Any)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr indexTable
hsc_ptr Int
8)) Ptr indexTable
ptr
{-# LINE 146 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}
        Maybe CostCentreStack
it_ccs' <- AddressSet
-> IORef (IntMap CostCentre)
-> Ptr Any
-> IO (Maybe CostCentreStack)
forall costCentreStack.
AddressSet
-> IORef (IntMap CostCentre)
-> Ptr costCentreStack
-> IO (Maybe CostCentreStack)
peekCostCentreStack AddressSet
loopBreakers IORef (IntMap CostCentre)
costCenterCacheRef Ptr Any
it_ccs_ptr
        Ptr Any
it_next_ptr <- ((\Ptr indexTable
hsc_ptr -> Ptr indexTable -> Int -> IO (Ptr Any)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr indexTable
hsc_ptr Int
16)) Ptr indexTable
ptr
{-# LINE 148 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}
        Maybe IndexTable
it_next' <- AddressSet
-> IORef (IntMap CostCentre) -> Ptr Any -> IO (Maybe IndexTable)
forall indexTable.
AddressSet
-> IORef (IntMap CostCentre)
-> Ptr indexTable
-> IO (Maybe IndexTable)
peekIndexTable AddressSet
loopBreakers IORef (IntMap CostCentre)
costCenterCacheRef Ptr Any
it_next_ptr
        Bool
it_back_edge' <- ((\Ptr indexTable
hsc_ptr -> Ptr indexTable -> Int -> IO Bool
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr indexTable
hsc_ptr Int
24)) Ptr indexTable
ptr
{-# LINE 150 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}

        Maybe IndexTable -> IO (Maybe IndexTable)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe IndexTable -> IO (Maybe IndexTable))
-> Maybe IndexTable -> IO (Maybe IndexTable)
forall a b. (a -> b) -> a -> b
$ IndexTable -> Maybe IndexTable
forall a. a -> Maybe a
Just IndexTable {
            it_cc :: CostCentre
it_cc = CostCentre
it_cc',
            it_ccs :: Maybe CostCentreStack
it_ccs = Maybe CostCentreStack
it_ccs',
            it_next :: Maybe IndexTable
it_next = Maybe IndexTable
it_next',
            it_back_edge :: Bool
it_back_edge = Bool
it_back_edge'
        }

-- | casts a @Ptr@ to an @Int@
ptrToInt :: Ptr a -> Int
ptrToInt :: forall a. Ptr a -> Int
ptrToInt (Ptr Addr#
a#) = Int# -> Int
I# (Addr# -> Int#
addr2Int# Addr#
a#)


{-# LINE 174 "GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc" #-}