{-# LANGUAGE ForeignFunctionInterface #-} {-# LANGUAGE ScopedTypeVariables #-} module Data.Memory.Debug.FFI where import Control.Monad import Foreign import Foreign.C import System.Posix.Types import Data.Memory.Debug.IOVec type SSize_T = CULong -------------------------------------------------------------------------------- -- process_vm_readv -- -------------------------------------------------------------------------------- foreign import ccall unsafe "sys/uio.h process_vm_readv" processVMReadV_ :: CPid -> Ptr IOVec -- Local IO Vector -> CULong -- Local IO Vector count -> Ptr IOVec -- Remote IO Vector -> CULong -- Remote IO Vector count -> CULong -- Flags -> IO SSize_T -- | Wrapper function for process_vm_readv. No flags, only single io vectors are -- read processVMReadV :: CPid -- Process to read the virtual memory from -> Ptr Word8 -- Pointer to a on the remote side -> Int -- Length from the pointer to read -> IO [Word8] processVMReadV pid addr len = allocaBytes len $ \buf -> alloca $ \iov_local_ptr -> alloca $ \iov_remote_ptr -> do -- Set up the local and remote IO vectors poke iov_local_ptr $ IOVec buf (fromIntegral len) poke iov_remote_ptr $ IOVec addr (fromIntegral len) print $ IOVec addr (fromIntegral len) -- Perform the read readBytes <- processVMReadV_ pid iov_local_ptr 1 iov_remote_ptr 1 0 print readBytes -- Return the result iov_local <- peek iov_local_ptr result <- peekArray (iov_len iov_local) (iov_base iov_local) return result -------------------------------------------------------------------------------- -- process_vm_writev -- -------------------------------------------------------------------------------- foreign import ccall unsafe "sys/uio.h process_vm_writev" processVMWriteV_ :: CPid -> Ptr IOVec -- Local IO Vector -> CULong -- Local IO Vector count -> Ptr IOVec -- Remote IO Vector -> CULong -- Remote IO Vector count -> CULong -- Flags -> IO SSize_T -- | Wrapper function for process_vm_writev. No flags, only single io vectors -- are written processVMWriteV :: CPid -> Ptr Word8 -> Int -> [Word8] -> IO () processVMWriteV pid addr len xs = allocaBytes len $ \buf -> alloca $ \iov_local_ptr -> alloca $ \iov_remote_ptr -> do pokeArray buf xs -- Set up the local and remote IO vectors poke iov_local_ptr $ IOVec buf (fromIntegral len) poke iov_remote_ptr $ IOVec addr (fromIntegral len) print $ IOVec addr (fromIntegral len) -- Perform the write writtenBytes <- processVMWriteV_ pid iov_local_ptr 1 iov_remote_ptr 1 0 return ()