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 | Safe |
Language | Haskell2010 |
A collection of FFI declarations for using Windows DebugApi.
Synopsis
- 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
- = UnknownException
- | AccessViolation Bool ForeignAddress
- | ArrayBoundsExceeded
- | Breakpoint
- | DataTypeMisalignment
- | FltDenormalOperand
- | FltDivideByZero
- | FltInexactResult
- | FltInvalidOperation
- | FltOverflow
- | FltStackCheck
- | FltUnderflow
- | IllegalInstruction
- | InPageError
- | IntDivideByZero
- | IntOverflow
- | InvalidDisposition
- | NonContinuable
- | PrivilegedInstruction
- | SingleStep
- | StackOverflow
- data DebugEventInfo
- type DebugEvent = (DebugEventId, DebugEventInfo)
- debugBreak :: IO ()
- isDebuggerPresent :: IO BOOL
- 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
- rax :: Int
- rbx :: Int
- rcx :: Int
- rdx :: Int
- rsi :: Int
- rdi :: Int
- rbp :: Int
- rip :: Int
- rsp :: 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 ()
Documentation
type DebugEventId = (PID, TID) Source #
type ForeignAddress = Word32 Source #
type ThreadInfo = (THANDLE, ForeignAddress, ForeignAddress) Source #
type ImageInfo = (HANDLE, ForeignAddress, DWORD, DWORD, ForeignAddress) Source #
type ExceptionInfo = (Bool, Bool, ForeignAddress) Source #
data DebugEventInfo Source #
Instances
Show DebugEventInfo Source # | |
Defined in System.Win32.DebugApi |
type DebugEvent = (DebugEventId, DebugEventInfo) Source #
debugBreak :: IO () Source #
Debug events
waitForDebugEvent :: Maybe Int -> IO (Maybe DebugEvent) Source #
getDebugEvents :: Int -> IO [DebugEvent] Source #
continueDebugEvent :: DebugEventId -> Bool -> IO () Source #
Debugging another process
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 b Source #
Thread control
Thread register control
useAllRegs :: Ptr a -> IO () Source #
Sending debug output to another process
outputDebugString :: String -> IO () Source #