Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations wOOdy-Soft on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

How to check Process Existence

Status
Not open for further replies.

varan123

Programmer
Feb 21, 2003
6
GB
Hi all,

I would like to design a program in VB5, whereby
it can detect or check whether particular process is currently active or not active, maybe by using parameters
such as the file name and the path.

For example,
If calculator program is executed from windows platform and if I enter the file name 'calc.exe' or the path directory 'c:\windows' in VB program, this eventually should indicate that the process is active!

Could anyone help me with this.....I would greatly appreciate this!!
 
look into the EnumProcess API call,
should get you started..

good luck If somethings hard to do, its not worth doing - Homer Simpson
 
sorry that should be EnumProcesses, alternatively check out thread222-69608! If somethings hard to do, its not worth doing - Homer Simpson
 
Hi again,
I used the EnumProcesses API but I have another problem where it indicate psapi.dll not found, even though
I copied this file to c:\windows\system.

Any help would be appreciated!

Cheers
Hamish
 
oooo....

>I copied this file to c:\windows\system

although you have copied the file to this directory(for whatever reason) it is still not registered there (unless you ran regsvr32)

the file should be in (dependant on OS) either

c:\winnt\system32 (for NT and 2000)
or
c:\windows\system32 (for 98)

im not sure what the path for XP is!

delete your copy out of system folder, and if the file isnt already in system32 paste it there (you will probably need to run "regsvr32 c:\winnt\system32\psapi.dll"

good luck If somethings hard to do, its not worth doing - Homer Simpson
 
Um...you don't need to (and, in fact, can't) register psapi.dll as it is a regular DLL rather than a COM DLL.

It should be pointed out that it only runs under NT4/2000/XP. It will not work under W9x/Me. You have to write your own EnumProcesses function for these latter OS's
 
ok, apologies i did not know that (the registering bit)!!
If somethings hard to do, its not worth doing - Homer Simpson
 
There is perhaps an alternative that you can use in Win9X/Me that may provide you the information you need. It is based on 4 API's, those being the following:
Code:
Private Declare Function CreateToolhelpSnapshot Lib "kernel32" Alias "CreateToolhelp32Snapshot" (ByVal lFlags As Long, ByVal lProcessId As Long) As Long

Private Declare Function ProcessFirst Lib "kernel32" Alias "Process32First" (ByVal hSnapShot As Long, uProcess As PROCESSENTRY32) As Long

Private Declare Function ProcessNext Lib "kernel32" Alias "Process32Next" (ByVal hSnapShot As Long, uProcess As PROCESSENTRY32) As Long

Private Declare Sub CloseHandle Lib "kernel32" (ByVal hPass As Long)
and you'll need the following type structure:
Code:
Private Type PROCESSENTRY32
   dwSize               As Long
   cntUsage             As Long
   th32ProcessID        As Long
   th32DefaultHeapID    As Long
   th32ModuleID         As Long
   cntThreads           As Long
   th32ParentProcessID  As Long
   pcPriClassBase       As Long
   dwFlags              As Long
   szExeFile            As String * 256
End Type
As Long Good Luck
--------------
As a circle of light increases so does the circumference of darkness around it. - Albert Einstein
 
hope im not breaking any copyrights here but:-

1 form and 1 module:

form named "EnumProcs" has 2 listboxes "lstProcesses","lstmodules" and 2 buttons "cmdRefresh""cmdExit"

----code-------
Dim rTop As Integer, rWidth As Integer, rHeight As Integer, rLeft As Integer
Dim i As Integer
Dim iStart As Integer, iWidth As Integer
Dim cMem As Currency

rTop = RectMem.Top
rLeft = RectMem.Left
rWidth = RectMem.Width
rHeight = RectMem.Height

cMem = 4294967296#

' Clear all
Me.Line (rLeft, rTop)-Step(rWidth, rHeight), &HC0C0C0, BF

' Redraw box
Me.Line (rLeft, rTop)-Step(rWidth, rHeight), &H0, B

For i = 1 To cModules

' Compute the starting location
iStart = Int((cModuleBase(i) / cMem) * rWidth)

' Compute Width
iWidth = Int((lModuleSize(i) / cMem) * rWidth)

If i Mod 2 = 0 Then
Me.Line (rLeft + iStart, rTop)-Step(iWidth, rHeight), &HFF0000, BF
Else
Me.Line (rLeft + iStart, rTop)-Step(iWidth, rHeight), &HFF, BF
End If

Next

' Do drivers
For i = 1 To cDrivers

' Compute the starting location
iStart = Int(((curDriverBase(i)) / cMem) * rWidth)

iWidth = 10

If i Mod 2 = 0 Then
Me.Line (rLeft + iStart, rTop)-Step(iWidth, rHeight), &HFF0000, BF
Else
Me.Line (rLeft + iStart, rTop)-Step(iWidth, rHeight), &HFF, BF
End If

Next

' Finish with line at 2GB
iStart = Int(rWidth / 2)
iWidth = 10
Me.Line (rLeft + iStart, rTop)-Step(iWidth, rHeight / 2), &H0, BF

End Sub


Sub FlashModuleWhite(idx As Integer)

Dim rTop As Integer, rWidth As Integer, rHeight As Integer, rLeft As Integer
Dim iStart As Integer, iWidth As Integer
Dim cMem As Currency
Dim i As Integer

rTop = RectMem.Top
rLeft = RectMem.Left
rWidth = RectMem.Width
rHeight = RectMem.Height

ShowMemoryMap

cMem = 4294967296#
' Compute the starting location
iStart = Int((cModuleBase(idx) / cMem) * rWidth)

' Compute width
iWidth = Int((lModuleSize(idx) / cMem) * rWidth)

Me.Line (rLeft + iStart, rTop)-Step(iWidth, rHeight), &HFFFFFF, BF

' Finish with line at 2GB
iStart = Int(rWidth / 2)
iWidth = 10
Me.Line (rLeft + iStart, rTop)-Step(iWidth, rHeight / 2), &H0, BF

End Sub
--------end code------------


module named "basEnumProcs"


------------code-----------

Option Explicit

' *****************************************
' NOTE: This runs only under Windows 95/98
' *****************************************

Public MemMapProcID As Long
Public MemMapProcess As String

Declare Sub CopyMemoryToLong Lib "kernel32" Alias "RtlMoveMemory" ( _
Destination As Long, _
ByVal Source As Long, _
ByVal Length As Long _
)

Public Const EM_SETTABSTOPS = &HCB

Public Const MAX_MODULE_NAME32 = 255
Public Const MAX_PATH = 260

Public Const TH32CS_SNAPHEAPLIST = &H1
Public Const TH32CS_SNAPPROCESS = &H2
Public Const TH32CS_SNAPTHREAD = &H4
Public Const TH32CS_SNAPMODULE = &H8
Public Const TH32CS_SNAPALL = (TH32CS_SNAPHEAPLIST Or TH32CS_SNAPPROCESS Or TH32CS_SNAPTHREAD Or TH32CS_SNAPMODULE)
Public Const TH32CS_INHERIT = &H80000000

'HANDLE WINAPI CreateToolhelp32Snapshot( DWORD dwFlags,
' DWORD th32ProcessID );

Public Declare Function CreateToolhelp32Snapshot Lib "kernel32" ( _
ByVal dwFlags As Long, _
ByVal th32ProcessID As Long _
) As Long

Public Declare Function Process32First Lib "kernel32" ( _
ByVal hSnapShot As Long, _
lppe As PROCESSENTRY32 _
) As Long

Public Declare Function Process32Next Lib "kernel32" ( _
ByVal hSnapShot As Long, _
lppe As PROCESSENTRY32 _
) As Long

Public Type PROCESSENTRY32
dwSize As Long
cntUsage As Long
th32ProcessID As Long ' process ID
th32DefaultHeapID As Long
th32ModuleID As Long ' only for Toolhelp functions
cntThreads As Long ' number of threads
th32ParentProcessID As Long ' process ID of parent
pcPriClassBase As Long
dwFlags As Long
szExeFile As String * MAX_PATH ' path/file of EXE file
End Type

Public Type MODULEENTRY32
dwSize As Long
th32ModuleID As Long
th32ProcessID As Long
GlblcntUsage As Long
ProccntUsage As Long
modBaseAddr As Long
modBaseSize As Long
hModule As Long
szModule As String * MAX_MODULE_NAME32
szExePath As String * MAX_PATH
End Type

Public Declare Function Module32First& Lib "kernel32" ( _
ByVal hSnapShot As Long, _
lpme As MODULEENTRY32 _
)
Public Declare Function Module32Next& Lib "kernel32" ( _
ByVal hSnapShot As Long, _
lpme As MODULEENTRY32 _
)
Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long

' ----------
' API errors
' ----------
Public Const FORMAT_MESSAGE_FROM_SYSTEM = &H1000
Public Const FORMAT_MESSAGE_IGNORE_INSERTS = &H200

Declare Function FormatMessage Lib "kernel32" Alias "FormatMessageA" ( _
ByVal dwFlags As Long, lpSource As Any, ByVal dwMessageId As Long, _
ByVal dwLanguageId As Long, ByVal lpBuffer As String, _
ByVal nSize As Long, ByVal Arguments As Long) As Long

' --------------
' Memory Mapping (OK for Win 95)
' --------------
Declare Function VirtualQuery Lib "kernel32" ( _
ByVal lpAddress As Long, _
lpBuffer As MEMORY_BASIC_INFORMATION, _
ByVal dwLength As Long _
) As Long

Declare Function VirtualQueryEx Lib "kernel32" ( _
ByVal hProcess As Long, _
ByVal lpAddress As Long, _
lpBuffer As MEMORY_BASIC_INFORMATION, _
ByVal dwLength As Long _
) As Long


Public Type MEMORY_BASIC_INFORMATION
BaseAddress As Long 'base address of region
AllocationBase As Long 'allocation base address
AllocationProtect As Long 'initial access protection
RegionSize As Long 'size, in bytes, of region
State As Long 'committed, reserved, free
Protect As Long 'current access protection
Type As Long 'type of pages
End Type

Public Const MEM_COMMIT = &H1000
Public Const MEM_RESERVE = &H2000
Public Const MEM_DECOMMIT = &H4000
Public Const MEM_RELEASE = &H8000
Public Const MEM_FREE = &H10000
Public Const MEM_PRIVATE = &H20000
Public Const MEM_MAPPED = &H40000
Public Const MEM_RESET = &H80000
Public Const MEM_TOP_DOWN = &H100000
Public Const MEM_IMAGE = &H1000000

Public Const PAGE_NOACCESS = &H1
Public Const PAGE_READONLY = &H2
Public Const PAGE_READWRITE = &H4
Public Const PAGE_WRITECOPY = &H8
Public Const PAGE_EXECUTE = &H10
Public Const PAGE_EXECUTE_READ = &H20
Public Const PAGE_EXECUTE_READWRITE = &H40
Public Const PAGE_EXECUTE_WRITECOPY = &H80
Public Const PAGE_GUARD = &H100
Public Const PAGE_NOCACHE = &H200

Public Const PROCESS_VM_READ = &H10
Public Const PROCESS_QUERY_INFORMATION = &H400

Declare Sub GlobalMemoryStatus Lib "kernel32" (lpBuffer As MEMORYSTATUS)

Public Type MEMORYSTATUS
dwLength As Long 'sizeof(MEMORYSTATUS)
dwMemoryLoad As Long 'percent of memory in use
dwTotalPhys As Long 'bytes of physical memory
dwAvailPhys As Long 'free physical memory bytes
dwTotalPageFile As Long 'bytes of paging file
dwAvailPageFile As Long 'free bytes of paging file
dwTotalVirtual As Long 'user bytes of address space
dwAvailVirtual As Long 'free user bytes
End Type

Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) As Long
Declare Function GetModuleHandle Lib "kernel32" Alias "GetModuleHandleA" (ByVal lpModuleName As String) As Long
Declare Function GetModuleFileName Lib "kernel32" Alias "GetModuleFileNameA" (ByVal hModule As Long, ByVal lpFileName As String, ByVal nSize As Long) As Long
Declare Function GetWindowThreadProcessId Lib "user32" (ByVal hwnd As Long, lpdwProcessId As Long) As Long

Declare Function OpenProcess Lib "kernel32" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal dwProcessId As Long) As Long


Public Function GetAPIErrorText(ByVal lError As Long) As String

Dim sOut As String
Dim sMsg As String
Dim lret As Long

GetAPIErrorText = ""
sMsg = String$(256, 0)

lret = FormatMessage(FORMAT_MESSAGE_FROM_SYSTEM Or _
FORMAT_MESSAGE_IGNORE_INSERTS, _
0&, lError, 0&, sMsg, Len(sMsg), 0&)

sOut = "Error: " & lError & "(&H" & Hex(lError) & "): "
If lret <> 0 Then
' Check for ending vbcrlf
sMsg = Trim0(sMsg)
If Right$(sMsg, 2) = vbCrLf Then sMsg = Left$(sMsg, Len(sMsg) - 2)
sOut = sOut & Trim0(sMsg)
Else
sOut = sOut & &quot;<No such error>&quot;
End If

GetAPIErrorText = sOut

End Function

Public Sub RaiseApiError(ByVal e As Long)
Err.Raise vbObjectError + 29000 + e, App.EXEName & &quot;.Windows&quot;, GetAPIErrorText(e)
End Sub

Public Function Trim0(sName As String) As String

' Keep left portion of string sName up to first 0. Useful with Win API null terminated strings.

Dim x As Integer
x = InStr(sName, Chr$(0))
If x > 0 Then Trim0 = Left$(sName, x - 1) Else Trim0 = sName

End Function
Sub Delay(rTime As Single)

'Delay rTime seconds (min=.01, max=300)

Dim OldTime As Variant

'Safty net
If rTime < 0.01 Or rTime > 300 Then rTime = 1

OldTime = Timer
Do
DoEvents
Loop Until Timer - OldTime >= rTime

End Sub

Public Function ProcHndFromProcID(ByVal lProcID As Long) As Long
ProcHndFromProcID = OpenProcess(PROCESS_QUERY_INFORMATION Or PROCESS_VM_READ, 0&, lProcID)
End Function

Function MemType(vValue As Variant) As String

' Function returns name of constant for given value.

Dim sName As String

Select Case vValue
Case &H1000
sName = &quot;COMMIT&quot;
Case &H2000
sName = &quot;RESERVE&quot;
Case &H4000
sName = &quot;DECOMMIT&quot;
Case &H8000
sName = &quot;RELEASE&quot;
Case &H10000
sName = &quot;FREE&quot;
Case &H20000
sName = &quot;PRIVATE&quot;
Case &H40000
sName = &quot;MAPPED&quot;
Case &H80000
sName = &quot;RESET&quot;
Case &H100000
sName = &quot;TOP_DOWN&quot;
Case &H1000000
sName = &quot;IMAGE&quot;
Case Else
sName = vValue
End Select

MemType = sName

End Function
Function AccessType(vValue As Variant) As String

' Function returns name of constant for given value.

Dim sName As String

Select Case vValue

Case &H1
sName = &quot;NOACCESS&quot;
Case &H2
sName = &quot;READONLY&quot;
Case &H4
sName = &quot;READWRITE&quot;
Case &H8
sName = &quot;WRITECOPY&quot;
Case &H10
sName = &quot;EXECUTE&quot;
Case &H20
sName = &quot;EXECUTE_READ&quot;
Case &H40
sName = &quot;EXECUTE_READWRITE&quot;
Case &H80
sName = &quot;EXECUTE_WRITECOPY&quot;
Case &H100
sName = &quot;GUARD&quot;
Case &H200
sName = &quot;NOCACHE&quot;
Case Else
sName = vValue

End Select

AccessType = sName

End Function

-----end code----------

from win32 API programming with Visual basic

good luck!! If somethings hard to do, its not worth doing - Homer Simpson
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top