{-# OPTIONS_GHC -optc-DPROFILING #-}
{-# LINE 1 "libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc" #-}
{-# LANGUAGE NoMonoLocalBinds #-}
module GHC.Exts.Heap.InfoTableProf
    ( module GHC.Exts.Heap.InfoTable.Types
    , itblSize
    , peekItbl
    , pokeItbl
    ) where

-- This file overrides InfoTable.hsc's implementation of peekItbl and pokeItbl.
-- Manually defining PROFILING gives the #peek and #poke macros an accurate
-- representation of StgInfoTable_ when hsc2hs runs.



import Prelude -- See note [Why do we import Prelude here?]
import GHC.Exts.Heap.InfoTable.Types

{-# LINE 21 "libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc" #-}
import Foreign

-- | Read an InfoTable from the heap into a haskell type.
-- WARNING: This code assumes it is passed a pointer to a "standard" info
-- table. If tables_next_to_code is enabled, it will look 1 byte before the
-- start for the entry field.
peekItbl :: Ptr StgInfoTable -> IO StgInfoTable
peekItbl :: Ptr StgInfoTable -> IO StgInfoTable
peekItbl Ptr StgInfoTable
a0 = do

{-# LINE 33 "libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc" #-}
  let ptr :: Ptr StgInfoTable
ptr = Ptr StgInfoTable
a0
      entry' :: Maybe a
entry' = Maybe a
forall a. Maybe a
Nothing

{-# LINE 36 "libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc" #-}
  ptrs'   <- ((\hsc_ptr -> peekByteOff hsc_ptr 16)) ptr
{-# LINE 37 "libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc" #-}
  nptrs'  <- ((\hsc_ptr -> peekByteOff hsc_ptr 20)) ptr
{-# LINE 38 "libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc" #-}
  tipe'   <- ((\hsc_ptr -> peekByteOff hsc_ptr 24)) ptr
{-# LINE 39 "libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc" #-}

{-# LINE 40 "libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc" #-}
  srtlen' <- ((\hsc_ptr -> peekByteOff hsc_ptr 28)) a0
{-# LINE 41 "libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc" #-}

{-# LINE 44 "libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc" #-}
  StgInfoTable -> IO StgInfoTable
forall (m :: * -> *) a. Monad m => a -> m a
return StgInfoTable :: Maybe EntryFunPtr
-> HalfWord
-> HalfWord
-> ClosureType
-> HalfWord
-> Maybe ItblCodes
-> StgInfoTable
StgInfoTable
    { entry :: Maybe EntryFunPtr
entry  = Maybe EntryFunPtr
forall a. Maybe a
entry'
    , ptrs :: HalfWord
ptrs   = HalfWord
ptrs'
    , nptrs :: HalfWord
nptrs  = HalfWord
nptrs'
    , tipe :: ClosureType
tipe   = Int -> ClosureType
forall a. Enum a => Int -> a
toEnum (HalfWord -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (HalfWord
tipe' :: HalfWord))
    , srtlen :: HalfWord
srtlen = HalfWord
srtlen'
    , code :: Maybe ItblCodes
code   = Maybe ItblCodes
forall a. Maybe a
Nothing
    }

pokeItbl :: Ptr StgInfoTable -> StgInfoTable -> IO ()
pokeItbl :: Ptr StgInfoTable -> StgInfoTable -> IO ()
pokeItbl Ptr StgInfoTable
a0 StgInfoTable
itbl = do

{-# LINE 58 "libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc" #-}
  ((\Ptr StgInfoTable
hsc_ptr -> Ptr StgInfoTable -> Int -> HalfWord -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr StgInfoTable
hsc_ptr Int
16)) Ptr StgInfoTable
a0 (StgInfoTable -> HalfWord
ptrs StgInfoTable
itbl)
{-# LINE 59 "libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc" #-}
  ((\hsc_ptr -> pokeByteOff hsc_ptr 20)) a0 (nptrs itbl)
{-# LINE 60 "libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc" #-}
  ((\hsc_ptr -> pokeByteOff hsc_ptr 24)) a0 (fromEnum (tipe itbl))
{-# LINE 61 "libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc" #-}

{-# LINE 62 "libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc" #-}
  ((\hsc_ptr -> pokeByteOff hsc_ptr 28)) a0 (srtlen itbl)
{-# LINE 63 "libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc" #-}

{-# LINE 66 "libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc" #-}

{-# LINE 67 "libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc" #-}
  let code_offset = a0 `plusPtr` ((32))
{-# LINE 68 "libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc" #-}
  case code itbl of
    Nothing -> return ()
    Just (Left xs) -> pokeArray code_offset xs
    Just (Right xs) -> pokeArray code_offset xs

{-# LINE 73 "libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc" #-}

itblSize :: Int
itblSize :: Int
itblSize = ((Int
32))
{-# LINE 76 "libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc" #-}