{-# LINE 1 "libraries\\Win32\\System\\Win32\\Process.hsc" #-}
{-# LINE 2 "libraries\\Win32\\System\\Win32\\Process.hsc" #-}
{-# LANGUAGE Safe #-}
{-# LINE 6 "libraries\\Win32\\System\\Win32\\Process.hsc" #-}
module System.Win32.Process where
import Control.Exception ( bracket )
import Control.Monad ( liftM5 )
import Foreign ( Ptr, peekByteOff, allocaBytes, pokeByteOff
, plusPtr )
import Foreign.C.Types ( CUInt(..) )
import System.Win32.File ( closeHandle )
import System.Win32.DebugApi ( ForeignAddress )
import System.Win32.Types
#include "windows_cconv.h"
iNFINITE :: DWORD
iNFINITE = 4294967295
{-# LINE 39 "libraries\\Win32\\System\\Win32\\Process.hsc" #-}
foreign import WINDOWS_CCONV unsafe "windows.h Sleep"
sleep :: DWORD -> IO ()
type ProcessId = DWORD
type ProcessHandle = HANDLE
type ProcessAccessRights = DWORD
pROCESS_ALL_ACCESS :: ProcessAccessRights
pROCESS_ALL_ACCESS = 2097151
pROCESS_CREATE_PROCESS :: ProcessAccessRights
pROCESS_CREATE_PROCESS = 128
pROCESS_CREATE_THREAD :: ProcessAccessRights
pROCESS_CREATE_THREAD = 2
pROCESS_DUP_HANDLE :: ProcessAccessRights
pROCESS_DUP_HANDLE = 64
pROCESS_QUERY_INFORMATION :: ProcessAccessRights
pROCESS_QUERY_INFORMATION = 1024
pROCESS_SET_QUOTA :: ProcessAccessRights
pROCESS_SET_QUOTA = 256
pROCESS_SET_INFORMATION :: ProcessAccessRights
pROCESS_SET_INFORMATION = 512
pROCESS_TERMINATE :: ProcessAccessRights
pROCESS_TERMINATE = 1
pROCESS_VM_OPERATION :: ProcessAccessRights
pROCESS_VM_OPERATION = 8
pROCESS_VM_READ :: ProcessAccessRights
pROCESS_VM_READ = 16
pROCESS_VM_WRITE :: ProcessAccessRights
pROCESS_VM_WRITE = 32
{-# LINE 59 "libraries\\Win32\\System\\Win32\\Process.hsc" #-}
foreign import WINDOWS_CCONV unsafe "windows.h OpenProcess"
c_OpenProcess :: ProcessAccessRights -> BOOL -> ProcessId -> IO ProcessHandle
openProcess :: ProcessAccessRights -> BOOL -> ProcessId -> IO ProcessHandle
openProcess r inh i = failIfNull "OpenProcess" $ c_OpenProcess r inh i
foreign import WINDOWS_CCONV unsafe "windows.h GetProcessId"
c_GetProcessId :: ProcessHandle -> IO ProcessId
getProcessId :: ProcessHandle -> IO ProcessId
getProcessId h = failIfZero "GetProcessId" $ c_GetProcessId h
foreign import WINDOWS_CCONV unsafe "windows.h GetCurrentProcess"
c_GetCurrentProcess :: IO ProcessHandle
foreign import WINDOWS_CCONV unsafe "windows.h GetCurrentProcessId"
c_GetCurrentProcessId :: IO ProcessId
getCurrentProcessId :: IO ProcessId
getCurrentProcessId = c_GetCurrentProcessId
getCurrentProcess :: IO ProcessHandle
getCurrentProcess = c_GetCurrentProcess
foreign import WINDOWS_CCONV unsafe "windows.h TerminateProcess"
c_TerminateProcess :: ProcessHandle -> CUInt -> IO Bool
terminateProcessById :: ProcessId -> IO ()
terminateProcessById p = bracket
(openProcess pROCESS_TERMINATE False p)
closeHandle
(\h -> failIfFalse_ "TerminateProcess" $ c_TerminateProcess h 1)
type Th32SnapHandle = HANDLE
type Th32SnapFlags = DWORD
type ProcessEntry32 = (ProcessId, Int, ProcessId, LONG, String)
type ModuleEntry32 = (ForeignAddress, Int, HMODULE, String, String)
tH32CS_SNAPALL :: Th32SnapFlags
tH32CS_SNAPALL = 15
tH32CS_SNAPHEAPLIST :: Th32SnapFlags
tH32CS_SNAPHEAPLIST = 1
tH32CS_SNAPMODULE :: Th32SnapFlags
tH32CS_SNAPMODULE = 8
tH32CS_SNAPMODULE32 :: Th32SnapFlags
tH32CS_SNAPMODULE32 = 16
tH32CS_SNAPMODULE64 :: Th32SnapFlags
tH32CS_SNAPMODULE64 = 24
tH32CS_SNAPPROCESS :: Th32SnapFlags
tH32CS_SNAPPROCESS = 2
tH32CS_SNAPTHREAD :: Th32SnapFlags
tH32CS_SNAPTHREAD = 4
{-# LINE 108 "libraries\\Win32\\System\\Win32\\Process.hsc" #-}
foreign import WINDOWS_CCONV unsafe "tlhelp32.h CreateToolhelp32Snapshot"
c_CreateToolhelp32Snapshot :: Th32SnapFlags -> ProcessId -> IO Th32SnapHandle
foreign import WINDOWS_CCONV unsafe "tlhelp32.h Process32FirstW"
c_Process32First :: Th32SnapHandle -> Ptr ProcessEntry32 -> IO BOOL
foreign import WINDOWS_CCONV unsafe "tlhelp32.h Process32NextW"
c_Process32Next :: Th32SnapHandle -> Ptr ProcessEntry32 -> IO BOOL
foreign import WINDOWS_CCONV unsafe "tlhelp32.h Module32FirstW"
c_Module32First :: Th32SnapHandle -> Ptr ModuleEntry32 -> IO BOOL
foreign import WINDOWS_CCONV unsafe "tlhelp32.h Module32NextW"
c_Module32Next :: Th32SnapHandle -> Ptr ModuleEntry32 -> IO BOOL
createToolhelp32Snapshot :: Th32SnapFlags -> Maybe ProcessId -> IO Th32SnapHandle
createToolhelp32Snapshot f p
= failIfNull "CreateToolhelp32Snapshot" $ c_CreateToolhelp32Snapshot
f (maybe 0 id p)
withTh32Snap :: Th32SnapFlags -> Maybe ProcessId -> (Th32SnapHandle -> IO a) -> IO a
withTh32Snap f p = bracket (createToolhelp32Snapshot f p) (closeHandle)
peekProcessEntry32 :: Ptr ProcessEntry32 -> IO ProcessEntry32
peekProcessEntry32 buf = liftM5 (,,,,)
(((\hsc_ptr -> peekByteOff hsc_ptr 8)) buf)
{-# LINE 140 "libraries\\Win32\\System\\Win32\\Process.hsc" #-}
(((\hsc_ptr -> peekByteOff hsc_ptr 28)) buf)
{-# LINE 141 "libraries\\Win32\\System\\Win32\\Process.hsc" #-}
(((\hsc_ptr -> peekByteOff hsc_ptr 32)) buf)
{-# LINE 142 "libraries\\Win32\\System\\Win32\\Process.hsc" #-}
(((\hsc_ptr -> peekByteOff hsc_ptr 36)) buf)
{-# LINE 143 "libraries\\Win32\\System\\Win32\\Process.hsc" #-}
(peekTString $ ((\hsc_ptr -> hsc_ptr `plusPtr` 44)) buf)
{-# LINE 144 "libraries\\Win32\\System\\Win32\\Process.hsc" #-}
peekModuleEntry32 :: Ptr ModuleEntry32 -> IO ModuleEntry32
peekModuleEntry32 buf = liftM5 (,,,,)
(((\hsc_ptr -> peekByteOff hsc_ptr 24)) buf)
{-# LINE 148 "libraries\\Win32\\System\\Win32\\Process.hsc" #-}
(((\hsc_ptr -> peekByteOff hsc_ptr 32)) buf)
{-# LINE 149 "libraries\\Win32\\System\\Win32\\Process.hsc" #-}
(((\hsc_ptr -> peekByteOff hsc_ptr 40)) buf)
{-# LINE 150 "libraries\\Win32\\System\\Win32\\Process.hsc" #-}
(peekTString $ ((\hsc_ptr -> hsc_ptr `plusPtr` 48)) buf)
{-# LINE 151 "libraries\\Win32\\System\\Win32\\Process.hsc" #-}
(peekTString $ ((\hsc_ptr -> hsc_ptr `plusPtr` 560)) buf)
{-# LINE 152 "libraries\\Win32\\System\\Win32\\Process.hsc" #-}
th32SnapEnumProcesses :: Th32SnapHandle -> IO [ProcessEntry32]
th32SnapEnumProcesses h = allocaBytes ((568)) $ \pe -> do
{-# LINE 156 "libraries\\Win32\\System\\Win32\\Process.hsc" #-}
((\hsc_ptr -> pokeByteOff hsc_ptr 0)) pe (((568))::DWORD)
{-# LINE 157 "libraries\\Win32\\System\\Win32\\Process.hsc" #-}
ok <- c_Process32First h pe
readAndNext ok pe []
where
readAndNext ok pe res
| not ok = do
err <- getLastError
if err == (18)
{-# LINE 164 "libraries\\Win32\\System\\Win32\\Process.hsc" #-}
then return $ reverse res
else failWith "th32SnapEnumProcesses: Process32First/Process32Next" err
| otherwise = do
entry <- peekProcessEntry32 pe
ok' <- c_Process32Next h pe
readAndNext ok' pe (entry:res)
th32SnapEnumModules :: Th32SnapHandle -> IO [ModuleEntry32]
th32SnapEnumModules h = allocaBytes ((1080)) $ \pe -> do
{-# LINE 174 "libraries\\Win32\\System\\Win32\\Process.hsc" #-}
((\hsc_ptr -> pokeByteOff hsc_ptr 0)) pe (((1080))::DWORD)
{-# LINE 175 "libraries\\Win32\\System\\Win32\\Process.hsc" #-}
ok <- c_Module32First h pe
readAndNext ok pe []
where
readAndNext ok pe res
| not ok = do
err <- getLastError
if err == (18)
{-# LINE 182 "libraries\\Win32\\System\\Win32\\Process.hsc" #-}
then return $ reverse res
else failWith "th32SnapEnumModules: Module32First/Module32Next" err
| otherwise = do
entry <- peekModuleEntry32 pe
ok' <- c_Module32Next h pe
readAndNext ok' pe (entry:res)