Win32-2.2.0.0: A binding to part of the Win32 librarySource codeContentsIndex
System.Win32.DebugApi
Portabilityportable
Stabilityprovisional
MaintainerEsa Ilari Vuokko <ei@vuokko.info>
Description
A collection of FFI declarations for using Windows DebugApi.
Documentation
type PID = DWORDSource
type TID = DWORDSource
type DebugEventId = (PID, TID)Source
type ForeignAddress = Word32Source
type PHANDLE = Ptr ()Source
type THANDLE = Ptr ()Source
type ThreadInfo = (THANDLE, ForeignAddress, ForeignAddress)Source
type ImageInfo = (HANDLE, ForeignAddress, DWORD, DWORD, ForeignAddress)Source
type ExceptionInfo = (Bool, Bool, ForeignAddress)Source
data Exception Source
Constructors
UnknownException
AccessViolation Bool ForeignAddress
ArrayBoundsExceeded
Breakpoint
DataTypeMisalignment
FltDenormalOperand
FltDivideByZero
FltInexactResult
FltInvalidOperation
FltOverflow
FltStackCheck
FltUnderflow
IllegalInstruction
InPageError
IntDivideByZero
IntOverflow
InvalidDisposition
NonContinuable
PrivilegedInstruction
SingleStep
StackOverflow
show/hide Instances
data DebugEventInfo Source
Constructors
UnknownDebugEvent
Exception ExceptionInfo Exception
CreateThread ThreadInfo
CreateProcess PHANDLE ImageInfo ThreadInfo
ExitThread TID
ExitProcess PID
LoadDll ImageInfo
UnloadDll TID
DebugString ForeignAddress Bool WORD
show/hide Instances
type DebugEvent = (DebugEventId, DebugEventInfo)Source
peekDebugEvent :: Ptr a -> IO DebugEventSource
waitForDebugEvent :: Maybe Int -> IO (Maybe DebugEvent)Source
getDebugEvents :: Int -> IO [DebugEvent]Source
continueDebugEvent :: DebugEventId -> Bool -> IO ()Source
debugActiveProcess :: PID -> IO ()Source
peekProcessMemory :: PHANDLE -> ForeignAddress -> Int -> Ptr a -> IO ()Source
readProcessMemory :: PHANDLE -> ForeignAddress -> Int -> IO (ForeignPtr a)Source
pokeProcessMemory :: PHANDLE -> ForeignAddress -> Int -> Ptr a -> IO ()Source
withProcessMemory :: PHANDLE -> ForeignAddress -> Int -> (Ptr a -> IO b) -> IO bSource
peekP :: Storable a => PHANDLE -> ForeignAddress -> IO aSource
pokeP :: Storable a => PHANDLE -> ForeignAddress -> a -> IO ()Source
suspendThread :: THANDLE -> IO DWORDSource
resumeThread :: THANDLE -> IO DWORDSource
withSuspendedThread :: THANDLE -> IO a -> IO aSource
getThreadContext :: THANDLE -> Ptr a -> IO ()Source
setThreadContext :: THANDLE -> Ptr a -> IO ()Source
useAllRegs :: Ptr a -> IO ()Source
withThreadContext :: THANDLE -> (Ptr a -> IO b) -> IO bSource
ebx :: IntSource
ecx :: IntSource
edx :: IntSource
eax :: IntSource
edi :: IntSource
esi :: IntSource
eip :: IntSource
esp :: IntSource
ebp :: IntSource
segDs :: IntSource
segEs :: IntSource
segFs :: IntSource
segGs :: IntSource
segCs :: IntSource
eFlags :: IntSource
dr :: Int -> IntSource
setReg :: Ptr a -> Int -> DWORD -> IO ()Source
getReg :: Ptr a -> Int -> IO DWORDSource
modReg :: Ptr a -> Int -> (DWORD -> DWORD) -> IO DWORDSource
makeModThreadContext :: [(Int, DWORD -> DWORD)] -> Ptr a -> IO [DWORD]Source
modifyThreadContext :: THANDLE -> [(Int, DWORD -> DWORD)] -> IO [DWORD]Source
outputDebugString :: String -> IO ()Source
c_SuspendThread :: THANDLE -> IO DWORDSource
c_ResumeThread :: THANDLE -> IO DWORDSource
c_WaitForDebugEvent :: Ptr () -> DWORD -> IO BOOLSource
c_ContinueDebugEvent :: DWORD -> DWORD -> DWORD -> IO BOOLSource
c_DebugActiveProcess :: DWORD -> IO BoolSource
c_ReadProcessMemory :: PHANDLE -> Ptr () -> Ptr Word8 -> DWORD -> Ptr DWORD -> IO BOOLSource
c_WriteProcessMemory :: PHANDLE -> Ptr () -> Ptr Word8 -> DWORD -> Ptr DWORD -> IO BOOLSource
c_GetThreadContext :: THANDLE -> Ptr () -> IO BOOLSource
c_SetThreadContext :: THANDLE -> Ptr () -> IO BOOLSource
c_OutputDebugString :: LPTSTR -> IO ()Source
isDebuggerPresent :: IO BOOLSource
debugBreak :: IO ()Source
Produced by Haddock version 2.4.2