{-# LINE 1 "GHCi/InfoTable.hsc" #-} {-# LANGUAGE CPP, MagicHash, ScopedTypeVariables #-} {-# LINE 2 "GHCi/InfoTable.hsc" #-} -- | -- Run-time info table support. This module provides support for -- creating and reading info tables /in the running program/. -- We use the RTS data structures directly via hsc2hs. -- module GHCi.InfoTable ( peekItbl, StgInfoTable(..) , conInfoPtr {-# LINE 14 "GHCi/InfoTable.hsc" #-} ) where {-# LINE 19 "GHCi/InfoTable.hsc" #-} import Foreign import Foreign.C import GHC.Ptr import GHC.Exts import System.IO.Unsafe type ItblCodes = Either [Word8] [Word32] -- Get definitions for the structs, constants & config etc. {-# LINE 29 "GHCi/InfoTable.hsc" #-} -- Ultra-minimalist version specially for constructors {-# LINE 32 "GHCi/InfoTable.hsc" #-} type HalfWord = Word32 {-# LINE 38 "GHCi/InfoTable.hsc" #-} type EntryFunPtr = FunPtr (Ptr () -> IO (Ptr ())) data StgInfoTable = StgInfoTable { entry :: Maybe EntryFunPtr, -- Just <=> not ghciTablesNextToCode ptrs :: HalfWord, nptrs :: HalfWord, tipe :: HalfWord, srtlen :: HalfWord, code :: Maybe ItblCodes -- Just <=> ghciTablesNextToCode } peekItbl :: Ptr StgInfoTable -> IO StgInfoTable peekItbl a0 = do {-# LINE 53 "GHCi/InfoTable.hsc" #-} let entry' = Nothing {-# LINE 57 "GHCi/InfoTable.hsc" #-} ptrs' <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) a0 {-# LINE 58 "GHCi/InfoTable.hsc" #-} nptrs' <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) a0 {-# LINE 59 "GHCi/InfoTable.hsc" #-} tipe' <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) a0 {-# LINE 60 "GHCi/InfoTable.hsc" #-} srtlen' <- ((\hsc_ptr -> peekByteOff hsc_ptr 12)) a0 {-# LINE 61 "GHCi/InfoTable.hsc" #-} return StgInfoTable { entry = entry' , ptrs = ptrs' , nptrs = nptrs' , tipe = tipe' , srtlen = srtlen' , code = Nothing } -- | Convert a pointer to an StgConInfo into an info pointer that can be -- used in the header of a closure. conInfoPtr :: Ptr () -> Ptr () conInfoPtr ptr | ghciTablesNextToCode = ptr `plusPtr` ((24)) {-# LINE 75 "GHCi/InfoTable.hsc" #-} | otherwise = ptr ghciTablesNextToCode :: Bool {-# LINE 79 "GHCi/InfoTable.hsc" #-} ghciTablesNextToCode = True {-# LINE 83 "GHCi/InfoTable.hsc" #-} {-# LINE 458 "GHCi/InfoTable.hsc" #-}