Page 2 of 2

Posted: Thu Oct 30, 2003 10:52 am
by Rings
dmoc wrote:Yep, only one.

Re "old" os: give me ONE good reason to upgrade and I'll give several against. How's it feel to be one of Billy Boy's slobbering masses? :lol:
stable while coding

Posted: Sat Nov 01, 2003 11:47 am
by gnozal
Rings wrote:
dmoc wrote:Yep, only one.

Re "old" os: give me ONE good reason to upgrade and I'll give several against. How's it feel to be one of Billy Boy's slobbering masses? :lol:
stable while coding
My Win98SE is as stable as my WinNT4 : almost never a BSOD ! Despite what most people says, I find Win98SE a quite stable OS, whatever I do (programming, gaming, watching movies, else ...).

Posted: Sun Nov 02, 2003 2:02 pm
by geoff
Rings wrote:who cares on the old OS's .
another reason to drop all those Win89 into trashcan !
And when Longhorn comes out, we can dump all your new code in the trashcan and then when the next OS ....

What's the point of starting afresh every 2 years?

You could have applications that work on all versions of Windows, Win3 to XP.
Isn't that a more worthwhile objective?

But...

Posted: Sun Nov 02, 2003 5:45 pm
by Hi-Toro
You could have applications that work on all versions of Windows, Win3 to XP.
Isn't that a more worthwhile objective?
Easier said than done, though, due to subtleties between the OSes (eg. functions returning information in slightly different formats, being non-existent on earlier OSes, Registry item locations differing) and as we can see from this thread, some things that Microsoft tell you will work on Windows 95 and 98, well, don't...

Posted: Sun Nov 30, 2003 1:21 am
by Hi-Toro
UPDATED: Fixed the first 2 posts so that it works on Windows 9x!

It seems that for some reason, Proc32Next () fails when called from inside a function. Weird thing is, it does this when called from Blitz too! Must be an obscure Windows bug...?

Posted: Sun Nov 30, 2003 3:52 pm
by Henrik
Great James and thanks for your effort on the win98 subject :D
Works fine under win 98se now :)

Best Regards
Henrik.

Posted: Sun Nov 30, 2003 7:21 pm
by Hi-Toro
Code updated for 5.20+

Here's a (fairly useless) little program that tries to list only open, visible windows, listed on the taskbar (it's not quite perfect as you sometimes get a window that's not on the taskbar), and lets you send a request to close that window. Might be handy for 'safe' closing of other programs from within your own.

It also shows how to retrieve a window's process name, which you can't get any other way, AFAIK.

Code: Select all

; -----------------------------------------------------------------------------
; Constants required by process functions, etc...
; -----------------------------------------------------------------------------

#TH32CS_SNAPHEAPLIST = $1
#TH32CS_SNAPPROCESS = $2
#TH32CS_SNAPTHREAD = $4
#TH32CS_SNAPMODULE = $8
#TH32CS_SNAPALL = #TH32CS_SNAPHEAPLIST | #TH32CS_SNAPPROCESS | #TH32CS_SNAPTHREAD | #TH32CS_SNAPMODULE
#TH32CS_INHERIT = $80000000
#INVALID_HANDLE_VALUE = -1
#MAX_PATH = 260
#PROCESS32LIB = 9999

Structure TaskbarWindow
    handle.i
EndStructure

Global NewList TaskbarList.TaskbarWindow ()


Procedure ListTaskbarWindows (window, parameter)
  Protected *memoryBuffer
  
    If GetParent_ (window) = #Null
    
        If GetWindowLong_ (window, #GWL_STYLE) & #WS_VISIBLE
          
            *memoryBuffer = ReAllocateMemory (*memoryBuffer, 255)
            GetClassName_ (window, *memoryBuffer, 255)
            class$ = PeekS (*memoryBuffer)

            ; Ignore Explorer classes...
                        
            Select LCase (class$)
                Case "explorewclass"
                    ignore = #True
                Case "workerw"
                    ignore = #True
                Case "progman"
                    ignore = #True
                Case "shell_traywnd"
                    ignore = #True
            EndSelect

            If ignore = #False
                AddElement (TaskbarList ())
                TaskbarList ()\handle = window
            EndIf

            FreeMemory (*memoryBuffer)
                        
        EndIf
        
    EndIf

    ProcedureReturn #True
    
EndProcedure

Procedure WinHook (WindowID, Message, wParam, lParam)
    If Message = #WM_SIZE
        ResizeGadget (0, 0, 0, WindowWidth (0), WindowHeight (0) - 25)
        ResizeGadget (1, 0, WindowHeight (0) - 24, WindowWidth (0), 25)
        RedrawWindow_ (GadgetID (0), #Null, #Null, #RDW_INVALIDATE)
    EndIf
    ProcedureReturn #PB_ProcessPureBasicEvents
EndProcedure

NewList Process32.PROCESSENTRY32 ()
Define *memoryBuffer

; Add processes to Process32 () list...

If OpenLibrary (#PROCESS32LIB, "kernel32.dll")

    snap = CallFunction (#PROCESS32LIB, "CreateToolhelp32Snapshot", #TH32CS_SNAPPROCESS, 0)

    If snap

        Define.PROCESSENTRY32 Proc32
        Proc32\dwSize = SizeOf (PROCESSENTRY32)
        
        If CallFunction (#PROCESS32LIB, "Process32First", snap, @Proc32)

            AddElement (Process32 ())
            CopyMemory (@Proc32, @Process32 (), SizeOf (PROCESSENTRY32))
            
            While CallFunction (#PROCESS32LIB, "Process32Next", snap, @Proc32)
                AddElement (Process32 ())
                CopyMemory (@Proc32, @Process32 (), SizeOf (PROCESSENTRY32))
            Wend
            
        EndIf    
        CloseHandle_ (snap)
    
    EndIf

    CloseLibrary (#PROCESS32LIB)
    
EndIf

OpenWindow (0, 0, 0, 400, 300, "Processes", #PB_Window_SystemMenu | #PB_Window_MinimizeGadget | #PB_Window_MaximizeGadget | #PB_Window_SizeGadget | #PB_Window_ScreenCentered)

lv = ListViewGadget (0, 0, 0, WindowWidth (0), WindowHeight (0) - 25)
ButtonGadget (1, 0, WindowHeight (0) - 24, WindowWidth (0), 25, "Close program...")
ClearList (TaskbarList ())
EnumWindows_ (@ListTaskbarWindows (), 0)

SetWindowCallback (@WinHook ())

ResetList (TaskbarList ())
While NextElement (TaskbarList ())
    *memoryBuffer = AllocateMemory (255)
    GetWindowText_ (TaskbarList ()\handle, *memoryBuffer, 255)
    title$ = PeekS (*memoryBuffer)
    ResetList (Process32 ())
    While NextElement (Process32 ())
        GetWindowThreadProcessId_ (TaskbarList ()\handle, @pid)
        If pid = Process32 ()\th32ProcessID
            exe$ = GetFilePart (PeekS (@Process32 ()\szExeFile))
            LastElement (Process32 ())
        EndIf
    Wend
    AddGadgetItem (0, -1, title$ + " [Process " + Str (pid) + ": " + exe$ + "]")
Wend

SetGadgetState (0, 0)

SetTimer_ (WindowID (0), 0, 1000, 0)

Repeat

    Select WaitWindowEvent ()
    
        Case #WM_TIMER
            selected = GetGadgetState (0)
            ClearGadgetItems (0)
            ClearList (TaskbarList ())
            EnumWindows_ (@ListTaskbarWindows (), 0)
            ResetList (TaskbarList ()) 
            While NextElement (TaskbarList ())
                *memoryBuffer = AllocateMemory (255)
                GetWindowText_ (TaskbarList ()\handle, *memoryBuffer, 255)
                title$ = PeekS (*memoryBuffer)
                ResetList (Process32 ())
                While NextElement (Process32 ())
                    GetWindowThreadProcessId_ (TaskbarList ()\handle, @pid)
                    If pid = Process32 ()\th32ProcessID
                        exe$ = GetFilePart (PeekS (@Process32 ()\szExeFile))
                    EndIf
                Wend
                AddGadgetItem (0, -1, title$ + " [Process " + Str (pid) + ": " + exe$ + "]")
            Wend
            If SetGadgetState (0, selected) = -1
                SetGadgetState (0, 0)
            EndIf

        Case #PB_Event_CloseWindow
            End
            
        Case #PB_Event_Gadget
            Select EventGadget ()
                Case 1
                    ClearList (TaskbarList ())
                    EnumWindows_ (@ListTaskbarWindows (), 0)
                    ResetList (TaskbarList ())
                    While NextElement (TaskbarList ())
                        *memoryBuffer = AllocateMemory (255)
                        GetWindowText_ (TaskbarList ()\handle, *memoryBuffer, 255)
                        title$ = PeekS (*memoryBuffer)
                        ; SORT THIS!
                        item$ = GetGadgetItemText (0, GetGadgetState (0), 0)
                        found = FindString (item$, " [Process ", 1)
                        If found > 1
                            found = found - 1
                            If title$ = Left (item$, found)
                                If MessageRequester ("Processes...", "Close window: " + title$ +" ?", #PB_MessageRequester_YesNo) = #IDYES
                                    PostMessage_ (TaskbarList ()\handle, #WM_CLOSE, 0, 0)
                                    LastElement (TaskbarList ())
                                EndIf
                            EndIf
                        EndIf
                    Wend
            EndSelect
            
    EndSelect
    
ForEver
... and if a program refuses to close like that, you could instead 'force' it closed via this, passing the 'pid' variable from the above code:

Code: Select all

#PROCESS_TERMINATE = $1
#PROCESS_CREATE_THREAD = $2
#PROCESS_VM_OPERATION = $8
#PROCESS_VM_READ = $10
#PROCESS_VM_WRITE = $20
#PROCESS_DUP_HANDLE = $40
#PROCESS_CREATE_PROCESS = $80
#PROCESS_SET_QUOTA = $100
#PROCESS_SET_INFORMATION = $200
#PROCESS_QUERY_INFORMATION = $400
#PROCESS_ALL_ACCESS = #STANDARD_RIGHTS_REQUIRED | #SYNCHRONIZE | $FFF

; This appears to be pretty much how Windows kills a program if you 'End Process'
; from the Task Manager. Note that this is 'unfriendly'!

Procedure KillProcess (pid)
    phandle = OpenProcess_ (#PROCESS_TERMINATE, #FALSE, pid)
    If phandle <> #NULL
        If TerminateProcess_ (phandle, 1)
            result = #TRUE
        EndIf
        CloseHandle_ (phandle)
    EndIf
    ProcedureReturn result
EndProcedure

; Enter process ID here! I suggest going to Task Manager,
; making sure PIDs are shown (try View menu -> Select columns if
; they are not listed), then run a program and enter its number here...

Debug KillProcess ( x )

Re: ... and even if no-one cares, there's more!

Posted: Thu Jan 12, 2006 2:06 am
by SFSxOI
When I run this I keep getting an error that the structure or interface PROCESSENTRY32 is already declared.
Hi-Toro wrote:

Code: Select all


; -----------------------------------------------------------------------------
; Constants required by process functions, etc...
; -----------------------------------------------------------------------------

#TH32CS_SNAPHEAPLIST = $1
#TH32CS_SNAPPROCESS = $2
#TH32CS_SNAPTHREAD = $4
#TH32CS_SNAPMODULE = $8
#TH32CS_SNAPALL = #TH32CS_SNAPHEAPLIST | #TH32CS_SNAPPROCESS | #TH32CS_SNAPTHREAD | #TH32CS_SNAPMODULE
#TH32CS_INHERIT = $80000000
#INVALID_HANDLE_VALUE = -1
#MAX_PATH = 260
#PROCESS32LIB = 9999

Structure PROCESSENTRY32
    dwSize.l
    cntUsage.l
    th32ProcessID.l
    *th32DefaultHeapID.l
    th32ModuleID.l
    cntThreads.l
    th32ParentProcessID.l
    pcPriClassBase.l
    dwFlags.l
    szExeFile.b [#MAX_PATH]
EndStructure

; -----------------------------------------------------------------------------
; GLOBAL PROCESS LIST! Used to retrieve information after getting process list...
; -----------------------------------------------------------------------------

NewList Process32.PROCESSENTRY32 ()

; This function sorts processes into TreeGadget list, so that child processes branch off from parents...

Procedure CompareProcs (gadget, currentid, currentname$)

    Debug "Comparing " + currentname$ + " [" + Str (currentid) + "]"
    
    ResetList (Process32 ())
    
    While NextElement (Process32 ())

        ; Skip if checking against 'currentid', ie. same process...
                
        If Process32 ()\th32ProcessID <> currentid
            
            ; Check currentid against this one...
            
            againstid = Process32 ()\th32ProcessID
            againstparent = Process32 ()\th32ParentProcessID
        
            ; If 'currentid' is parent of this process...
            
            If currentid = againstparent
            
                OpenTreeGadgetNode (gadget)

                    proc$ = PeekS (@Process32 ()\szExeFile)
                    Debug "--------> " + proc$ + " [" + Str (Process32 ()\th32ProcessID) + "]" + " / " + " [" + Str (Process32 ()\th32ParentProcessID) + "]"
                    
                    AddGadgetItem (gadget, -1, PeekS (@Process32 ()\szExeFile))
                    
                    current = ListIndex (Process32 ())
                    CompareProcs (gadget, againstid, proc$)
                    SelectElement (Process32 (), current)
                    DeleteElement (Process32 ())

                CloseTreeGadgetNode (gadget)
                
            EndIf
            
        EndIf
        
    Wend
    
EndProcedure

; Add processes to Process32 () list...

If OpenLibrary (#PROCESS32LIB, "kernel32.dll")

    snap = CallFunction (#PROCESS32LIB, "CreateToolhelp32Snapshot", #TH32CS_SNAPPROCESS, 0)

    If snap

        DefType.PROCESSENTRY32 Proc32
        Proc32\dwSize = SizeOf (PROCESSENTRY32)
        
        If CallFunction (#PROCESS32LIB, "Process32First", snap, @Proc32)

            AddElement (Process32 ())
            CopyMemory (@Proc32, @Process32 (), SizeOf (PROCESSENTRY32))
            
            While CallFunction (#PROCESS32LIB, "Process32Next", snap, @Proc32)
                AddElement (Process32 ())
                CopyMemory (@Proc32, @Process32 (), SizeOf (PROCESSENTRY32))
            Wend
            
        EndIf    
        CloseHandle_ (snap)
    
    EndIf

    CloseLibrary (#PROCESS32LIB)
    
EndIf

; Window hook, used to resize/redraw TreeGadget when window is resized...

Procedure WinHook (WindowID, Message, wParam, lParam)
    If Message = #WM_PAINT
        ResizeGadget (0, 0, 0, WindowWidth (), WindowHeight ())
        RedrawWindow_ (GadgetID (0), #NULL, #NULL, #RDW_INVALIDATE)
    EndIf
    ProcedureReturn #PB_ProcessPureBasicEvents
EndProcedure

; GUI...

OpenWindow (0, 320, 200, 320, 400, #PB_Window_SystemMenu | #PB_Window_SizeGadget | #PB_Window_MinimizeGadget | #PB_Window_MaximizeGadget, "Process list...")
CreateGadgetList (WindowID ())
TreeGadget (0, 0, 0, WindowWidth (), WindowHeight ())

SetWindowCallback (@WinHook ())

OpenTreeGadgetNode (0)

; Add processes to TreeGadget...

ResetList (Process32 ())

While NextElement (Process32 ())
    AddGadgetItem (0, -1, PeekS (@Process32 ()\szExeFile))
    current = ListIndex (Process32 ())
    CompareProcs (0, Process32 ()\th32ProcessID, PeekS (@Process32 ()\szExeFile))
    SelectElement (Process32 (), current)
Wend

Repeat

Until WaitWindowEvent () = #PB_Event_CloseWindow
End


Posted: Thu Jan 12, 2006 2:58 am
by Dare2
Hi SFSxOI.

As PureBasic evolves, things become part of the language. In cases like this, just change the structure name. I generally put zz_ in front, eg

Code: Select all

Structure zz_PROCESSENTRY32
If it then works, good.

If it doesn't, I rename all PROCESSENTRY32 (or whatever) references to zz_PROCESSENTRY32 (or whatever).

Most things work one way or the other. :)

Posted: Fri Jan 13, 2006 2:47 am
by Hi-Toro
Interestingly, I found mention of a minor bug in this code--the "If snap" line, in the section marked "add processes to Process32 () list", needs to be corrected to:

Code: Select all

If snap <> #INVALID_HANDLE_VALUE
... as described here:

http://msdn.microsoft.com/msdnmag/issue ... fault.aspx

(#INVALID_HANDLE_VALUE is -1, not zero.)

CheckRunningExe

Posted: Sun Jul 09, 2006 8:03 am
by oryaaaaa
This is inspired code

Code: Select all

Procedure.b CheckRunningExe(FileName.s)
  Protected snap.l , Proc32.PROCESSENTRY32 , dll_kernel32.l
  FileName = GetFilePart( FileName )
  dll_kernel32 = OpenLibrary (#PB_Any, "kernel32.dll")
  If dll_kernel32
    snap = CallFunction (dll_kernel32, "CreateToolhelp32Snapshot",$2, 0)
    If snap
      Proc32\dwSize = SizeOf (PROCESSENTRY32)
      If CallFunction (dll_kernel32, "Process32First", snap, @Proc32) 
        While CallFunction (dll_kernel32, "Process32Next", snap, @Proc32)
          If PeekS (@Proc32\szExeFile)=FileName
            CloseHandle_ (snap)
            CloseLibrary (dll_kernel32)
            ProcedureReturn #True
          EndIf
        Wend
      EndIf   
      CloseHandle_ (snap)
    EndIf
    CloseLibrary (dll_kernel32)
  EndIf
  ProcedureReturn #False
EndProcedure

Debug CheckRunningExe("firefox.exe")

Posted: Sun Jul 09, 2006 2:08 pm
by Rescator
oryaaaaa here is a more complete one, based on the example in the PSDK.

This one also works with unicode enabled as well, with unicode your code fail to work here.

Note! There are some PB unicode bugs, please see comment in code,
and this thread for more: http://www.purebasic.fr/english/viewtopic.php?t=22619

Code: Select all

;BOOL GetProcessList( );
;BOOL ListProcessModules( DWORD dwPID );
;BOOL ListProcessThreads( DWORD dwOwnerPID );
;void printError( TCHAR* msg );

Procedure printError(msg.s)
Protected eNum.l,sysMsg.s{256},p.s

 eNum=GetLastError_()
 FormatMessage_(#FORMAT_MESSAGE_FROM_SYSTEM|#FORMAT_MESSAGE_IGNORE_INSERTS,#Null,eNum,0,@sysMsg,256,#Null)
 Print(#CRLF$+"  WARNING: "+msg+" failed with error "+StrU(eNum,#Long)+" ("+sysMsg+")")
EndProcedure

Procedure.l ListProcessModules(dwPID.l)
 Protected hModuleSnap.l,me32.MODULEENTRY32

  hModuleSnap=#INVALID_HANDLE_VALUE;

  ;Take a snapshot of all modules in the specified process.
  hModuleSnap=CreateToolhelp32Snapshot_(#TH32CS_SNAPMODULE,dwPID)

  If hModuleSnap=#INVALID_HANDLE_VALUE
   printError("CreateToolhelp32Snapshot (of modules)")
   ProcedureReturn #False
  EndIf

  ;Set the size of the structure before using it.
  me32\dwSize=SizeOf(MODULEENTRY32)

  ;Retrieve information about the first module,
  ;and exit if unsuccessful
  If Module32First_(hModuleSnap,me32)=#False
   printError("Module32First") ;Show cause of failure
   CloseHandle_(hModuleSnap)   ;Must clean up the snapshot object!
   ProcedureReturn #False
  EndIf

  ;Now walk the module list of the process,
  ;and display information about each module
  Repeat
    Print(#CRLF$+#CRLF$+"     MODULE NAME:     "+PeekS(@me32\szModule,#MAX_MODULE_NAME32,#PB_Ascii))
    Print(#CRLF$+"     executable     = "+PeekS((@me32\szModule+#MAX_MODULE_NAME32)+1,#MAX_PATH,#PB_Ascii))
;The two above is a "hack", proper way is below, wait for PB4 fix so they work.
;    Print(#CRLF$+#CRLF$+"     MODULE NAME:     "+PeekS(@me32\szModule,#MAX_MODULE_NAME32))
;    Print(#CRLF$+"     executable     = "+PeekS(@me32\szExePath,#MAX_PATH))

    Print(#CRLF$+"     process ID     = $"+LSet(Hex(me32\th32ProcessID),8,"0"))
    Print(#CRLF$+"     ref count (g)  = $"+LSet(Hex(me32\GlblcntUsage),4,"0"))
    Print(#CRLF$+"     ref count (p)  = $"+LSet(Hex(me32\ProccntUsage),4,"0"))
    Print(#CRLF$+"     base address   = $"+LSet(Hex(me32\modBaseAddr),8,"0"))
    Print(#CRLF$+"     base size      = "+StrU(me32\modBaseSize,#Long))
  Until Module32Next_(hModuleSnap,me32)=#False

  CloseHandle_(hModuleSnap)
   ProcedureReturn #True
EndProcedure

Procedure.l ListProcessThreads(dwOwnerPID.l) 
Protected hThreadSnap.l,te32.THREADENTRY32
 hThreadSnap=#INVALID_HANDLE_VALUE

 ;Take a snapshot of all running threads  
 hThreadSnap=CreateToolhelp32Snapshot_(#TH32CS_SNAPTHREAD,0)
 If hThreadSnap=#INVALID_HANDLE_VALUE
  ProcedureReturn #False
 EndIf

 ;Fill in the size of the structure before using it. 
 te32\dwSize=SizeOf(THREADENTRY32)

 ;Retrieve information about the first thread,
 ;and exit if unsuccessful
 If Thread32First_(hThreadSnap,te32)=#False 
  printError("Thread32First" ) ;Show cause of failure
  CloseHandle_(hThreadSnap)     ;Must clean up the snapshot object!
  ProcedureReturn #False
 EndIf

 ;Now walk the thread list of the system,
 ;and display information about each thread
 ;associated with the specified process

 Repeat
  If te32\th32OwnerProcessID=dwOwnerPID
   Print(#CRLF$+#CRLF$+"     THREAD ID      = $"+LSet(Hex(te32\th32ThreadID),8,"0"))
   Print(#CRLF$+"     base priority  = "+StrU(te32\tpBasePri,#Long))
   Print(#CRLF$+"     delta priority = "+StrU(te32\tpDeltaPri,#Long))
  EndIf
 Until Thread32Next_(hThreadSnap,te32)=#False

 CloseHandle_(hThreadSnap)
 ProcedureReturn #True
EndProcedure

Procedure.l GetProcessList()
Protected hProcessSnap.l,hProcess.l,wPriorityClass.l,pe32.PROCESSENTRY32

 ;Take a snapshot of all processes in the system.
 hProcessSnap=CreateToolhelp32Snapshot_(#TH32CS_SNAPPROCESS,0)
 If(hProcessSnap=#INVALID_HANDLE_VALUE)
  printError("CreateToolhelp32Snapshot (of processes)")
  ProcedureReturn #False
 EndIf

 ;Set the size of the Structure before using it.
 pe32\dwSize=SizeOf(PROCESSENTRY32)

 ;Retrieve information about the first process,
 ;And exit if unsuccessful
 If Process32First_(hProcessSnap,pe32)=#False
  printError("Process32First") ;Show cause of failure
  CloseHandle_(hProcessSnap)    ;Must clean up the snapshot object!
  ProcedureReturn #False
 EndIf

 ;Now walk the snapshot of processes, and
 ;display information about each process in turn

 Repeat
  Print(#CRLF$+#CRLF$+"=====================================================")
  Print(#CRLF$+"PROCESS NAME:  "+PeekS(@pe32\szExeFile,260,#PB_Ascii)) ;#PB_Ascii should not be necessary, but there is a PB bug.
  Print(#CRLF$+"-----------------------------------------------------" )

  ;Retrieve the priority class.
  dwPriorityClass=0
  hProcess=OpenProcess_(#PROCESS_ALL_ACCESS,#False,pe32\th32ProcessID)
  If hProcess=#Null
   printError("OpenProcess")
  Else
   dwPriorityClass=GetPriorityClass_(hProcess)
   If dwPriorityClass=#False
    printError("GetPriorityClass")
   EndIf
   CloseHandle_(hProcess)
  EndIf

  Print(#CRLF$+"  process ID        = $"+LSet(Hex(pe32\th32ProcessID),8,"0"))
  Print(#CRLF$+"  thread count      = "+StrU(pe32\cntThreads,#Long))
  Print(#CRLF$+"  parent process ID = $"+LSet(Hex(pe32\th32ParentProcessID),8,"0"))
  Print(#CRLF$+"  Priority Base     = "+StrU(pe32\pcPriClassBase,#Long))
  If dwPriorityClass
   Print(#CRLF$+"  Priority Class    = "+StrU(dwPriorityClass,#Long))
  EndIf

  ;List the modules and threads associated with this process
  ListProcessModules(pe32\th32ProcessID)
  ListProcessThreads(pe32\th32ProcessID)
 Until Process32Next_(hProcessSnap,pe32)=#False

 CloseHandle_(hProcessSnap)
 ProcedureReturn #True
EndProcedure

OpenConsole()
GetProcessList()
CloseConsole()

Posted: Mon Jul 10, 2006 11:20 am
by b1be

Code: Select all

#TH32CS_SNAPHEAPLIST = $1
#TH32CS_SNAPPROCESS = $2
#TH32CS_SNAPTHREAD = $4
#TH32CS_SNAPMODULE = $8
#TH32CS_SNAPALL = #TH32CS_SNAPHEAPLIST | #TH32CS_SNAPPROCESS | #TH32CS_SNAPTHREAD | #TH32CS_SNAPMODULE
#TH32CS_INHERIT = $80000000
#INVALID_HANDLE_VALUE = -1
#MAX_PATH = 260
#PROCESS32LIB = 9999
#PSAPI = 9998

Procedure.s ExePath(); - Return the path and name of the running execute
  Prg.s = Space(#MAX_PATH+1)
  GetModuleFileName_(GetModuleHandle_(0), @Prg, #MAX_PATH)
  ProcedureReturn Prg
EndProcedure

OpenConsole()
FileName.s=GetFilePart(ExePath())
If OpenLibrary (#PROCESS32LIB, "kernel32.dll")
  snap = CallFunction (#PROCESS32LIB, "CreateToolhelp32Snapshot", #TH32CS_SNAPPROCESS, 0)
  If snap
    Define.PROCESSENTRY32 Proc32
    Proc32\dwSize = SizeOf (PROCESSENTRY32)
    If CallFunction (#PROCESS32LIB, "Process32First", snap, @Proc32)
      PrintN(LSet(PeekS (@Proc32\szExeFile),30)+"["+RSet(Str(Proc32\th32ProcessID),4)+"]")
      While CallFunction (#PROCESS32LIB, "Process32Next", snap, @Proc32)
        If PeekS (@Proc32\szExeFile)<>FileName.s
          PrintN(LSet(PeekS (@Proc32\szExeFile),30)+"["+RSet(Str(Proc32\th32ProcessID),4)+"]")
        EndIf
      Wend      
    EndIf   
    CloseHandle_ (snap)
  EndIf
  CloseLibrary (#PROCESS32LIB)
EndIf
CloseConsole()
LSMOD.exe
compile with console exe.. similar to lsmod in Linux

Code: Select all

#TH32CS_SNAPHEAPLIST = $1
#TH32CS_SNAPPROCESS = $2
#TH32CS_SNAPTHREAD = $4
#TH32CS_SNAPMODULE = $8
#TH32CS_SNAPALL = #TH32CS_SNAPHEAPLIST | #TH32CS_SNAPPROCESS | #TH32CS_SNAPTHREAD | #TH32CS_SNAPMODULE
#TH32CS_INHERIT = $80000000
#INVALID_HANDLE_VALUE = -1
#MAX_PATH = 260
#PROCESS32LIB = 9999
#PSAPI = 9998

Procedure.s NamePid(pid.l)
  Result.s=""
  If OpenLibrary (#PROCESS32LIB, "kernel32.dll")
    snap = CallFunction (#PROCESS32LIB, "CreateToolhelp32Snapshot", #TH32CS_SNAPPROCESS, 0)
    If snap
      Define.PROCESSENTRY32 Proc32
      Proc32\dwSize = SizeOf (PROCESSENTRY32)
      If CallFunction (#PROCESS32LIB, "Process32First", snap, @Proc32)
        If Proc32\th32ProcessID=pid:Result=PeekS (@Proc32\szExeFile):EndIf  
        While CallFunction (#PROCESS32LIB, "Process32Next", snap, @Proc32)
          If Proc32\th32ProcessID=pid:Result=PeekS (@Proc32\szExeFile):EndIf  
        Wend      
      EndIf   
      CloseHandle_ (snap)
    EndIf
    CloseLibrary (#PROCESS32LIB)
  EndIf
  ProcedureReturn Result
EndProcedure

Procedure.l PidName(Name.s)
  Result.l=0
  If OpenLibrary (#PROCESS32LIB, "kernel32.dll")
    snap = CallFunction (#PROCESS32LIB, "CreateToolhelp32Snapshot", #TH32CS_SNAPPROCESS, 0)
    If snap
      Define.PROCESSENTRY32 Proc32
      Proc32\dwSize = SizeOf (PROCESSENTRY32)
      If CallFunction (#PROCESS32LIB, "Process32First", snap, @Proc32)
        If UCase(PeekS (@Proc32\szExeFile))=UCase(Name):Result=Proc32\th32ProcessID:EndIf
        While CallFunction (#PROCESS32LIB, "Process32Next", snap, @Proc32)
          If UCase(PeekS (@Proc32\szExeFile))=UCase(Name):Result=Proc32\th32ProcessID:EndIf
        Wend      
      EndIf   
      CloseHandle_ (snap)
    EndIf
    CloseLibrary (#PROCESS32LIB)
  EndIf
  ProcedureReturn Result
EndProcedure

Procedure KillProcess2(pid.l)
  Result=#False
  If pid<>0
    OpenConsole()
    PrintN("Process  -> "+NamePid(pid)+" ["+Str(pid)+"] <-  Killed")
    CloseConsole()
      phandle = OpenProcess_ (#PROCESS_TERMINATE, #False, pid)
      If phandle <> #Null
        If TerminateProcess_ (phandle, 1)
          Result = #True
        EndIf
        CloseHandle_ (phandle)
      EndIf
      ProcedureReturn Result
    Else
      OpenConsole()
      PrintN("Usage  : Kill [ProgramID|ProgramExeName]")
      CloseConsole()
  EndIf
EndProcedure

CommandC.s=ProgramParameter()

pid=Val(UCase(CommandC))
If Len(Str(pid))<Len(CommandC)
  KillProcess2(PidName(CommandC))
Else
  KillProcess2(pid)
EndIf 
Kill.exe

this one kills by PID or EXENAME .. again .. console exe


should work with 9x and up .. (except NT)
i use them everyday ... :D

and btw.. Credits goes to this forum.. (they're a little addpated by me.. but ... :D .. the source is found on this forum ... Great Tips.. sorry for Offtopic

Posted: Mon Jul 10, 2006 4:33 pm
by Hi-Toro
I'd recommend testing your code on 9x if possible, as I found that the various Proc32* functions failed on 9x when called from within a procedure -- read through the thread for more info. Interestingly, this seemed to happen from any language (I think I tried both Blitz and C).

Posted: Fri Jul 14, 2006 11:11 am
by b1be

Code: Select all

#TH32CS_SNAPHEAPLIST = $1
#TH32CS_SNAPPROCESS = $2
#TH32CS_SNAPTHREAD = $4
#TH32CS_SNAPMODULE = $8
#TH32CS_SNAPALL = #TH32CS_SNAPHEAPLIST | #TH32CS_SNAPPROCESS | #TH32CS_SNAPTHREAD | #TH32CS_SNAPMODULE
#TH32CS_INHERIT = $80000000
#INVALID_HANDLE_VALUE = -1
#MAX_PATH = 260
#PROCESS32LIB = 9999
#PSAPI = 9998

CommandC.s=ProgramParameter()

pid=Val(UCase(CommandC))
If Len(Str(pid))<Len(CommandC)
  Gosub PidName
  pid=ResultPid
  Goto KillProcess2
Else
  Goto KillProcess2
EndIf 


PidName:
  ResultPid.l=0
  If OpenLibrary (#PROCESS32LIB, "kernel32.dll")
    snap = CallFunction (#PROCESS32LIB, "CreateToolhelp32Snapshot", #TH32CS_SNAPPROCESS, 0)
    If snap
      Define.PROCESSENTRY32 Proc32
      Proc32\dwSize = SizeOf (PROCESSENTRY32)
      If CallFunction (#PROCESS32LIB, "Process32First", snap, @Proc32)
        If UCase(PeekS (@Proc32\szExeFile))=UCase(CommandC):ResultPid=Proc32\th32ProcessID:EndIf
        While CallFunction (#PROCESS32LIB, "Process32Next", snap, @Proc32)
          If UCase(PeekS (@Proc32\szExeFile))=UCase(CommandC):ResultPid=Proc32\th32ProcessID:EndIf
        Wend      
      EndIf   
      CloseHandle_ (snap)
    EndIf
    CloseLibrary (#PROCESS32LIB)
  EndIf
Return
  
  
NamePid:
    ResultName.s=""
    If OpenLibrary (#PROCESS32LIB, "kernel32.dll")
      snap = CallFunction (#PROCESS32LIB, "CreateToolhelp32Snapshot", #TH32CS_SNAPPROCESS, 0)
      If snap
        Define.PROCESSENTRY32 Proc32
        Proc32\dwSize = SizeOf (PROCESSENTRY32)
        If CallFunction (#PROCESS32LIB, "Process32First", snap, @Proc32)
          If Proc32\th32ProcessID=pid:ResultName=PeekS (@Proc32\szExeFile):EndIf  
          While CallFunction (#PROCESS32LIB, "Process32Next", snap, @Proc32)
            If Proc32\th32ProcessID=pid:ResultName=PeekS (@Proc32\szExeFile):EndIf  
          Wend      
        EndIf   
        CloseHandle_ (snap)
      EndIf
      CloseLibrary (#PROCESS32LIB)
    EndIf
    Return
    
KillProcess2:
    If pid<>0
      Gosub NamePid
      phandle = OpenProcess_ (#PROCESS_TERMINATE, #False, pid)
      If phandle <> #Null
        If TerminateProcess_ (phandle, 1)
          OpenConsole()
          PrintN("Process  -> "+ResultName+" ["+Str(pid)+"] <-  Killed")
          CloseConsole()
        Else
          OpenConsole()
          PrintN("Failed To Kill: "+ResultName+" ["+Str(pid)+"]")
          CloseConsole() 
        EndIf
        CloseHandle_ (phandle)
      EndIf
      End
    Else
      OpenConsole()
      PrintN("Usage  : Kill [ProgramID|ProgramExeName]")
      CloseConsole()
    EndIf
End
Kill.exe (Without procedures) .. cant test on 9x .. :( .. should work now :D
again .. sorry for OFFTOPIC