Announcement

Collapse
No announcement yet.

Exe Dll Windows-Dialogs Is this possible?

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

  • Michael Mattias
    replied
    See my comments re TRY..CATCH...END TRY in the other thread. This is not a proper use.

    Leave a comment:


  • norbert doerre
    replied
    Cliff,
    the ways of MS are often quite epical....
    Some of them are not made to be understood.
    Just reading this thread i find out that You are working on the same problems as me but just from the other direction. Accessing dialogs amongst DLLs is nearly just like having only one DLL. But You have always to consider the content of all participating DLLs at a whole just not to get into code or naming conflicts.
    Now and then You have to look at the limitations of win 98 an below because these OS handle focus different from XP. In these cases You have to 'patch' with a code like this for XP:
    Code:
    Sub SetFocusForegroundWindow(hDialog As Long)
    	'Following procedure sets the focus in advance to a window 
    	'and hereafter calls SetForegroundWindow.
    	'INPUT:	Handle of window to be placed in foreground. This could be any window,
            '          even a window within another window. 
    	Local Thread1 As Dword
    	Local Thread2 As Dword
    	Thread1 = GetCurrentThreadId()
    	Thread2 = GetWindowThreadProcessId(GetForegroundWindow(), 0)
    	AttachThreadInput(Thread1, Thread2, %True)
    	Try
    		SetForegroundWindow(hDialog)
    	Catch
    		AttachThreadInput(Thread1, Thread2, %False)
    	End Try
    End Sub
    Using threads might also be a good advice for large code.
    Most problems however are caused by a wrong Z-order of open interacting windows. In these cases, You may use the above code.

    The following code gives back the current window having the focus, even if this is not visible on screen.
    Code:
    Function GetControlWithFocus(szClassName As Asciiz) As Long
    	'INPUT:	./.
    	'OUTPUT:	szClassName[128] = Klassenname des gefundenen Dialogs
    	'			FUNCTION VALUE: Handle des gefundenen Dialogs	
    	Local szBuffer As Asciiz * 128
    	Local OtherThrdID As Long
    	Local Thrd1 As Long
    	Local Thrd2 As Long
    	Local Note As Long
    	Local hWnd As Long
    	Thrd1 = GetWindowThreadProcessId(hWnd, GetCurrentThreadID)
    	Thrd2 = GetWindowThreadProcessId(GetForegroundWindow, OtherThrdID)
    	If Thrd1 <> Thrd2 Then 
    		Note = AttachThreadInput(Thrd2, Thrd1, %True)
    	End If
    	hWnd = GetFocus()
    	If Note Then 
    		Note = AttachThreadInput(Thrd2, Thrd1, %False)
    	End If
    	Call GetClassName(hWnd, szBuffer, 128)
    	szClassName = szBuffer 'Class Name
    	Function = hWnd 'Dialog Handle
    End Function

    Leave a comment:


  • Michael Mattias
    replied
    >If you do not know how to "Phrase" your question, how can you get answers?

    "List of" (human) ==> "ENUMxxxx" (windows) ==> OPEN Win32API.INC, Find All "Enum"

    Leave a comment:


  • Cliff Nichols
    replied
    Thank you MCM....at least now I got a idea of what to research...never would have thought of a word like "EnumTHREADWindows"...I was searching for stuff like enum - Dialog or Enum-Window or Enum-child or some way of searching.

    Seems like the more I get into SDK and API, the more my biggest 2 complaints come true.
    1. If you do not know how to "Phrase" your question, how can you get answers?
    2. When you can find out the proper "Phrase" (or close to it), then how do you actually use the samples? (for me I would rather "UNDERSTAND" than just use, but sometimes I get (frustrated...because I do not understand) or lazy till I can understand) and just reading the docs is confusing (at least to me) until I see a sample, and compare it to the doc when the bulb goes off....and I go ... When the doc says this...it really means "My understanding"....How come I could not see that before....now its easy

    Anyways, thank you...I have a bit of googling to do and a ton to search on in PB to get it, but at least I know what to look for.

    Leave a comment:


  • Michael Mattias
    replied
    EnumThreadWindows

    Leave a comment:


  • Dominic Mitchell
    replied
    Is there a way to find the handles to all the "Dialog/Windows" within the main process (exe) so each piece can become aware of the other pieces? (The closest thing I can find is EnumWindows, but that assumes you know the values you are looking for? unless I mis-read)
    Sure you can, and it is very easy to do. Assign a window property to each window. The name of the property could be the human readable form of a guid which you just simply check for when enumerating.

    Leave a comment:


  • Cliff Nichols
    started a topic Exe Dll Windows-Dialogs Is this possible?

    Exe Dll Windows-Dialogs Is this possible?

    For the sake of argument, consider "Window" and "Dialog" as being the same thing.

    Now I know each DLL becomes part of the parent process as if it were an Inc in my main executable (except done at run time instead of code time).

    Now lets say each DLL has at least one "Dialog/Window" in it (if not more) and each Dll or the main exe itself does not have code that knows about the handle to the others "Dialog/Window".

    Is there a way to find the handles to all the "Dialog/Windows" within the main process (exe) so each piece can become aware of the other pieces? (The closest thing I can find is EnumWindows, but that assumes you know the values you are looking for? unless I mis-read)

    I am hoping no matter the 1st Dll, 2nd....or 2000th, and the parent can each locate any "Dialog/Window" within the running process, and interact/monitor each other, but the wall I am hitting is is this possible? and to a further extent possible to know DialogExe belongs to the parent process(exe) DialogDll1 belongs to DLL1, and DialogDll2 belongs to Dll2?

    A poor example of part of my thoughts below

    DLL1
    Code:
    #COMPILE DLL
    #DIM ALL
    
    %USEMACROS = 1
    #INCLUDE "Win32API.inc"
    #INCLUDE "FileFolder.inc"
    #INCLUDE "SoftwareInfo.inc"
    GLOBAL ghInstance AS DWORD
    
    DECLARE FUNCTION Load2 LIB "Dll2.dll" ALIAS "Load2"() AS LONG
    
    '-------------------------------------------------------------------------------
    ' Main DLL entry point called by Windows...
    '
    FUNCTION LIBMAIN (BYVAL hInstance   AS LONG, _
                      BYVAL fwdReason   AS LONG, _
                      BYVAL lpvReserved AS LONG) AS LONG
    
        SELECT CASE fwdReason
    
        CASE %DLL_PROCESS_ATTACH
            'Indicates that the DLL is being loaded by another process (a DLL
            'or EXE is loading the DLL).  DLLs can use this opportunity to
            'initialize any instance or global data, such as arrays.
    MSGBOX "Process Attached to DLL 1"
            ghInstance = hInstance
    
            FUNCTION = 1   'success!
    
            'FUNCTION = 0   'failure!  This will prevent the EXE from running.
    
        CASE %DLL_PROCESS_DETACH
            'Indicates that the DLL is being unloaded or detached from the
            'calling application.  DLLs can take this opportunity to clean
            'up all resources for all threads attached and known to the DLL.
    MSGBOX "Process Detach to DLL 1"
    
            FUNCTION = 1   'success!
    
            'FUNCTION = 0   'failure!
    
        CASE %DLL_THREAD_ATTACH
            'Indicates that the DLL is being loaded by a new thread in the
            'calling application.  DLLs can use this opportunity to
            'initialize any thread local storage (TLS).
    
            FUNCTION = 1   'success!
    
            'FUNCTION = 0   'failure!
    
        CASE %DLL_THREAD_DETACH
            'Indicates that the thread is exiting cleanly.  If the DLL has
            'allocated any thread local storage, it should be released.
    
            FUNCTION = 1   'success!
    
            'FUNCTION = 0   'failure!
    
        END SELECT
    
    END FUNCTION
    
    FUNCTION Load1 ALIAS "Load1"() EXPORT AS LONG
         LOCAL ParentPathAndName AS ASCIIZ * %MAX_PATH
         LOCAL ParentModule AS DWORD
         ParentPathAndName = GetSoftwareParentPath + GetSoftwareParentPathName
         REPLACE "/" WITH "\" IN ParentPathAndName
         ParentModule = GetModuleHandle(ParentPathAndName)
         MSGBOX FUNCNAME$ + " was loaded into " + ParentPathAndName + $CR + "at " + STR$(ParentModule)
         Load2
        LOCAL lRslt AS LONG
        LOCAL hDlg  AS DWORD
        DIALOG NEW %HWND_DESKTOP, "Dialog1", 217, 226, 201, 121, %WS_SYSMENU TO hDlg
        DIALOG SHOW MODAL hDlg
        FUNCTION = lRslt
    END FUNCTION
    DLL2
    Code:
    #COMPILE DLL
    #DIM ALL
    
    %USEMACROS = 1
    #INCLUDE "Win32API.inc"
    #INCLUDE "FileFolder.inc"
    #INCLUDE "SoftwareInfo.inc"
    GLOBAL ghInstance AS DWORD
    
    '-------------------------------------------------------------------------------
    ' Main DLL entry point called by Windows...
    '
    FUNCTION LIBMAIN (BYVAL hInstance   AS LONG, _
                      BYVAL fwdReason   AS LONG, _
                      BYVAL lpvReserved AS LONG) AS LONG
    
        SELECT CASE fwdReason
    
        CASE %DLL_PROCESS_ATTACH
            'Indicates that the DLL is being loaded by another process (a DLL
            'or EXE is loading the DLL).  DLLs can use this opportunity to
            'initialize any instance or global data, such as arrays.
    MSGBOX "Process Attached to DLL 2"
            ghInstance = hInstance
    
            FUNCTION = 1   'success!
    
            'FUNCTION = 0   'failure!  This will prevent the EXE from running.
    
        CASE %DLL_PROCESS_DETACH
            'Indicates that the DLL is being unloaded or detached from the
            'calling application.  DLLs can take this opportunity to clean
            'up all resources for all threads attached and known to the DLL.
    MSGBOX "Process Detach to DLL 2"
    
            FUNCTION = 1   'success!
    
            'FUNCTION = 0   'failure!
    
        CASE %DLL_THREAD_ATTACH
            'Indicates that the DLL is being loaded by a new thread in the
            'calling application.  DLLs can use this opportunity to
            'initialize any thread local storage (TLS).
    
            FUNCTION = 1   'success!
    
            'FUNCTION = 0   'failure!
    
        CASE %DLL_THREAD_DETACH
            'Indicates that the thread is exiting cleanly.  If the DLL has
            'allocated any thread local storage, it should be released.
    
            FUNCTION = 1   'success!
    
            'FUNCTION = 0   'failure!
    
        END SELECT
    
    END FUNCTION
    
    FUNCTION Load2 ALIAS "Load2"() EXPORT AS LONG
         LOCAL ParentPathAndName AS ASCIIZ * %MAX_PATH
         LOCAL ParentModule AS DWORD
         ParentPathAndName = GetSoftwareParentPath + GetSoftwareParentPathName
         REPLACE "/" WITH "\" IN ParentPathAndName
         ParentModule = GetModuleHandle(ParentPathAndName)
         MSGBOX FUNCNAME$ + " was loaded into " + ParentPathAndName + $CR + "at " + STR$(ParentModule)
        LOCAL lRslt AS LONG
        LOCAL hDlg  AS DWORD
        DIALOG NEW %HWND_DESKTOP, "Dialog2", 217, 226, 201, 121, %WS_SYSMENU TO hDlg
        DIALOG SHOW MODAL hDlg
        FUNCTION = lRslt
    END FUNCTION
    EXE
    Code:
    #COMPILE EXE
    #DIM ALL
    #INCLUDE "Win32Api.inc"
    
    DECLARE FUNCTION Load1 LIB "Dll1.dll" ALIAS "Load1"() AS LONG
    FUNCTION PBMAIN () AS LONG
    
         Load1
    
    END FUNCTION
    Support Inc files (not a point of the question)
    FileFolder.Inc
    Code:
    DECLARE FUNCTION FileExist(BYVAL sfName AS STRING) AS LONG
    DECLARE FUNCTION FileNam (BYVAL Src AS STRING) AS STRING
    DECLARE FUNCTION FilePath (BYVAL Src AS STRING) AS STRING
    
    DECLARE FUNCTION OpenThisFile(BYVAL fn AS STRING) AS DWORD
    DECLARE SUB SaveFile (BYVAL Ask AS LONG)
    DECLARE SUB WriteRecentFiles (BYVAL OpenFName AS STRING)
    
    DECLARE FUNCTION FSO_AppPath()AS STRING
    DECLARE FUNCTION FSO_AppName()AS STRING
    DECLARE FUNCTION FSO_AppIniFile()AS STRING
    
    '------------------------------------------------------------------------------
    ' FileExist - make sure a file or folder exists
    '------------------------------------------------------------------------------
    FUNCTION FileExist(BYVAL sfName AS STRING) AS LONG
        ON ERROR GOTO ErrHandler
      LOCAL hRes AS DWORD, tWFD AS WIN32_FIND_DATA
    
      IF LEN(sfName) = 0 THEN EXIT FUNCTION       'no need to continue then..
      IF ASC(sfName, -1) = 92 THEN                'if a path with trailing backslash
         sfName = LEFT$(sfName, LEN(sfName) - 1)  'remove trailing backslash
      END IF
    
      hRes = FindFirstFile(BYVAL STRPTR(sfName), tWFD)
      IF hRes <> %INVALID_HANDLE_VALUE THEN
         FUNCTION = %TRUE
         FindClose hRes
      END IF
        EXIT FUNCTION
    ErrHandler:
    '    StartTrace
    '    ErrorCheck ERR
    '    EndTrace
    END FUNCTION
    
    '------------------------------------------------------------------------------
    ' Get file name part of given path & name
    '------------------------------------------------------------------------------
    FUNCTION FileNam (BYVAL Src AS STRING) AS STRING
        ON ERROR GOTO ErrHandler
      LOCAL x AS LONG
    
      x = INSTR(-1, Src, ANY ":/\")
      IF x THEN
          FUNCTION = MID$(Src, x + 1)
      ELSE
          FUNCTION = Src
      END IF
    
        EXIT FUNCTION
    ErrHandler:
    '    StartTrace
    '    ErrorCheck ERR
    '    EndTrace
    END FUNCTION
    
    '------------------------------------------------------------------------------
    ' Get path -part of given path & name
    '------------------------------------------------------------------------------
    FUNCTION FilePath (BYVAL Src AS STRING) AS STRING
        ON ERROR GOTO ErrHandler
      LOCAL x AS LONG
    
      x = INSTR(-1, Src, ANY ":\/")
      IF x THEN FUNCTION = LEFT$(Src, x)
    
        EXIT FUNCTION
    ErrHandler:
    '    StartTrace
    '    ErrorCheck ERR
    '    EndTrace
    END FUNCTION
    
    ''------------------------------------------------------------------------------
    '' Open file procedure
    ''------------------------------------------------------------------------------
    'FUNCTION OpenThisFile(BYVAL fn AS STRING) AS DWORD
    '    ON ERROR GOTO ErrHandler
    '  LOCAL hMdi AS DWORD, zText AS ASCIIZ * %MAX_PATH
    '
    '  hMdi = GetWindow(hWndClient, %GW_CHILD) 'first look at already opened docs
    '  WHILE hMdi
    '     GetWindowText hMdi, zText, %MAX_PATH
    '     IF UCASE$(zText) = UCASE$(fn) THEN                   'if already opened
    '        SendMessage hWndClient, %WM_MDIACTIVATE, hMdi, 0  'activate it
    ''        WriteRecentFiles fn                               'update MRU menu and exit
    '        EXIT FUNCTION
    '     END IF
    '     hMdi = GetWindow(hMdi, %GW_HWNDNEXT)
    '  WEND
    '  '------------------------------------------------------------------------------
    ''*** Determine if data is for edit or Terminal
    ''msgbox zText + $cr + fn
    ''    SELECT CASE zText
    ''        CASE "Terminal"
    ''            CONTROL sET TEXT HwndDlgTerminalSimple&, %TxtSend, fn
    ''        case else
    '          IF MdiGetActive(hWndClient) AND _      'if not first doc and docs are maximized
    '             IsZoomed(MdiGetActive(hWndClient)) THEN freezeMenu = 1 'turn off menu redraw
    '             hMdi = CreateMdiChild("PBNOTE32", hWndClient, fn, %SW_SHOWNORMAL)   '%WS_MAXIMIZE
    '
    '          IF freezeMenu THEN       'if menu redraw was turned off
    '             freezeMenu = 0        'reset flag
    '             DrawMenuBar hWndMain  'and redraw menu
    '          END IF
    ''    end select
    '  FUNCTION = hMdi
    '    EXIT FUNCTION
    'ErrHandler:
    ''    StartTrace
    ''    ErrorCheck ERR
    ''    EndTrace
    'END FUNCTION
    
    ''------------------------------------------------------------------------------
    '' Save as -procedure
    ''------------------------------------------------------------------------------
    'SUB SaveFile (BYVAL Ask AS LONG)
    '    ON ERROR GOTO ErrHandler
    '  LOCAL STYLE  AS DWORD
    '  LOCAL nFile  AS DWORD
    '  LOCAL Path   AS STRING
    '  LOCAL f      AS STRING
    '  LOCAL Buffer AS STRING
    '  LOCAL zText  AS ASCIIZ * %MAX_PATH
    '
    '  GetWindowText MdiGetActive(hWndClient), zText, SIZEOF(zText)
    '
    '  IF INSTR(zText, ANY ":\/") = 0 THEN 'if no path, it's a new doc
    '      Path = CURDIR$
    '      IF RIGHT$(Path, 1) <> "\" THEN Path = Path + "\"
    '      f    = zText & ".txt"  'suggest this name
    '      Ask  = %TRUE           'we need the dialog for new docs
    '  ELSE
    '      Path = FilePath(zText)
    '      f    = FileNam(zText)
    '  END IF
    '  STYLE = %OFN_HIDEREADONLY OR %OFN_LONGNAMES
    '
    '  IF Ask THEN
    '     IF SaveFileDialog(hWndMain, "", f, Path, _
    '        "COSMOS Files (*.TXT, *.VEL)|*.txt;*.vel|All Files|*.*", "", STYLE) = 0 THEN EXIT SUB
    '  ELSE
    '     f = Path & f
    '  END IF
    ''*** if no extension then default to txt file
    '    SELECT CASE UCASE$(RIGHT$(f,4))
    '        CASE ".TXT", ".VEL"
    '        CASE ELSE
    '            f = f + ".txt"
    '    END SELECT
    '  nFile = FREEFILE  'time to save the file
    ''*** Determine if data is from edit or Terminal
    '    SELECT CASE zText
    '        CASE "Terminal"
    '            DIM TerminalText AS STRING
    '            CONTROL GET TEXT HwndDlgTerminalSimple&, %TxtSend TO TerminalText
    '            OPEN f FOR OUTPUT AS nFile
    ''MSGBOX f + $CR + TerminalText
    '                PRINT #nFile, TerminalText
    '            CLOSE #nFile
    '        CASE ELSE
    '          OPEN f FOR BINARY AS nFile
    '             IF ERR THEN  'if something went wrong
    '                BEEP      'we should flash a message, but..
    '                EXIT SUB
    '             END IF
    '             Buffer = SPACE$(GetWindowTextLength(GetEdit) + 1)
    '             GetWindowText GetEdit, BYVAL STRPTR(Buffer), LEN(Buffer)
    '             PUT$ nFile, LEFT$(Buffer, LEN(Buffer) - 1)
    '             SETEOF nFile
    '          CLOSE nFile
    '    END SELECT
    '
    '  IF Ask THEN 'if dialog, update caption in case name was changed
    '      SELECT CASE zText
    '          CASE "Terminal"
    '          CASE ELSE
    '            SetWindowText MdiGetActive(hWndClient), BYVAL STRPTR(f)
    '      END SELECT
    '  END IF
    '  SendMessage GetEdit, %EM_SETMODIFY, 0, 0
    ''  WriteRecentFiles f   'finally, update reopen file list (MRU menu)
    '
    '    EXIT SUB
    'ErrHandler:
    ''    StartTrace
    ''    ErrorCheck ERR
    ''    EndTrace
    'END SUB
    '
    ''------------------------------------------------------------------------------
    '' Save the list of recently opened files
    ''------------------------------------------------------------------------------
    'SUB WriteRecentFiles (BYVAL OpenFName AS STRING)
    '    ON ERROR GOTO ErrHandler
    '  LOCAL Ac AS LONG, dwRes AS DWORD, zText AS ASCIIZ * %MAX_PATH
    '  LOCAL zSection AS ASCIIZ * 30, zKey AS ASCIIZ * 30, zDefault AS ASCIIZ * 30
    '
    '  DIM IniName(1 : 8) AS STRING
    '  zSection = "Reopen files"
    '
    '  FOR Ac = 1 TO 8
    '     zKey = "File " & FORMAT$(Ac)
    '     dwRes = GetPrivateProfileString(zSection, zKey, zDefault, zText, %MAX_PATH, iniFile)
    '     IF dwRes THEN IniName(Ac) = LEFT$(zText, dwRes)
    '  NEXT Ac
    '
    '  Ac = 0
    '  ARRAY SCAN IniName(), COLLATE UCASE, = UCASE$(OpenFName), TO Ac
    '  IF Ac THEN ARRAY DELETE IniName(Ac)
    '  ARRAY INSERT IniName(), OpenFName
    '
    '  FOR Ac = 1 TO 8
    '     IF LEN(IniName(Ac)) THEN
    '        zKey   = "File " & FORMAT$(Ac)
    '        zText = IniName(Ac)
    '        WritePrivateProfileString zSection, zKey, zText, iniFile
    '     END IF
    '  NEXT Ac
    '
    '  GetRecentFiles 'update MRU menu
    '
    '    EXIT SUB
    'ErrHandler:
    ''    StartTrace
    ''    ErrorCheck ERR
    ''    EndTrace
    'END SUB
    
    
    FUNCTION FSO_AppPath()EXPORT AS STRING
        ON ERROR GOTO ErrHandler
        LOCAL l&,Buffer$
        Buffer$=SPACE$(500)
        L& = GetModuleFileName(%NULL, BYVAL STRPTR(Buffer$), BYVAL LEN(Buffer$))
        IF L& = 0 THEN FUNCTION = "":EXIT FUNCTION
        FUNCTION = LEFT$(Buffer$,INSTR(-1,Buffer$,"\"))
        EXIT FUNCTION
    ErrHandler:
    '    StartTrace
    '    ErrorCheck ERR
    '    EndTrace
    END FUNCTION
    
    FUNCTION FSO_AppName()EXPORT AS STRING
        ON ERROR GOTO ErrHandler
        LOCAL l&,Buffer$
        Buffer$=SPACE$(500)
        L& = GetModuleFileName(%NULL, BYVAL STRPTR(Buffer$), BYVAL LEN(Buffer$))
        IF L& = 0 THEN FUNCTION = "":EXIT FUNCTION
        Buffer$=LEFT$(Buffer$,L&)
        FUNCTION = MID$(Buffer$,INSTR(-1,Buffer$,"\")+1)
        EXIT FUNCTION
    ErrHandler:
    '    StartTrace
    '    ErrorCheck ERR
    '    EndTrace
    END FUNCTION
    
    FUNCTION FSO_AppIniFile()EXPORT AS STRING
        ON ERROR GOTO ErrHandler
        LOCAL l&,Buffer$
        Buffer$=SPACE$(500)
        L& = GetModuleFileName(%NULL, BYVAL STRPTR(Buffer$), BYVAL LEN(Buffer$))
        IF L& = 0 THEN FUNCTION = "":EXIT FUNCTION
        Buffer$=LEFT$(Buffer$,L&)
        FUNCTION = LEFT$(Buffer$,INSTR(-1,Buffer$,".")) & "INI"
        EXIT FUNCTION
    ErrHandler:
    '    StartTrace
    '    ErrorCheck ERR
    '    EndTrace
    END FUNCTION
    SoftwareInfo.Inc
    Code:
    DECLARE FUNCTION GetSoftwarePath ALIAS "GetSoftwarePath"() AS STRING
    DECLARE FUNCTION GetSoftwarePathName ALIAS "GetSoftwarePathName"() AS STRING
    DECLARE FUNCTION GetSoftwareParentPath ALIAS "GetSoftwareParentPath"() AS STRING
    DECLARE FUNCTION GetSoftwareParentPathName ALIAS "GetSoftwareParentPathName"() AS STRING
    
    DECLARE FUNCTION GetSoftwareCompanyName ALIAS "GetSoftwareCompanyName"() AS STRING
    DECLARE FUNCTION GetSoftwareFileDescription ALIAS "GetSoftwareFileDescription"() AS STRING
    DECLARE FUNCTION GetSoftwareFileVersion ALIAS "GetSoftwareFileVersion"() AS STRING
    DECLARE FUNCTION GetSoftwareInternalName ALIAS "GetSoftwareInternalName"() AS STRING
    DECLARE FUNCTION GetSoftwareOriginalFilename ALIAS "GetSoftwareOriginalFilename"() AS STRING
    DECLARE FUNCTION GetSoftwareLegalCopyright ALIAS "GetSoftwareLegalCopyright"() AS STRING
    DECLARE FUNCTION GetSoftwareProductName ALIAS "GetSoftwareProductName"() AS STRING
    DECLARE FUNCTION GetSoftwareProductVersion ALIAS "GetSoftwareProductVersion"() AS STRING
    DECLARE FUNCTION GetSoftwareComments ALIAS "GetSoftwareComments"() AS STRING
    
    
    DECLARE FUNCTION FileExist ALIAS "FileExist"(BYVAL sfName AS STRING) AS LONG
    DECLARE FUNCTION FilePath ALIAS "FilePath"(BYVAL Src AS STRING) AS STRING
    DECLARE FUNCTION FilePathName ALIAS "FilePathName"(BYVAL Src AS STRING) AS STRING
    
    GLOBAL HwndMain AS DWORD
    
    FUNCTION GetSoftwarePath ALIAS "GetSoftwarePath"()EXPORT AS STRING
         ON ERROR GOTO ErrHandler
         DIM aEXEName AS ASCIIZ * %MAX_PATH
         DIM i AS LONG
         GetModuleFileName(HwndMain, aExeName, %MAX_PATH)       'Get Exe/Dll Path and Name
         aExeName = FilePath(aExeName)
         REPLACE "\" WITH "/" IN aExeName        'Added because "\" is an escape code for RTF commands
         FUNCTION = aExeName
         EXIT FUNCTION
    ErrHandler:
    '     LogError ERR, ERROR$(ERR)
    '     RESUME NEXT             'Resume once error has been handled
    END FUNCTION
    
    FUNCTION GetSoftwarePathName ALIAS "GetSoftwarePathName"()EXPORT AS STRING
         ON ERROR GOTO ErrHandler
         DIM aEXEName AS ASCIIZ * %MAX_PATH
         DIM i AS LONG
         GetModuleFileName(HwndMain, aExeName, %MAX_PATH)       'Get Exe/Dll Path and Name
         FUNCTION = FilePathName(aExeName)
         EXIT FUNCTION
    ErrHandler:
    '     LogError ERR, ERROR$(ERR)
    '     RESUME NEXT             'Resume once error has been handled
    END FUNCTION
    
    FUNCTION GetSoftwareParentPath ALIAS "GetSoftwareParentPath"()EXPORT AS STRING
         ON ERROR GOTO ErrHandler
         DIM aEXEName AS ASCIIZ * %MAX_PATH
         DIM i AS LONG
         GetModuleFileName(BYVAL %NULL, aExeName, %MAX_PATH)       'Get Exe/Dll Path and Name
         aExeName = FilePath(aExeName)
         REPLACE "\" WITH "/" IN aExeName        'Added because "\" is an escape code for RTF commands
         FUNCTION = aExeName
         EXIT FUNCTION
    ErrHandler:
    '     LogError ERR, ERROR$(ERR)
    '     RESUME NEXT             'Resume once error has been handled
    END FUNCTION
    
    FUNCTION GetSoftwareParentPathName ALIAS "GetSoftwareParentPathName"()EXPORT AS STRING
         ON ERROR GOTO ErrHandler
         DIM aEXEName AS ASCIIZ * %MAX_PATH
         DIM i AS LONG
         GetModuleFileName(BYVAL %NULL, aExeName, %MAX_PATH)       'Get Exe/Dll Path and Name
         FUNCTION = FilePathName(aExeName)
         EXIT FUNCTION
    ErrHandler:
    '     LogError ERR, ERROR$(ERR)
    '     RESUME NEXT             'Resume once error has been handled
    END FUNCTION
    
    FUNCTION GetSoftwareCompanyName ALIAS "GetSoftwareCompanyName"()EXPORT AS STRING
         ON ERROR GOTO ErrHandler
         DIM aEXEName AS ASCIIZ * %MAX_PATH
         DIM lDummy AS LONG, lBufferLen AS LONG, i AS LONG
         DIM bBuffer() AS BYTE ,sBuffer AS STRING, pReceive AS ASCIIZ PTR ,lReceive AS LONG
    
         GetModuleFileName(HwndMain, aExeName, %MAX_PATH)       'Get Exe/Dll Path and Name
         lBufferlen = GetFileVersionInfoSize(aExeName, lDummy)
         REDIM bBuffer(lBufferlen)
         GetFileVersionInfo(aExeName, 0&, lBufferLen, bBuffer(0))
         FOR i = 0 TO lBufferlen - 1        'Setup for VerQueryValue
              sBuffer=sBuffer + CHR$(bBuffer(i))
         NEXT
         VerQueryValue(BYVAL STRPTR(sBuffer), "\StringFileInfo\040904B0\CompanyName", pReceive, lReceive) ' 040904E4
         IF pReceive THEN FUNCTION = @pReceive
         EXIT FUNCTION
    ErrHandler:
    '     LogError ERR, ERROR$(ERR)
    '     RESUME NEXT             'Resume once error has been handled
    END FUNCTION
    
    FUNCTION GetSoftwareFileDescription ALIAS "GetSoftwareFileDescription"()EXPORT AS STRING
         ON ERROR GOTO ErrHandler
         DIM aEXEName AS ASCIIZ * %MAX_PATH
         DIM lDummy AS LONG, lBufferLen AS LONG, i AS LONG
         DIM bBuffer() AS BYTE ,sBuffer AS STRING, pReceive AS ASCIIZ PTR ,lReceive AS LONG
    
         GetModuleFileName(HwndMain, aExeName, %MAX_PATH)       'Get Exe/Dll Path and Name
         lBufferlen = GetFileVersionInfoSize(aExeName, lDummy)
         REDIM bBuffer(lBufferlen)
         GetFileVersionInfo(aExeName, 0&, lBufferLen, bBuffer(0))
         FOR i = 0 TO lBufferlen - 1        'Setup for VerQueryValue
              sBuffer=sBuffer + CHR$(bBuffer(i))
         NEXT
         VerQueryValue(BYVAL STRPTR(sBuffer), "\StringFileInfo\040904B0\FileDescription", pReceive, lReceive) ' 040904E4
         IF pReceive THEN FUNCTION = @pReceive
         EXIT FUNCTION
    ErrHandler:
    '     LogError ERR, ERROR$(ERR)
    '     RESUME NEXT             'Resume once error has been handled
    END FUNCTION
    
    FUNCTION GetSoftwareFileVersion ALIAS "GetSoftwareFileVersion"()EXPORT AS STRING
         ON ERROR GOTO ErrHandler
         DIM aEXEName AS ASCIIZ * %MAX_PATH
         DIM lDummy AS LONG, lBufferLen AS LONG, i AS LONG
         DIM bBuffer() AS BYTE ,sBuffer AS STRING, pReceive AS ASCIIZ PTR ,lReceive AS LONG
    
         GetModuleFileName(HwndMain, aExeName, %MAX_PATH)       'Get Exe/Dll Path and Name
         lBufferlen = GetFileVersionInfoSize(aExeName, lDummy)
         REDIM bBuffer(lBufferlen)
         GetFileVersionInfo(aExeName, 0&, lBufferLen, bBuffer(0))
         FOR i = 0 TO lBufferlen - 1        'Setup for VerQueryValue
              sBuffer=sBuffer + CHR$(bBuffer(i))
         NEXT
         VerQueryValue(BYVAL STRPTR(sBuffer), "\StringFileInfo\040904B0\FileVersion", pReceive, lReceive) ' 040904E4
         IF pReceive THEN FUNCTION = @pReceive
         EXIT FUNCTION
    ErrHandler:
    '     LogError ERR, ERROR$(ERR)
    '     RESUME NEXT             'Resume once error has been handled
    END FUNCTION
    
    FUNCTION GetSoftwareInternalName ALIAS "GetSoftwareInternalName"()EXPORT AS STRING
         ON ERROR GOTO ErrHandler
         DIM aEXEName AS ASCIIZ * %MAX_PATH
         DIM lDummy AS LONG, lBufferLen AS LONG, i AS LONG
         DIM bBuffer() AS BYTE ,sBuffer AS STRING, pReceive AS ASCIIZ PTR ,lReceive AS LONG
    
         GetModuleFileName(HwndMain, aExeName, %MAX_PATH)       'Get Exe/Dll Path and Name
         lBufferlen = GetFileVersionInfoSize(aExeName, lDummy)
         REDIM bBuffer(lBufferlen)
         GetFileVersionInfo(aExeName, 0&, lBufferLen, bBuffer(0))
         FOR i = 0 TO lBufferlen - 1        'Setup for VerQueryValue
              sBuffer=sBuffer + CHR$(bBuffer(i))
         NEXT
         VerQueryValue(BYVAL STRPTR(sBuffer), "\StringFileInfo\040904B0\InternalName", pReceive, lReceive) ' 040904E4
         IF pReceive THEN FUNCTION = @pReceive
         EXIT FUNCTION
    ErrHandler:
    '     LogError ERR, ERROR$(ERR)
    '     RESUME NEXT             'Resume once error has been handled
    END FUNCTION
    
    FUNCTION GetSoftwareOriginalFilename ALIAS "GetSoftwareOriginalFilename"()EXPORT AS STRING
         ON ERROR GOTO ErrHandler
         DIM aEXEName AS ASCIIZ * %MAX_PATH
         DIM lDummy AS LONG, lBufferLen AS LONG, i AS LONG
         DIM bBuffer() AS BYTE ,sBuffer AS STRING, pReceive AS ASCIIZ PTR ,lReceive AS LONG
    
         GetModuleFileName(HwndMain, aExeName, %MAX_PATH)       'Get Exe/Dll Path and Name
         lBufferlen = GetFileVersionInfoSize(aExeName, lDummy)
         REDIM bBuffer(lBufferlen)
         GetFileVersionInfo(aExeName, 0&, lBufferLen, bBuffer(0))
         FOR i = 0 TO lBufferlen - 1        'Setup for VerQueryValue
              sBuffer=sBuffer + CHR$(bBuffer(i))
         NEXT
         VerQueryValue(BYVAL STRPTR(sBuffer), "\StringFileInfo\040904B0\OriginalFilename", pReceive, lReceive) ' 040904E4
         IF pReceive THEN FUNCTION = @pReceive
         EXIT FUNCTION
    ErrHandler:
    '     LogError ERR, ERROR$(ERR)
    '     RESUME NEXT             'Resume once error has been handled
    END FUNCTION
    
    
    FUNCTION GetSoftwareLegalCopyright ALIAS "GetSoftwareLegalCopyright"()EXPORT AS STRING
         ON ERROR GOTO ErrHandler
         DIM aEXEName AS ASCIIZ * %MAX_PATH
         DIM lDummy AS LONG, lBufferLen AS LONG, i AS LONG
         DIM bBuffer() AS BYTE ,sBuffer AS STRING, pReceive AS ASCIIZ PTR ,lReceive AS LONG
    
         GetModuleFileName(HwndMain, aExeName, %MAX_PATH)       'Get Exe/Dll Path and Name
         lBufferlen = GetFileVersionInfoSize(aExeName, lDummy)
         REDIM bBuffer(lBufferlen)
         GetFileVersionInfo(aExeName, 0&, lBufferLen, bBuffer(0))
         FOR i = 0 TO lBufferlen - 1        'Setup for VerQueryValue
              sBuffer=sBuffer + CHR$(bBuffer(i))
         NEXT
         VerQueryValue(BYVAL STRPTR(sBuffer), "\StringFileInfo\040904B0\LegalCopyright", pReceive, lReceive) ' 040904E4
         IF pReceive THEN FUNCTION = @pReceive
         EXIT FUNCTION
    ErrHandler:
    '     LogError ERR, ERROR$(ERR)
    '     RESUME NEXT             'Resume once error has been handled
    END FUNCTION
    
    FUNCTION GetSoftwareProductName ALIAS "GetSoftwareProductName"()EXPORT AS STRING
         ON ERROR GOTO ErrHandler
         DIM aEXEName AS ASCIIZ * %MAX_PATH
         DIM lDummy AS LONG, lBufferLen AS LONG, i AS LONG
         DIM bBuffer() AS BYTE ,sBuffer AS STRING, pReceive AS ASCIIZ PTR ,lReceive AS LONG
    
         GetModuleFileName(HwndMain, aExeName, %MAX_PATH)       'Get Exe/Dll Path and Name
         lBufferlen = GetFileVersionInfoSize(aExeName, lDummy)
         REDIM bBuffer(lBufferlen)
         GetFileVersionInfo(aExeName, 0&, lBufferLen, bBuffer(0))
         FOR i = 0 TO lBufferlen - 1        'Setup for VerQueryValue
              sBuffer=sBuffer + CHR$(bBuffer(i))
         NEXT
         VerQueryValue(BYVAL STRPTR(sBuffer), "\StringFileInfo\040904B0\ProductName", pReceive, lReceive) ' 040904E4
         IF pReceive THEN FUNCTION = @pReceive
         EXIT FUNCTION
    ErrHandler:
    '     LogError ERR, ERROR$(ERR)
    '     RESUME NEXT             'Resume once error has been handled
    END FUNCTION
    
    FUNCTION GetSoftwareProductVersion ALIAS "GetSoftwareProductVersion"()EXPORT AS STRING
         ON ERROR GOTO ErrHandler
         DIM aEXEName AS ASCIIZ * %MAX_PATH
         DIM lDummy AS LONG, lBufferLen AS LONG, i AS LONG
         DIM bBuffer() AS BYTE ,sBuffer AS STRING, pReceive AS ASCIIZ PTR ,lReceive AS LONG
    
         GetModuleFileName(HwndMain, aExeName, %MAX_PATH)       'Get Exe/Dll Path and Name
         lBufferlen = GetFileVersionInfoSize(aExeName, lDummy)
         REDIM bBuffer(lBufferlen)
         GetFileVersionInfo(aExeName, 0&, lBufferLen, bBuffer(0))
         FOR i = 0 TO lBufferlen - 1        'Setup for VerQueryValue
              sBuffer=sBuffer + CHR$(bBuffer(i))
         NEXT
         VerQueryValue(BYVAL STRPTR(sBuffer), "\StringFileInfo\040904B0\ProductVersion", pReceive, lReceive) ' 040904E4
         IF pReceive THEN FUNCTION = @pReceive
         EXIT FUNCTION
    ErrHandler:
    '     LogError ERR, ERROR$(ERR)
    '     RESUME NEXT             'Resume once error has been handled
    END FUNCTION
    
    FUNCTION GetSoftwareComments ALIAS "GetSoftwareComments"()EXPORT AS STRING
         ON ERROR GOTO ErrHandler
         DIM aEXEName AS ASCIIZ * %MAX_PATH
         DIM lDummy AS LONG, lBufferLen AS LONG, i AS LONG
         DIM bBuffer() AS BYTE ,sBuffer AS STRING, pReceive AS ASCIIZ PTR ,lReceive AS LONG
    
         GetModuleFileName(HwndMain, aExeName, %MAX_PATH)       'Get Exe/Dll Path and Name
         lBufferlen = GetFileVersionInfoSize(aExeName, lDummy)
         REDIM bBuffer(lBufferlen)
         GetFileVersionInfo(aExeName, 0&, lBufferLen, bBuffer(0))
         FOR i = 0 TO lBufferlen - 1        'Setup for VerQueryValue
              sBuffer=sBuffer + CHR$(bBuffer(i))
         NEXT
         VerQueryValue(BYVAL STRPTR(sBuffer), "\StringFileInfo\040904B0\Comments", pReceive, lReceive) ' 040904E4
         IF pReceive THEN FUNCTION = @pReceive
         EXIT FUNCTION
    ErrHandler:
    '     LogError ERR, ERROR$(ERR)
    '     RESUME NEXT             'Resume once error has been handled
    END FUNCTION
    
    
    '------------------------------------------------------------------------------
    ' FileExist - make sure a file or folder exists
    '------------------------------------------------------------------------------
    'FUNCTION FileExist ALIAS "FileExist"(BYVAL sfName AS STRING) EXPORT AS LONG
    '    ON ERROR GOTO ErrHandler
    '  LOCAL hRes AS DWORD, tWFD AS WIN32_FIND_DATA
    '
    '  IF LEN(sfName) = 0 THEN EXIT FUNCTION       'no need to continue then..
    '  IF ASC(sfName, -1) = 92 THEN                'if a path with trailing backslash
    '     sfName = LEFT$(sfName, LEN(sfName) - 1)  'remove trailing backslash
    '  END IF
    '
    '  hRes = FindFirstFile(BYVAL STRPTR(sfName), tWFD)
    '  IF hRes <> %INVALID_HANDLE_VALUE THEN
    '     FUNCTION = %TRUE
    '     FindClose hRes
    '  END IF
    '    EXIT FUNCTION
    'ErrHandler:
    ''     LogError ERR, ERROR$(ERR)
    ''     RESUME NEXT             'Resume once error has been handled
    'END FUNCTION
    '
    '------------------------------------------------------------------------------
    ' Get path -part of given path & name
    '------------------------------------------------------------------------------
    'FUNCTION FilePath ALIAS "FilePath"(BYVAL Src AS STRING) EXPORT AS STRING
    '     ON ERROR GOTO ErrHandler
    '     LOCAL x AS LONG
    '
    '     x = INSTR(-1, Src, ANY ":\/")
    '     IF x THEN FUNCTION = LEFT$(Src, x)
    '
    '     EXIT FUNCTION
    'ErrHandler:
    ''     LogError ERR, ERROR$(ERR)
    ''     RESUME NEXT             'Resume once error has been handled
    'END FUNCTION
    
    '------------------------------------------------------------------------------
    ' Get file name part of given path & name
    '------------------------------------------------------------------------------
    FUNCTION FilePathName ALIAS "FilePathName"(BYVAL Src AS STRING) EXPORT AS STRING
         ON ERROR GOTO ErrHandler
         LOCAL x AS LONG
    
         x = INSTR(-1, Src, ANY ":/\")
         IF x THEN
              FUNCTION = MID$(Src, x + 1)
         ELSE
              FUNCTION = Src
         END IF
    
        EXIT FUNCTION
    ErrHandler:
    '     LogError ERR, ERROR$(ERR)
    '     RESUME NEXT             'Resume once error has been handled
    END FUNCTION
    Hopefully someone gets what I am after, and a idea how to do it?
Working...
X