Announcement

Collapse
No announcement yet.

Processes Running

Collapse
X
 
  • Filter
  • Time
  • Show
Clear All
new posts

    Processes Running

    Is there a way to get the names of all exe files that are
    currently running in memory?

    I used enumwindows and it only shows the WINDOWS that are
    running - I want the actual processes that are running

    The code below gives me an error of "No Entry Point" into the
    psapi dll

    Jim

    Code:
    #compile exe
    
    ''#include "d:\pbwin80\winapi\win32api.inc"
    
    Declare Function EnumProcesses Lib "PSAPI.DLL" ( _
                     ByRef lpidProcess As Long, _
                     ByVal cb As Long, _
                     ByRef cbNeeded As Long _
                     ) As Long
    
    
    function pbmain() as long
    
         dim processes???(1024)
    
         b$=""
    
         if enumprocesses(processes???,sizeof(processes???),cbneeded&) then
    
           cprocesses&=cbneeded&/4
    
           for i&=1 to cprocesses&
             if processes???(i&)=0 then iterate for
             b$=b$+str$(processes???(i&))+chr$(13,10)
           next i&
    
         end if
    
         ''retval&=terminateprocess(hprocess???,uexitcode???)
    
    
         msgbox b$
    
    end function
    [This message has been edited by Jim Seekamp (edited May 02, 2007).]
    Jim Seekamp

    #2
    >The code below gives me an error of "No Entry Point" into the psapi dll

    Then either it is DECLAREd wrong, the DLL is missing, or you are not running on a sufficiently recent version of windows. (i.e., NT+)

    But I think a search in source code forum will turn up the code you need, and that code will run on any version of Windows. I know this because I wrote one of the three or four different demos which do this.

    Michael Mattias
    Tal Systems (retired)
    Port Washington WI USA
    [email protected]
    http://www.talsystems.com

    Comment


      #3
      > ''retval&=terminateprocess(hprocess???,uexitcode???)

      Oops, my bad.

      If you are going to uncomment this line: No, there is no code anywhere which can help you.

      (Give a man a fish, he will eat today. Teach a man to fish, you will find him dead, swinging from a tree, held up only by the fishing line around his neck).

      Michael Mattias
      Tal Systems (retired)
      Port Washington WI USA
      [email protected]
      http://www.talsystems.com

      Comment


        #4
        Is there something wrong with using "terminateprocess" to
        stop a copy of the program that is already running??

        Throw me a bone here man!


        ------------------
        Jim Seekamp
        Jim Seekamp

        Comment


          #5
          You need to add the ALIAS clause to the declaration:
          Code:
          Declare Function EnumProcesses Lib "PSAPI.DLL" ALIAS "EnumProcesses" ( _
                           ByRef lpidProcess As Long, _
                           ByVal cb As Long, _
                           ByRef cbNeeded As Long _
                           ) As Long

          ------------------
          Website: http://com.it-berater.org
          SED Editor, TypeLib Browser, COM Wrappers.
          Forum: http://www.forum.it-berater.org
          Forum: http://www.jose.it-berater.org/smfforum/index.php

          Comment


            #6
            Is there something wrong with using "terminateprocess" to stop a copy of the program that is already running??
            First of all, the code you posted is attempting to "terminate process" for [/b]all[/b] processes running on the system (although you likely do not have permissions required to do "all"). It is not attempting to terminate only another copy of the currently running program.

            Well, maybe not, because hProcess??? is never assigned a value in that function. But it looks like that is what is in your mind.

            Secondly, doth sayest Microsoft:
            Remarks
            The TerminateProcess function is used to unconditionally cause a process to exit. Use it only in extreme circumstances [italics mine MCM]
            You can get the complete list of undesirable things which happen when you use TerminateProcess in your favorite SDK reference.

            If you just want to "stop a copy of the program that is already running" (that is, another instance of your program), there are other ways.

            If you want to stop "Everything" there is no way to do that, at least not any way which will escape my lips.

            MCM
            Michael Mattias
            Tal Systems (retired)
            Port Washington WI USA
            [email protected]
            http://www.talsystems.com

            Comment


              #7
              (Give a man a fish, he will eat today. Teach a man to fish, you will find him dead, swinging from a tree, held up only by the fishing line around his neck).
              Jezus Michael, talk about your truth in quotes, but jeez if the man was taught right then he would know enough to hide the body and eliminate the evidence *LOL*



              ------------------
              Engineer's Motto: If it aint broke take it apart and fix it

              "If at 1st you don't succeed... call it version 1.0"

              "Half of Programming is coding"....."The other 90% is DEBUGGING"

              "Document my code????" .... "WHYYY??? do you think they call it CODE? "

              Comment


                #8
                oops we must have been posting at the same time.

                your second post expands a bit on what I was thinking
                (When you terminate...be dagnabit sure that it is your process and not
                an OS process) or all WTF may occur

                ------------------
                Engineer's Motto: If it aint broke take it apart and fix it

                "If at 1st you don't succeed... call it version 1.0"

                "Half of Programming is coding"....."The other 90% is DEBUGGING"

                "Document my code????" .... "WHYYY??? do you think they call it CODE? "

                Comment


                  #9
                  Well, just so you don't freak out, the terminateprocess is a NOTE
                  after looking at the Win32api - I never even knew it existed
                  until today. It's not a part of that sample test code...

                  How would you BETTER delete a duplicate process?
                  I can't use %wm_syscommand,%sc_close because there
                  is no window open in the process I am deleting.
                  For the same reason, I can't use destroywindow.


                  ------------------
                  Jim Seekamp
                  Jim Seekamp

                  Comment


                    #10
                    >How would you BETTER delete a duplicate process?

                    Well, first I'd ask myself if instead of ending a duplicate I could prevent the second copy from starting in the first place. There is a lot of code here re how to use a mutex object to effect that, and it would be the cleanest solution.

                    But if I had to allow for the possibility that my program had to be terminated gracefully from without by a cooperating application (i.e, another copy of the program)?

                    First instinct is to set up the program to wait on a named event and exit gracefully when that event is signalled, but that could be tricky to code, especially if it's possible that more than one duplicate instance of the program existed.

                    So I think I would go with creating a window in my program, having that window respond to some message, then enum windows of that class sending the 'magic' message to the program. (Window does not have to be visible to handle messages).

                    MCM




                    Michael Mattias
                    Tal Systems (retired)
                    Port Washington WI USA
                    [email protected]
                    http://www.talsystems.com

                    Comment


                      #11
                      Thanks MCM

                      For anyone interested, here is the test code I ended up with;
                      works great:

                      Code:
                      #compile exe
                      
                      #include "\pbwin80\winapi\win32api.inc"
                      
                      type processentry32
                           dwSize as dword
                           cntUsage as dword
                           th32ProcessID as dword
                           th32DefaultHeapID as long ptr
                           th32ModuleID as dword
                           cntThreads as dword
                           th32ParentProcessID as dword
                           pcPriClassBase as long
                           dwFlags as dword
                           szExeFile as asciiz*%max_path
                      end type
                      
                      declare function enumprocesses(dword,byval dword,dword) as long
                      declare function getmodulefilenameex(byval dword,byval Dword,Asciiz,byval dword) as dword
                      declare function enumprocessmodules(byval dword,byref Dword,byval dword,dword) as long
                      
                      function pbmain() as long
                      
                           dim proc as processentry32
                      
                           b$=""
                      
                           do
                             hpsapidll???=getmodulehandle("psapi.dll")
                             if hpsapidll???=0 then hpsapidll???=loadlibrary("psapi.dll")
                      
                             henumprocesses???=getprocaddress(hpsapidll???,"EnumProcesses")
                             hgetmodulefilenameex???=getprocaddress(hpsapidll???,"GetModuleFileNameExA")
                             henumprocessmodules???=getprocaddress(hpsapidll???,"EnumProcessModules")
                      
                             cb???=100
                      
                             do
                               redim processids???(1 to (cb???/4))
                               call dword henumprocesses??? using enumprocesses(processids???(1),cb???,cbneeded???) to lresult&
                               if cb???>cbneeded??? then exit loop
                               cb???=cb???*2
                             loop
                      
                             nprocesses&=cbneeded???/4
                      
                             for i&=1 to nprocesses&
                               hprocess&=openprocess(%PROCESS_QUERY_INFORMATION Or %PROCESS_VM_READ,%false,processids???(i&))
                      
                               if hprocess&<>0 then
                                 cb???=100
                      
                                 do
                                   redim modules???(1 to (cb???/4))
                      
                                   call dword henumprocessmodules??? using enumprocessmodules(hprocess&,modules???(1),cb???,cbneeded???) to lresult&
                      
                                   if lresult&=0 then
                                     cbneeded???=0
                                     exit loop
                                   end if
                      
                                   if cb???>cbNeeded??? then
                                     exit loop
                                   else
                                     cb???=cb???*2
                                   end if
                      
                                 loop
                      
                                 nmodules&=cbneeded???/4
                      
                                 for j&=1 to nmodules&
                      
                                   call dword hgetmodulefilenameex??? using getmodulefilenameex _
                                        (hprocess&,modules???(j&),proc.szexeFile,sizeof(proc.szexefile)) to lresult&
                      
                                   if lresult& then
                                     b$=b$+proc.szexefile+chr$(13,10)
                                   end if
                      
                                 next j&
                      
                                 closehandle hprocess&
                               end if
                      
                             next i&
                      
                             exit loop
                           loop
                      
                           ff&=freefile
                           open "output.txt" for binary as #ff& base=0
                           seek #ff&,0
                           put$ #ff&,b$
                           seteof #ff&
                           close #ff&
                      
                           msgbox "All Done!"
                      
                      end function

                      ------------------
                      Jim Seekamp

                      [This message has been edited by Jim Seekamp (edited May 03, 2007).]
                      Jim Seekamp

                      Comment


                        #12
                        Added File creation to Running Processes

                        Great code, Jim. I won't say I understabd it but is easily adaptable to suit my purposes.

                        Wanting something to run down errant processes, or ones that get installed and not removed when no longer used, I looked around found Jim's code. What I did was add some sorts to the file.

                        What it does now is create a date and time file of services in a specific folder so if some aberrant behavior developes (virus? rogue? ...?), one can compare services running before (say at startup on a good day) with what's running currently.

                        Now it's easy (for me) to clip out a service and Google it to see if it's necessary.

                        '
                        Code:
                        'http://www.powerbasic.com/support/pbforums/showthread.php?t=14206&highlight=running+processes
                        ' by Jim Seekamp                                             
                         
                         
                         
                        #Compile Exe
                        #Dim All 
                        #Include "win32api.inc"
                         
                        $Foldr = "C:\Processes_Running\" '<-- Change to suit yourself
                         
                        Type processentry32
                             dwSize As Dword
                             cntUsage As Dword
                             th32ProcessID As Dword
                             th32DefaultHeapID As Long Ptr
                             th32ModuleID As Dword
                             cntThreads As Dword
                             th32ParentProcessID As Dword
                             pcPriClassBase As Long
                             dwFlags As Dword
                             szExeFile As Asciiz*%max_path
                        End Type
                         
                        Type Process_Array
                           Sort As String * %Max_path
                           Nam As String * 100 'way big but who cares
                           Folder As String * 250
                           Extension As String * 10 'should be plenty
                        End Type
                         
                        Declare Function enumprocesses(Dword,ByVal Dword,Dword) As Long
                        Declare Function getmodulefilenameex(ByVal Dword,ByVal Dword,Asciiz,ByVal Dword) As Dword
                        Declare Function enumprocessmodules(ByVal Dword,ByRef Dword,ByVal Dword,Dword) As Long
                         
                        Macro pf = Print #ff, 
                         
                        Macro Sort_By_Name
                           For ctr = LBound(Loaded()) To UBound(Loaded())
                               Loaded(ctr).Sort = UCase$(Loaded(ctr).Nam)
                           Next ctr                              
                           Array Sort Loaded()
                        End Macro
                         
                        Macro Sort_By_Folder
                           For ctr = LBound(Loaded()) To UBound(Loaded())
                               Loaded(ctr).Sort = UCase$(Loaded(ctr).Folder)
                           Next ctr                              
                           Array Sort Loaded()
                        End Macro
                         
                        Macro Sort_By_Extension
                           For ctr = LBound(Loaded()) To UBound(Loaded())
                               Loaded(ctr).Sort = UCase$(Loaded(ctr).Extension) & _
                                                  UCase$(Loaded(ctr).Nam)
                           Next ctr                              
                           Array Sort Loaded()
                        End Macro
                         
                         
                         
                        Function PBMain() As Long
                         
                         
                             Dim proc As processentry32
                             Local b$, lResult&, _
                                   hpsapidll???, _
                                   henumprocesses???, _
                                   hgetmodulefilenameex???, _
                                   henumprocessmodules???, _
                                   cb???, _
                                   cbneeded???, _
                                   processids???()
                             'Local Loaded()
                             Dim Loaded(0)   As Process_Array      
                             b$=""
                         
                             Do
                               hpsapidll???=GetModuleHandle("psapi.dll")
                               If hpsapidll???=0 Then hpsapidll???=LoadLibrary("psapi.dll")
                         
                               henumprocesses???=GetProcAddress(hpsapidll???,"EnumProcesses")
                               hgetmodulefilenameex???=GetProcAddress(hpsapidll???,"GetModuleFileNameExA")
                               henumprocessmodules???=GetProcAddress(hpsapidll???,"EnumProcessModules")
                         
                               cb???=100
                         
                               Do
                                 ReDim processids???(1 To (cb???/4))
                                 Call Dword henumprocesses??? Using enumprocesses(processids???(1),cb???,cbneeded???) To lresult&
                                 If cb???>cbneeded??? Then Exit Loop
                                 cb???=cb???*2
                               Loop
                               Local nprocesses&
                               nprocesses&=cbneeded???/4
                               Local i&
                               For i&=1 To nprocesses&
                                 Local hprocess&
                                 hprocess&=OpenProcess(%PROCESS_QUERY_INFORMATION Or %PROCESS_VM_READ,%false,processids???(i&))
                         
                                 If hprocess&<>0 Then
                                   cb???=100
                         
                                   Do           
                                     Local modules???()
                                     ReDim modules???(1 To (cb???/4))
                         
                                     Call Dword henumprocessmodules??? Using enumprocessmodules(hprocess&,modules???(1),cb???,cbneeded???) To lresult&
                         
                                     If lresult&=0 Then
                                       cbneeded???=0
                                       Exit Loop
                                     End If
                         
                                     If cb???>cbNeeded??? Then
                                       Exit Loop
                                     Else
                                       cb???=cb???*2
                                     End If
                         
                                   Loop
                                   Local nmodules&
                                   nmodules&=cbneeded???/4
                                   Local j&
                                   For j&=1 To nmodules&
                         
                                     Call Dword hgetmodulefilenameex??? Using getmodulefilenameex _
                                          (hprocess&,modules???(j&),proc.szexeFile,SizeOf(proc.szexefile)) To lresult&
                         
                                     If lresult& Then    
                                       Local x$, i1&
                                       x$ = UCase$(proc.szexefile)
                                       b$=b$+proc.szexefile+Chr$(13,10)
                                       
                                       ReDim Preserve Loaded(UBound(Loaded())+ 1)
                                       Loaded(UBound(Loaded())).Folder = proc.szexefile
                                       
                                       'get name stripped of folder
                                       i1 = InStr(-1, x$, "\")      
                                       If i1 Then
                                          Loaded(UBound(Loaded())).Nam = Mid$(proc.szexefile, i1 + 1)
                                         Else                            
                                           Loaded(UBound(Loaded())).Nam = "No Name"
                                       End If  
                                       'get extension
                                       i1 = InStr(-1, x$, ".")      
                                       If i1 Then
                                          Loaded(UBound(Loaded())).Extension = Mid$(proc.szexefile, i1 + 1)
                                         Else                            
                                           Loaded(UBound(Loaded())).Nam = "  "
                                       End If  
                         
                                     End If
                         
                                   Next j&
                         
                                   CloseHandle hprocess&
                                 End If
                         
                               Next i&
                         
                               Exit Loop
                             Loop                
                         
                            
                             
                             Local ff&, fil$, dr$, ctr&
                             
                             fil$ = $Foldr & _
                                    Date$ & "---" & Left$(Time$,2) & _
                                    ".txt"
                             'Replace ":" With "-" In fil$ 'in time$ 'remmed out as 
                             ff&=FreeFile
                             Open fil$ For Output As #ff&
                             Pf  ,Using$("#, Processes Loaded on ", UBound(Loaded())) & _
                                        Date$ & " @ " & Time$  & $CrLf 
                         
                              Pf  ,"Processes that are not DLL's" & $CrLf 
                         
                            Sort_By_Name 
                             b$ = ""
                             For ctr = LBound(Loaded())+ 1 To UBound(Loaded())
                                x$ = UCase$(Loaded(ctr).Nam)
                                If InStr(x$, "DLL") = 0 Then
                                  Pf  Trim$(Loaded(ctr).Nam), Loaded(ctr).Folder 
                                End If
                             Next ctr
                             Pf  $CrLf   
                               
                               
                             Sort_By_Folder     
                             Pf  ,"All Services Running"
                             b$ = ""                  
                             Local Proc_cnt&, Dll_cnt&
                             Proc_Cnt = 1
                             For ctr = LBound(Loaded())+ 1 To UBound(Loaded())
                               Local idnt$, l$  'set indents for display
                               idnt$ = ""    
                               l$ = Loaded(ctr).Folder 'easier coding                  
                               i = InStr(-1, l$, "\") 'find folder end
                                 If i And b$ > "" Then
                                   If Left$(l$, i) = Left$(b$, i) Then 'same folder
                                      idnt$ = Space$(i) 
                                      l$ = Mid$(l$, i + 1) 'process name only
                                      Incr dll_cnt
                                      Mid$(idnt$, i-6) = Using$("## ", dll_cnt)
                                     Else 
                                      Reset dll_cnt 
                                   End If
                                 End If
                               b$ = Loaded(ctr).Folder 'for indent next check
                               Pf  idnt$ & l$ 
                             Next ctr 
                             Pf   $CrLf  & $CrLf 
                             
                             Sort_By_Extension
                             pf, ,"Services Running in Extension order"
                             b$ = ""                  
                             For ctr = LBound(Loaded())+ 1 To UBound(Loaded())
                               If b$<>UCase$(Loaded(ctr).Extension) Then
                                  Pf  , Trim$(Loaded(ctr).Extension) & " 's"
                               End If
                               pf Trim$(loaded(ctr).Nam), Loaded(ctr).Folder
                               b$ = UCase$(Loaded(ctr).Extension)
                             Next ctr 
                             pf,  $CrLf  & $CrLf 
                             
                             
                             Close #ff&
                         
                             MsgBox "All Done!" & Str$(ctr) & $CrLf & fil$
                         
                        End Function
                        '
                        It's a pretty day. I hope you enjoy it.

                        Gösta

                        JWAM: (Quit Smoking): http://www.SwedesDock.com/smoking
                        LDN - A Miracle Drug: http://www.SwedesDock.com/LDN/

                        Comment


                          #13
                          Thanks Gosta,
                          Very cool
                          Jim
                          Jim Seekamp

                          Comment


                            #14
                            This method uses the Toolhelp32 library (tlhelp32.dll), and works on all Windows platforms from Win95 onwards ...
                            Code:
                            #COMPILE EXE
                            #INCLUDE "win32api.inc"
                            #INCLUDE "tlhelp32.inc"
                             
                            SUB ListProcesses
                             LOCAL hSnap AS LONG, p AS LONG, Proc AS PROCESSENTRY32
                             hSnap = CreateToolhelp32Snapshot (%TH32CS_SNAPPROCESS, 0&)
                             IF hSnap = 0 THEN EXIT SUB
                             Proc.dwSize = SIZEOF(Proc)
                             p = Process32First (hSnap, Proc)
                             WHILE p
                                 STDOUT STR$(Proc.th32ProcessID) & ": " & Proc.szExefile
                                 p = Process32Next (hSnap, Proc)
                             WEND
                             CloseHandle hSnap
                            END SUB
                             
                            FUNCTION PBMAIN() AS LONG
                             ListProcesses
                             WAITKEY$
                            END FUNCTION

                            This is the more recommended method, but it doesn't work under Win9x ...
                            Code:
                            #COMPILE EXE
                            #INCLUDE "win32api.inc"
                            
                            DECLARE FUNCTION EnumProcesses LIB "psapi.dll" ALIAS "EnumProcesses" (lpidProcess AS DWORD, BYVAL cb AS DWORD, cbNeeded AS DWORD) AS LONG
                            DECLARE FUNCTION GetModuleFileNameEx LIB "psapi.dll" ALIAS "GetModuleFileNameExA" (BYVAL hProcess AS DWORD, BYVAL hModule AS DWORD, ModuleName AS ASCIIZ, BYVAL nSize AS DWORD) AS DWORD
                            DECLARE FUNCTION EnumProcessModules LIB "psapi.dll" ALIAS "EnumProcessModules" (BYVAL hProcess AS DWORD, BYREF lphModule AS DWORD, BYVAL cb AS DWORD, cbNeeded AS DWORD) AS LONG
                            
                            FUNCTION PBMAIN() AS LONG
                                DIM aProcesses(1024) AS DWORD
                                LOCAL cbNeeded AS DWORD, cProcesses AS DWORD, i AS LONG, szFile AS ASCIIZ * 1024, hProcess AS LONG, cb AS LONG
                                IF ISFALSE EnumProcesses(aProcesses(LBOUND(aProcesses)), (UBOUND(aProcesses) - LBOUND(aProcesses) + 1) * 4, cbNeeded) THEN EXIT FUNCTION
                                cb = 100:  cProcesses = cbNeeded \ 4
                                FOR i = 0 TO cProcesses - 1
                                    hProcess = OpenProcess(%PROCESS_QUERY_INFORMATION OR %PROCESS_VM_READ, %False, aProcesses(i))
                                    IF hProcess THEN
                                        REDIM Modules(1 TO cb / 4) AS DWORD
                                        IF EnumProcessModules (hProcess, Modules(1), cb, cbNeeded) THEN
                                            GetModuleFileNameEx (hProcess, Modules(1), szFile, SIZEOF(szFile))
                                            STDOUT STR$(aProcesses(i)) & ": " & TRIM$(szFile)
                                        END IF
                                        CloseHandle hProcess
                                    ELSE
                                        STDOUT STR$(aProcesses(i)) & ": <Unknown filename>"
                                    END IF
                                NEXT
                            WAITKEY$
                            END FUNCTION

                            Here is another method which calls NtQuerySystemInformation with the SystemHandleInformation flag to get a list of all handles. It then displays the processID of each handle (you can then expand on that with OpenProcess\GetModuleFileNameEx to get the module filenames etc) ...
                            Code:
                            #COMPILE EXE
                            #INCLUDE "win32api.inc"
                            
                            DECLARE FUNCTION NtQuerySystemInformation LIB "ntdll.dll" ALIAS "NtQuerySystemInformation" (BYVAL unFlag1 AS DWORD, BYVAL lpvBuffer AS DWORD, BYVAL dwBufferSize AS DWORD, BYVAL unFlag2 AS DWORD) AS DWORD
                            
                            FUNCTION PBMAIN AS LONG
                            ON ERROR RESUME NEXT
                                #REGISTER NONE
                                REGISTER m_numstructs AS DWORD
                                LOCAL m_memptr        AS DWORD PTR
                                LOCAL ret_len         AS DWORD
                                LOCAL sStr            AS STRING
                                LOCAL I               AS LONG
                                REGISTER enumI        AS DWORD
                                m_memptr = VirtualAlloc(BYVAL %NULL, 100, %MEM_COMMIT, %PAGE_READWRITE)
                                IF (NtQuerySystemInformation(BYVAL 16, BYVAL m_memptr, 100, BYREF ret_len)) THEN
                                    VirtualFree BYVAL m_memptr, 0, %MEM_DECOMMIT
                                    m_memptr = VirtualAlloc(BYVAL %NULL, ret_len+256, %MEM_COMMIT, %PAGE_READWRITE)
                                    NtQuerySystemInformation BYVAL 16, BYVAL m_memptr, ret_len, BYREF ret_len       '// 16 = SystemHandleInformation
                                END IF
                                m_numstructs  = ret_len / 4
                                FOR enumI = 1 TO m_numstructs STEP 4
                                    STDOUT "Handle from processID: " & STR$(@m_memptr[enumI])
                                NEXT enumI
                                VirtualFree BYVAL m_memptr, 0, %MEM_DECOMMIT
                            WAITKEY$
                            END FUNCTION
                            -

                            Comment


                              #15
                              This is my "terminator"
                              Code:
                              FUNCTION KillProcess(sProcName AS STRING, _
                                                   BYVAL bProcToCarryOut AS BYTE) AS BYTE
                              
                              LOCAL szProcessTitle    AS ASCIIZ * 256
                              LOCAL hProcessName      AS LONG
                              LOCAL hProcess          AS LONG
                              LOCAL hProcessID        AS LONG
                              LOCAL hOpen             AS LONG
                              LOCAL hKill             AS LONG
                              LOCAL PROCESS_TERMINATE AS INTEGER
                              LOCAL bTerminate        AS BYTE
                              
                              ' bProcToCarryOut:
                              ' 1 - search and show process with exact name
                              ' 2 - search and terminate process with exact name
                              ' 11 - search and show process with part of name
                              ' 12 - search and terminate first process with part of name
                              '
                              ' szProcName - allways receive process name
                              
                              FUNCTION = 0
                              bTerminate     = 0
                              szProcessTitle = ""
                              PROCESS_TERMINATE = &H1
                              hProcess = GetDesktopWindow
                              hProcess = GetWindow(hProcess, %GW_CHILD)
                              DO
                                  IF hProcess = 0 THEN EXIT DO
                                  hProcessName = GetWindowText(hProcess, szProcessTitle, 255)
                              
                                  SELECT CASE bProcToCarryOut
                                      CASE 1
                                          IF sProcName = szProcessTitle THEN
                                              FUNCTION = 1
                                              EXIT FUNCTION
                                          END IF
                                      CASE 2
                                          IF sProcName = szProcessTitle THEN bTerminate = 1
                                      CASE 11
                                          IF TALLY(UCASE$(szProcessTitle),UCASE$(sProcName)) > 0 THEN
                                              sProcName = szProcessTitle
                                              FUNCTION = 11
                                              EXIT FUNCTION
                                          END IF
                                      CASE 12
                                          IF TALLY(UCASE$(szProcessTitle),UCASE$(sProcName)) > 0 THEN
                                              bTerminate = 1
                                              sProcName = szProcessTitle
                                          END IF
                                  END SELECT
                              
                                  IF bTerminate = 1 THEN
                                      hProcess = FindWindow("", BYCOPY szProcessTitle)
                                      GetWindowThreadProcessId hProcess, hProcessID
                                      hOpen = OpenProcess(PROCESS_TERMINATE, 1, hProcessID)
                                      hKill = TerminateProcess(hOpen, 0&)
                                      Closehandle hOpen
                                      SLEEP 250
                                      FUNCTION = 255
                                      EXIT DO
                                  END IF
                              
                                  hProcess = GetWindow(hProcess, %GW_HWNDNEXT)
                              LOOP
                              
                              END FUNCTION
                              Last edited by Alexander Holzer; 11 Jul 2008, 07:19 AM.
                              Yours sincerely

                              Comment


                                #16
                                Updated code

                                At the risk of repeating myself and unable to edit the posting above, I had occasion to revisit the code today and made the output file more organized:

                                Originally posted by Gösta H. Lovgren-2 View Post
                                ...
                                What it does now is create a date and time file of services in a specific folder so if some aberrant behavior developes (virus? rogue? ...?), one can compare services running before (say at startup on a good day) with what's running currently.

                                Now it's easy (for me) to clip out a service and Google it to see if it's necessary.
                                '
                                Code:
                                'http://www.powerbasic.com/support/pbforums/showthread.php?t=14206&highlight=running+processes
                                ' by Jim Seekamp                                             
                                'modified for file by Swede
                                
                                #Compile Exe
                                #Dim All 
                                #Include "win32api.inc"
                                $Foldr = "C:\Processes_Running\" '<-- Change to suit yourself
                                Type processentry32
                                     dwSize As Dword
                                     cntUsage As Dword
                                     th32ProcessID As Dword
                                     th32DefaultHeapID As Long Ptr
                                     th32ModuleID As Dword
                                     cntThreads As Dword
                                     th32ParentProcessID As Dword
                                     pcPriClassBase As Long
                                     dwFlags As Dword
                                     szExeFile As Asciiz*%max_path
                                End Type
                                Type Process_Array
                                   Sort As String * %Max_path
                                   Nam As String * 100 'way big but who cares
                                   Folder As String * 250
                                   Extension As String * 10 'should be plenty
                                End Type
                                Declare Function enumprocesses(Dword,ByVal Dword,Dword) As Long
                                Declare Function getmodulefilenameex(ByVal Dword,ByVal Dword,Asciiz,ByVal Dword) As Dword
                                Declare Function enumprocessmodules(ByVal Dword,ByRef Dword,ByVal Dword,Dword) As Long
                                Macro pf = Print #ff, 
                                Macro Sort_By_Name
                                   For ctr = LBound(Loaded()) To UBound(Loaded())
                                       Loaded(ctr).Sort = UCase$(Loaded(ctr).Nam)
                                   Next ctr                              
                                   Array Sort Loaded()
                                End Macro
                                Macro Sort_By_Folder
                                   For ctr = LBound(Loaded()) To UBound(Loaded())
                                       Loaded(ctr).Sort = UCase$(Loaded(ctr).Folder)
                                   Next ctr                              
                                   Array Sort Loaded()
                                End Macro
                                Macro Sort_By_Extension
                                   For ctr = LBound(Loaded()) To UBound(Loaded())
                                       Loaded(ctr).Sort = UCase$(Loaded(ctr).Extension) & _
                                                          UCase$(Loaded(ctr).Nam)
                                   Next ctr                              
                                   Array Sort Loaded()
                                End Macro
                                 
                                Function PBMain() As Long
                                
                                     Dim proc As processentry32
                                     Local b$, lResult&, _
                                           hpsapidll???, _
                                           henumprocesses???, _
                                           hgetmodulefilenameex???, _
                                           henumprocessmodules???, _
                                           cb???, _
                                           cbneeded???, _
                                           processids???()
                                     'Local Loaded()
                                     Dim Loaded(0)   As Process_Array      
                                     b$=""
                                     Do
                                       hpsapidll???=GetModuleHandle("psapi.dll")
                                       If hpsapidll???=0 Then hpsapidll???=LoadLibrary("psapi.dll")
                                       henumprocesses???=GetProcAddress(hpsapidll???,"EnumProcesses")
                                       hgetmodulefilenameex???=GetProcAddress(hpsapidll???,"GetModuleFileNameExA")
                                       henumprocessmodules???=GetProcAddress(hpsapidll???,"EnumProcessModules")
                                       cb???=100
                                       Do
                                         ReDim processids???(1 To (cb???/4))
                                         Call Dword henumprocesses??? Using enumprocesses(processids???(1),cb???,cbneeded???) To lresult&
                                         If cb???>cbneeded??? Then Exit Loop
                                         cb???=cb???*2
                                       Loop
                                       Local nprocesses&
                                       nprocesses&=cbneeded???/4
                                       Local i&
                                       For i&=1 To nprocesses&
                                         Local hprocess&
                                         hprocess&=OpenProcess(%PROCESS_QUERY_INFORMATION Or %PROCESS_VM_READ,%false,processids???(i&))
                                         If hprocess&<>0 Then
                                           cb???=100
                                           Do           
                                             Local modules???()
                                             ReDim modules???(1 To (cb???/4))
                                             Call Dword henumprocessmodules??? Using enumprocessmodules(hprocess&,modules???(1),cb???,cbneeded???) To lresult&
                                             If lresult&=0 Then
                                               cbneeded???=0
                                               Exit Loop
                                             End If
                                             If cb???>cbNeeded??? Then
                                               Exit Loop
                                             Else
                                               cb???=cb???*2
                                             End If
                                           Loop
                                           Local nmodules&
                                           nmodules&=cbneeded???/4
                                           Local j&
                                           For j&=1 To nmodules&
                                             Call Dword hgetmodulefilenameex??? Using getmodulefilenameex _
                                                  (hprocess&,modules???(j&),proc.szexeFile,SizeOf(proc.szexefile)) To lresult&
                                             If lresult& Then    
                                               Local x$, i1&
                                               x$ = UCase$(proc.szexefile)
                                               b$=b$+proc.szexefile+Chr$(13,10)
                                               
                                               ReDim Preserve Loaded(UBound(Loaded())+ 1)
                                               Loaded(UBound(Loaded())).Folder = proc.szexefile
                                               
                                               'get name stripped of folder
                                               i1 = InStr(-1, x$, "\")      
                                               If i1 Then
                                                  Loaded(UBound(Loaded())).Nam = Mid$(proc.szexefile, i1 + 1)
                                                 Else                            
                                                   Loaded(UBound(Loaded())).Nam = "No Name"
                                               End If  
                                               'get extension
                                               i1 = InStr(-1, x$, ".")      
                                               If i1 Then
                                                  Loaded(UBound(Loaded())).Extension = Mid$(proc.szexefile, i1 + 1)
                                                 Else                            
                                                   Loaded(UBound(Loaded())).Nam = "  "
                                               End If  
                                             End If
                                           Next j&
                                           CloseHandle hprocess&
                                         End If
                                       Next i&
                                       Exit Loop
                                     Loop                
                                    
                                     
                                     Local ff&, fil$, dr$, ctr&
                                     
                                     fil$ = $Foldr & _
                                            Date$ & "---" & Left$(Time$,2) & _
                                            ".txt"
                                     'Replace ":" With "-" In fil$ 'in time$ 'remmed out as 
                                     ff&=FreeFile
                                     Open fil$ For Output As #ff&
                                     Pf  ,Using$("#, Processes Loaded on ", UBound(Loaded())) & _
                                                Date$ & " @ " & Time$  & $CrLf 
                                      Pf  ,"Processes that are not DLL's" & $CrLf 
                                    Sort_By_Name 
                                     b$ = ""                                          
                                     Local ctr2&, tmp$, Last_Tmp$, u1$ 
                                        
                                      'no DLL's                         
                                      ctr2 = 1
                                     For ctr = LBound(Loaded()) + 1 To UBound(Loaded())-1 '+1 as first is blank
                                        x$ = UCase$(Loaded(ctr).Nam)
                                        If InStr(x$, "DLL") = 0 Then
                                          If Loaded(ctr).Nam & Loaded(ctr).Folder = _
                                             Loaded(ctr+1).Nam & Loaded(ctr+1).Folder Then
                                             Incr ctr2
                                            Else
                                             Pf  Using$("(#) ", ctr2) & Trim$(Loaded(ctr).Nam), Loaded(ctr).Folder 
                                             ctr2 = 1
                                          End If   
                                        End If
                                     Next ctr
                                     Pf  Using$("(#) ", ctr2) & Trim$(Loaded(ctr).Nam), Loaded(ctr).Folder 
                                     Pf  $CrLf   
                                       
                                       
                                     Sort_By_Folder     
                                     Pf  ,"All Services Running"
                                     b$ = ""                  
                                     Local Proc_cnt&, ctr1&, Dll_cnt&
                                     Proc_Cnt = 1          
                                     ctr1 = 1
                                     For ctr = LBound(Loaded())+ 1 To UBound(Loaded()) - 1
                                          If Loaded(ctr).Folder = _
                                             Loaded(ctr+1).Folder Then
                                             Incr ctr2
                                            Else
                                             Pf  Using$("(#) ", ctr2) & Loaded(ctr).Folder 
                                             ctr2 = 1
                                          End If   
                                     Next ctr 
                                     Pf  Using$("(#) ", ctr2) & Loaded(ctr).Folder 
                                     Pf   $CrLf  & $CrLf 
                                     
                                     Sort_By_Extension
                                     pf, ,"Services Running in Extension order"
                                     ctr1 = 1
                                     For ctr = LBound(Loaded())+ 1 To UBound(Loaded()) - 1
                                          If UCase$(Loaded(ctr).Folder) = _
                                             UCase$(Loaded(ctr+1).Folder) Then
                                             Incr ctr2
                                            Else
                                             Pf  Using$("(#) ", ctr2) & Loaded(ctr).Folder
                                             ctr2 = 1
                                          End If   
                                     Next ctr   
                                     Pf  Using$("(#) ", ctr2) & Loaded(ctr).Folder
                                     pf,  $CrLf  & $CrLf 
                                     
                                     
                                     Close #ff&
                                     MsgBox   fil$ ,, "All Done!" & Using$(" #, Services in file located:", ctr - 1)  
                                End Function
                                '
                                It's a pretty day. I hope you enjoy it.

                                Gösta

                                JWAM: (Quit Smoking): http://www.SwedesDock.com/smoking
                                LDN - A Miracle Drug: http://www.SwedesDock.com/LDN/

                                Comment


                                  #17
                                  Just an FYI - Microsoft bought Systernals - they have an AWESOME process explorer, shows exe's shelled out from the parent etc.....

                                  THere may be source code out there for that still, although Microsoft has probably closed that since purchasing it.

                                  Download's on MS's site, look for "PRocess Explorer".
                                  Scott Turchin
                                  MCSE, MCP+I
                                  http://www.tngbbs.com
                                  ----------------------
                                  True Karate-do is this: that in daily life, one's mind and body be trained and developed in a spirit of humility; and that in critical times, one be devoted utterly to the cause of justice. -Gichin Funakoshi

                                  Comment


                                    #18
                                    Thankfully not FULLY corrupted yet though cause SYSINTERNALS is tooo good not to pass up.

                                    More than once the tools have solved a wicked hawd problem for me.


                                    I hope it remains for a LOOOOOOOOOOOOOOOOONNNNNNNNNNNnnnnnnnnnnnnnnnnnnnnnnnnnnnng time to come
                                    Engineer's Motto: If it aint broke take it apart and fix it

                                    "If at 1st you don't succeed... call it version 1.0"

                                    "Half of Programming is coding"....."The other 90% is DEBUGGING"

                                    "Document my code????" .... "WHYYY??? do you think they call it CODE? "

                                    Comment

                                    Working...
                                    X
                                    😀
                                    🥰
                                    🤢
                                    😎
                                    😡
                                    👍
                                    👎