|
System.Win32.DebugApi | Portability | portable | Stability | provisional | Maintainer | Esa Ilari Vuokko <ei@vuokko.info> |
|
|
|
Description |
A collection of FFI declarations for using Windows DebugApi.
|
|
|
Documentation |
|
type PID = DWORD |
|
type TID = DWORD |
|
type DebugEventId = (PID, TID) |
|
type ForeignAddress = Word32 |
|
type PHANDLE = Ptr () |
|
type THANDLE = Ptr () |
|
type ThreadInfo = (THANDLE, ForeignAddress, ForeignAddress) |
|
type ImageInfo = (HANDLE, ForeignAddress, DWORD, DWORD, ForeignAddress) |
|
type ExceptionInfo = (Bool, Bool, ForeignAddress) |
|
data Exception |
Constructors | UnknownException | | AccessViolation Bool ForeignAddress | | ArrayBoundsExceeded | | Breakpoint | | DataTypeMisalignment | | FltDenormalOperand | | FltDivideByZero | | FltInexactResult | | FltInvalidOperation | | FltOverflow | | FltStackCheck | | FltUnderflow | | IllegalInstruction | | InPageError | | IntDivideByZero | | IntOverflow | | InvalidDisposition | | NonContinuable | | PrivilegedInstruction | | SingleStep | | StackOverflow | |
| Instances | |
|
|
data DebugEventInfo |
Constructors | | Instances | |
|
|
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 |
|
eax :: Int |
|
ebx :: Int |
|
ecx :: Int |
|
edx :: Int |
|
esi :: Int |
|
edi :: Int |
|
ebp :: Int |
|
eip :: Int |
|
esp :: Int |
|
segCs :: Int |
|
segDs :: Int |
|
segEs :: Int |
|
segFs :: Int |
|
segGs :: Int |
|
eFlags :: Int |
|
dr :: Int -> Int |
|
setReg :: Ptr a -> Int -> DWORD -> IO () |
|
getReg :: Ptr a -> Int -> IO DWORD |
|
modReg :: Ptr a -> Int -> (DWORD -> DWORD) -> IO DWORD |
|
makeModThreadContext :: [(Int, DWORD -> DWORD)] -> Ptr a -> IO [DWORD] |
|
modifyThreadContext :: THANDLE -> [(Int, DWORD -> DWORD)] -> IO [DWORD] |
|
outputDebugString :: String -> IO () |
|
c_SuspendThread :: THANDLE -> IO DWORD |
|
c_ResumeThread :: THANDLE -> IO DWORD |
|
c_WaitForDebugEvent :: Ptr () -> DWORD -> IO BOOL |
|
c_ContinueDebugEvent :: DWORD -> DWORD -> DWORD -> IO BOOL |
|
c_DebugActiveProcess :: DWORD -> IO Bool |
|
c_ReadProcessMemory :: PHANDLE -> Ptr () -> Ptr Word8 -> DWORD -> Ptr DWORD -> IO BOOL |
|
c_WriteProcessMemory :: PHANDLE -> Ptr () -> Ptr Word8 -> DWORD -> Ptr DWORD -> IO BOOL |
|
c_GetThreadContext :: THANDLE -> Ptr () -> IO BOOL |
|
c_SetThreadContext :: THANDLE -> Ptr () -> IO BOOL |
|
c_OutputDebugString :: LPTSTR -> IO () |
|
isDebuggerPresent :: IO BOOL |
|
debugBreak :: IO () |
|
Produced by Haddock version 0.8 |