Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
GHC.Debug.Types.Ptr
Description
Data types for representing different pointers and raw information All pointers are stored in little-endian to make arithmetic easier.
We have to send and recieve the pointers in big endian though. This conversion is dealt with in the Binary instance for ClosurePtr and then the other pointers are derived from this instance using DerivingVia
Synopsis
- newtype InfoTablePtr = InfoTablePtr Word64
- newtype RawInfoTable = RawInfoTable ByteString
- newtype ClosurePtr where
- UntaggedClosurePtr Word64
- pattern ClosurePtr :: Word64 -> ClosurePtr
- mkClosurePtr :: Word64 -> ClosurePtr
- readClosurePtr :: String -> Maybe ClosurePtr
- newtype RawClosure = RawClosure ByteString
- rawClosureSize :: RawClosure -> Int
- getInfoTblPtr :: HasCallStack => RawClosure -> InfoTablePtr
- applyBlockMask :: ClosurePtr -> BlockPtr
- applyMBlockMask :: ClosurePtr -> BlockPtr
- subtractBlockPtr :: ClosurePtr -> BlockPtr -> Word64
- heapAlloced :: ClosurePtr -> Bool
- getBlockOffset :: ClosurePtr -> Word64
- newtype BlockPtr = BlockPtr Word64
- data RawBlock = RawBlock BlockPtr Word16 ByteString
- isLargeBlock :: RawBlock -> Bool
- isPinnedBlock :: RawBlock -> Bool
- rawBlockAddr :: RawBlock -> BlockPtr
- extractFromBlock :: ClosurePtr -> RawBlock -> RawClosure
- blockMBlock :: BlockPtr -> Word64
- rawBlockSize :: RawBlock -> Int
- newtype StackPtr = StackPtr Word64
- newtype RawStack = RawStack ByteString
- subtractStackPtr :: StackPtr -> ClosurePtr -> Word64
- calculateStackLen :: Word32 -> Word64 -> ClosurePtr -> StackPtr -> Word64
- addStackPtr :: StackPtr -> Word64 -> StackPtr
- rawStackSize :: RawStack -> Int
- printStack :: RawStack -> String
- newtype PtrBitmap = PtrBitmap (Array Int Bool)
- traversePtrBitmap :: Monad m => (Bool -> m a) -> PtrBitmap -> m [a]
- blockMask :: Word64
- mblockMask :: Word64
- mblockMaxSize :: Word64
- blockMaxSize :: Word64
- profiling :: Bool
- tablesNextToCode :: Bool
- arrWordsBS :: [Word] -> ByteString
- prettyPrint :: ByteString -> String
- printBS :: HasCallStack => ByteString -> String
InfoTables
newtype InfoTablePtr Source #
Constructors
InfoTablePtr Word64 |
Instances
Show InfoTablePtr Source # | |
Defined in GHC.Debug.Types.Ptr Methods showsPrec :: Int -> InfoTablePtr -> ShowS # show :: InfoTablePtr -> String # showList :: [InfoTablePtr] -> ShowS # | |
Binary InfoTablePtr Source # | |
Defined in GHC.Debug.Types.Ptr | |
Eq InfoTablePtr Source # | |
Defined in GHC.Debug.Types.Ptr | |
Ord InfoTablePtr Source # | |
Defined in GHC.Debug.Types.Ptr Methods compare :: InfoTablePtr -> InfoTablePtr -> Ordering # (<) :: InfoTablePtr -> InfoTablePtr -> Bool # (<=) :: InfoTablePtr -> InfoTablePtr -> Bool # (>) :: InfoTablePtr -> InfoTablePtr -> Bool # (>=) :: InfoTablePtr -> InfoTablePtr -> Bool # max :: InfoTablePtr -> InfoTablePtr -> InfoTablePtr # min :: InfoTablePtr -> InfoTablePtr -> InfoTablePtr # | |
Hashable InfoTablePtr Source # | |
Defined in GHC.Debug.Types.Ptr |
newtype RawInfoTable Source #
Constructors
RawInfoTable ByteString |
Instances
Show RawInfoTable Source # | |
Defined in GHC.Debug.Types.Ptr Methods showsPrec :: Int -> RawInfoTable -> ShowS # show :: RawInfoTable -> String # showList :: [RawInfoTable] -> ShowS # | |
Binary RawInfoTable Source # | |
Defined in GHC.Debug.Types.Ptr | |
Eq RawInfoTable Source # | |
Defined in GHC.Debug.Types.Ptr | |
Ord RawInfoTable Source # | |
Defined in GHC.Debug.Types.Ptr Methods compare :: RawInfoTable -> RawInfoTable -> Ordering # (<) :: RawInfoTable -> RawInfoTable -> Bool # (<=) :: RawInfoTable -> RawInfoTable -> Bool # (>) :: RawInfoTable -> RawInfoTable -> Bool # (>=) :: RawInfoTable -> RawInfoTable -> Bool # max :: RawInfoTable -> RawInfoTable -> RawInfoTable # min :: RawInfoTable -> RawInfoTable -> RawInfoTable # |
Closures
newtype ClosurePtr Source #
Constructors
UntaggedClosurePtr Word64 |
Bundled Patterns
pattern ClosurePtr :: Word64 -> ClosurePtr |
Instances
Show ClosurePtr Source # | |
Defined in GHC.Debug.Types.Ptr Methods showsPrec :: Int -> ClosurePtr -> ShowS # show :: ClosurePtr -> String # showList :: [ClosurePtr] -> ShowS # | |
Binary ClosurePtr Source # | |
Defined in GHC.Debug.Types.Ptr | |
Eq ClosurePtr Source # | |
Defined in GHC.Debug.Types.Ptr | |
Ord ClosurePtr Source # | |
Defined in GHC.Debug.Types.Ptr Methods compare :: ClosurePtr -> ClosurePtr -> Ordering # (<) :: ClosurePtr -> ClosurePtr -> Bool # (<=) :: ClosurePtr -> ClosurePtr -> Bool # (>) :: ClosurePtr -> ClosurePtr -> Bool # (>=) :: ClosurePtr -> ClosurePtr -> Bool # max :: ClosurePtr -> ClosurePtr -> ClosurePtr # min :: ClosurePtr -> ClosurePtr -> ClosurePtr # | |
Hashable ClosurePtr Source # | |
Defined in GHC.Debug.Types.Ptr |
mkClosurePtr :: Word64 -> ClosurePtr Source #
readClosurePtr :: String -> Maybe ClosurePtr Source #
newtype RawClosure Source #
Constructors
RawClosure ByteString |
Instances
Show RawClosure Source # | |
Defined in GHC.Debug.Types.Ptr Methods showsPrec :: Int -> RawClosure -> ShowS # show :: RawClosure -> String # showList :: [RawClosure] -> ShowS # | |
Binary RawClosure Source # | |
Defined in GHC.Debug.Types.Ptr | |
Eq RawClosure Source # | |
Defined in GHC.Debug.Types.Ptr | |
Ord RawClosure Source # | |
Defined in GHC.Debug.Types.Ptr Methods compare :: RawClosure -> RawClosure -> Ordering # (<) :: RawClosure -> RawClosure -> Bool # (<=) :: RawClosure -> RawClosure -> Bool # (>) :: RawClosure -> RawClosure -> Bool # (>=) :: RawClosure -> RawClosure -> Bool # max :: RawClosure -> RawClosure -> RawClosure # min :: RawClosure -> RawClosure -> RawClosure # |
rawClosureSize :: RawClosure -> Int Source #
getInfoTblPtr :: HasCallStack => RawClosure -> InfoTablePtr Source #
Operations on ClosurePtr
applyBlockMask :: ClosurePtr -> BlockPtr Source #
applyMBlockMask :: ClosurePtr -> BlockPtr Source #
subtractBlockPtr :: ClosurePtr -> BlockPtr -> Word64 Source #
heapAlloced :: ClosurePtr -> Bool Source #
Check if the ClosurePtr is block allocated or not TODO: MP: These numbers are hard-coded from what mblock_address_space.begin and mblock_address_space.end were when I inspected them in gdb. I don't know if they are always the same of should be queried from the debuggee
getBlockOffset :: ClosurePtr -> Word64 Source #
Blocks
Constructors
RawBlock BlockPtr Word16 ByteString |
isLargeBlock :: RawBlock -> Bool Source #
isPinnedBlock :: RawBlock -> Bool Source #
rawBlockAddr :: RawBlock -> BlockPtr Source #
extractFromBlock :: ClosurePtr -> RawBlock -> RawClosure Source #
Invariant: ClosurePtr is within the range of the block
The RawClosure
this returns is actually the tail of the whole block,
this is fine because the memory for each block is only allocated once
due to how BS.drop is implemented via pointer arithmetic.
blockMBlock :: BlockPtr -> Word64 Source #
rawBlockSize :: RawBlock -> Int Source #
Stacks
Constructors
RawStack ByteString |
subtractStackPtr :: StackPtr -> ClosurePtr -> Word64 Source #
calculateStackLen :: Word32 -> Word64 -> ClosurePtr -> StackPtr -> Word64 Source #
rawStackSize :: RawStack -> Int Source #
printStack :: RawStack -> String Source #
Bitmaps
A bitmap that records whether each field of a stack frame is a pointer.
Constants
mblockMask :: Word64 Source #
Other utility
arrWordsBS :: [Word] -> ByteString Source #
prettyPrint :: ByteString -> String Source #
printBS :: HasCallStack => ByteString -> String Source #