[Migrated content. Thread originally posted on 06 May 2005]
Has anyone done any work in trying to determine if a program is currently running on a machine?  
I'm looking for a way to tell if an application has already been launched an running on the machine, instead of activating another instance of the program.
Is this functionality available in the USER32.DLL?
Thanks
JH
You're right that USER32.DLL is the place to look.
You use the FindWindowA function.
Below are some snippets of code:
Working Storage snippet
       01 H-ACU-WND                 PIC 9(4) COMP-5 EXTERNAL.
       01 WS-CLASS-NAME             PIC X(255) VALUE SPACES.
       01 WS-WINDOW-NAME            PIC X(255) VALUE SPACES.
       01 RETURN-VALUE              USAGE UNSIGNED-LONG.
Procedure Division snippet
           SET ENVIRONMENT "DLL-CONVENTION" TO 1.
           CALL "USER32.DLL".
           MOVE "AcucobolWClass" TO WS-CLASS-NAME.
           MOVE "Instance" TO WS-WINDOW-NAME.
           INSPECT WS-CLASS-NAME REPLACING TRAILING SPACES
             BY NULLS.
           INSPECT WS-WINDOW-NAME REPLACING TRAILING SPACES
             BY NULLS.
           CALL "FindWindowA" USING
             BY REFERENCE WS-CLASS-NAME
             BY REFERENCE WS-WINDOW-NAME
             RETURNING RETURN-VALUE.
           IF RETURN-VALUE NOT = 0
              DISPLAY MESSAGE BOX "Instance already running."
                TITLE "Program Running"
              CANCEL "USER32.DLL"
              STOP RUN.
You would need to move your window's title to the WS-WINDOW-NAME variable.
Jim
                
     
                                    
            [Migrated content. Thread originally posted on 06 May 2005]
Has anyone done any work in trying to determine if a program is currently running on a machine?  
I'm looking for a way to tell if an application has already been launched an running on the machine, instead of activating another instance of the program.
Is this functionality available in the USER32.DLL?
Thanks
JH
Where do you find what needs to be put in the class?
I am trying to figure out if there is a delphi program running that I have to interface with?
Thanks for your help
JH
                
     
                                    
            [Migrated content. Thread originally posted on 06 May 2005]
Has anyone done any work in trying to determine if a program is currently running on a machine?  
I'm looking for a way to tell if an application has already been launched an running on the machine, instead of activating another instance of the program.
Is this functionality available in the USER32.DLL?
Thanks
JH
Where do you find what needs to be put in the class?
I am trying to figure out if there is a delphi program running that I have to interface with?
Thanks for your help
JH
                
     
                                    
            [Migrated content. Thread originally posted on 06 May 2005]
Has anyone done any work in trying to determine if a program is currently running on a machine?  
I'm looking for a way to tell if an application has already been launched an running on the machine, instead of activating another instance of the program.
Is this functionality available in the USER32.DLL?
Thanks
JH
I think you should be able to use the GetClassNameA function, which is also in USER32.DLL.  I thought you were trying to test for an AcuCobol window.
Here are some code snippets:
Working storage:
       01 H-ACU-WND                 PIC 9(4) COMP-5 EXTERNAL.
       01 WS-CLASS-NAME             PIC X(255) VALUE SPACES.
       01 WS-SIZE                   USAGE UNSIGNED-LONG.
       01 WS-BUFFER                 PIC X(255) VALUE SPACES.
       01 PTR-WS-BUFFER             USAGE POINTER.
      *Return value must be unsigned-long for win32.
       01 RETURN-VALUE              USAGE UNSIGNED-LONG.
Procedure division:
           MOVE SPACES TO WS-BUFFER.
           SET PTR-WS-BUFFER TO NULL.
           INSPECT WS-BUFFER REPLACING TRAILING SPACES
             BY NULLS.
           SET PTR-WS-BUFFER TO ADDRESS OF WS-BUFFER.
           SET WS-SIZE TO SIZE OF WS-BUFFER.
           SUBTRACT 1 FROM WS-SIZE.
           CALL "GetClassNameA" USING
             BY VALUE H-ACU-WND
                      PTR-WS-BUFFER
                      WS-SIZE
             RETURNING RETURN-VALUE.
           IF RETURN-VALUE NOT = 0
              MOVE WS-BUFFER TO WS-CLASS-NAME.
Unfortunately, I don't think I've ever been able to get this to work with the H-ACU-WND variable.
Here's some VB documentation on the GetClassName function:
GetClassName
VB Declaration
Declare Function GetClassName& Lib "user32" Alias "GetClassNameA" (ByVal hwnd _
As Long, ByVal lpClassName As String, ByVal nMaxCount As Long)
Description
Retrieves the class name for the specified window.
Use with VB
No problem.
Parameter	Type/Description
hwnd	Long?Window handle for which to obtain the class name.
lpClassName	String?Buffer to load with the class name. Must be preallocated to at least nMaxCount 1 characters.
nMaxCount	Long?Length of the buffer provided by lpClassName.
Return Value
Long?The length in bytes of the class name excluding the final null terminating character. Zero on error. Sets GetLastError.
I guess the simplest way to find out the class name would be if a delphi programmer could tell you what the class name would be for a delphi window.  I think someone in tech support originally told me that an Acucobol window has the AcucobolWClass name.
Jim
                
     
                                    
            [Migrated content. Thread originally posted on 06 May 2005]
Has anyone done any work in trying to determine if a program is currently running on a machine?  
I'm looking for a way to tell if an application has already been launched an running on the machine, instead of activating another instance of the program.
Is this functionality available in the USER32.DLL?
Thanks
JH
Originally posted by JGramer 
Unfortunately, I don't think I've ever been able to get this to work with the H-ACU-WND variable.
 This is because you have not declared the datatypes correctly, it should be:
01 H-ACU-WND PIC X(4) COMP-N.
01 WS-SIZE PIC X(4) COMP-N.
01 PTR-WS-BUFFER PIC X(4) COMP-N.
01 RETURN-VALUE PIC S9(9) COMP-5.
With this change I think it should do the trick.
Apart of that, thank you for providing good examples!
As for the Window class name. Yes, enumerating windows with FindWindow followed by a GetClassName is the trick.