Copyright | (c) Esa Ilari Vuokko, 2006 |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Esa Ilari Vuokko <ei@vuokko.info> |
Stability | provisional |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell98 |
A collection of FFI declarations for using Windows DebugApi.
Documentation
type DebugEventId = (PID, TID)
type ForeignAddress = Word32
type ThreadInfo = (THANDLE, ForeignAddress, ForeignAddress)
type ImageInfo = (HANDLE, ForeignAddress, DWORD, DWORD, ForeignAddress)
type ExceptionInfo = (Bool, Bool, ForeignAddress)
data Exception
data DebugEventInfo
type DebugEvent = (DebugEventId, DebugEventInfo)
peekDebugEvent :: Ptr a -> IO DebugEvent
waitForDebugEvent :: Maybe Int -> IO (Maybe DebugEvent)
getDebugEvents :: Int -> IO [DebugEvent]
continueDebugEvent :: DebugEventId -> Bool -> IO ()
debugActiveProcess :: PID -> IO ()
peekProcessMemory :: PHANDLE -> ForeignAddress -> Int -> Ptr a -> IO ()
readProcessMemory :: PHANDLE -> ForeignAddress -> Int -> IO (ForeignPtr a)
pokeProcessMemory :: PHANDLE -> ForeignAddress -> Int -> Ptr a -> IO ()
withProcessMemory :: PHANDLE -> ForeignAddress -> Int -> (Ptr a -> IO b) -> IO b
peekP :: Storable a => PHANDLE -> ForeignAddress -> IO a
pokeP :: Storable a => PHANDLE -> ForeignAddress -> a -> IO ()
suspendThread :: THANDLE -> IO DWORD
resumeThread :: THANDLE -> IO DWORD
withSuspendedThread :: THANDLE -> IO a -> IO a
getThreadContext :: THANDLE -> Ptr a -> IO ()
setThreadContext :: THANDLE -> Ptr a -> IO ()
useAllRegs :: Ptr a -> IO ()
withThreadContext :: THANDLE -> (Ptr a -> IO b) -> IO b
outputDebugString :: String -> IO ()
c_SuspendThread :: THANDLE -> IO DWORD
c_ResumeThread :: THANDLE -> IO DWORD
c_WaitForDebugEvent :: Ptr () -> DWORD -> IO BOOL
c_DebugActiveProcess :: DWORD -> IO Bool
c_GetThreadContext :: THANDLE -> Ptr () -> IO BOOL
c_SetThreadContext :: THANDLE -> Ptr () -> IO BOOL
c_OutputDebugString :: LPTSTR -> IO ()
debugBreak :: IO ()