{-# LANGUAGE CPP #-} module Data.Memory.Debug.Wrapper where import System.Process import Foreign import Data.Word import Data.Int import Data.Binary (Binary(..)) import Data.Memory.Debug -- Class that wraps binary representable types so they can be read class Binary a => Wrapper a where load :: Pid -- Pid of the process that uses the memory region of the pointer -> Ptr Word8 -- Pointer to the first byte of where the type is stored -> IO a store :: Pid -- Pid of the process that uses the memory region of the pointer -> Ptr Word8 -- Pointer to the first byte of where the type is stored -> a -- The new value to store at the pointer -> IO () change :: Pid -> Ptr Word8 -> (a -> a) -> IO () change pid ptr f = load pid ptr >>= \v -> store pid ptr (f v) -- Macro that defines the instance for types that also have a Storable instance #define WRAPPER(TYPE) \ instance Wrapper TYPE where {\ load pid ptr = \ let len = sizeOf (undefined :: TYPE)\ in do { res <- processVMReadV pid ptr len ;\ return (decode res) };\ store pid ptr v = \ let len = sizeOf (undefined :: TYPE) \ in processVMWriteV pid ptr len (encode v)} -- Instances for Primitive Haskell types WRAPPER(Int) WRAPPER(Char) WRAPPER(Bool) -- Instances for Int types WRAPPER(Int8) WRAPPER(Int16) WRAPPER(Int32) WRAPPER(Int64) -- Instances for Word types WRAPPER(Word8) WRAPPER(Word16) WRAPPER(Word32) WRAPPER(Word64)