Results 1 to 17 of 17

Thread: VB6 - Program Communication

  1. #1

    Thread Starter
    Frenzied Member
    Join Date
    Dec 2012
    Posts
    1,477

    VB6 - Program Communication

    There are numerous examples of SendMessage useage, and this is my version of communication between 2 programs. The basics came from "www.TheScarms.com", and were adapted to provide a way to issue instructions from one program to another, and pass the results back. The use of a data structure
    Code:
    Private Type COPYDATASTRUCT
        dwData As Long   ' Use this to identify your message
        cbData As Long   ' Number of bytes to be transferred
        lpData As Long   ' Address of data
    End Type
    provides the ability to identify different types of messages. In this example, I have used the type identifier to distinguish between integer, long, and string variables, but it could be used to identify anything.

    J.A. Coutts
    Attached Files Attached Files

  2. #2
    VB-aholic & Lovin' It LaVolpe's Avatar
    Join Date
    Oct 2007
    Location
    Beside Waldo
    Posts
    19,541

    Re: VB6 - Program Communication

    Here's the MSDN link for WM_COPYDATA used in your examples. It could be helpful for others to read the remarks and comments section in that link.

    One thing that was mentioned in that link is that both applications must be running in the same elevation in order to talk to each other. For example, if one is running as Admin while the other is not, one of the apps won't be able to talk, just listen. You might want to try to verify this with compiled test apps?
    Insomnia is just a byproduct of, "It can't be done"

    Classics Enthusiast? Here's my 1969 Mustang Mach I Fastback. Her sister '67 Coupe has been adopted

    Newbie? Novice? Bored? Spend a few minutes browsing the FAQ section of the forum.
    Read the HitchHiker's Guide to Getting Help on the Forums.
    Here is the list of TAGs you can use to format your posts
    Here are VB6 Help Files online


    {Alpha Image Control} {Memory Leak FAQ} {Unicode Open/Save Dialog} {Resource Image Viewer/Extractor}
    {VB and DPI Tutorial} {Manifest Creator} {UserControl Button Template} {stdPicture Render Usage}

  3. #3

    Thread Starter
    Frenzied Member
    Join Date
    Dec 2012
    Posts
    1,477

    Re: VB6 - Program Communication

    Thanks for the info LaVolpe, but let me explain what I am trying to do. One small program will run all the time and do all the Internet communications. A second program will do all the database work and send requests to the first program to forward information to a server. The second program needs to know if the Internet actions were successful or if there was an error.

    J.A. Coutts

  4. #4
    PowerPoster
    Join Date
    Sep 2012
    Posts
    2,083

    Re: VB6 - Program Communication

    Quote Originally Posted by couttsj View Post
    Thanks for the info LaVolpe, but let me explain what I am trying to do. One small program will run all the time and do all the Internet communications. A second program will do all the database work and send requests to the first program to forward information to a server. The second program needs to know if the Internet actions were successful or if there was an error.

    J.A. Coutts
    Hi couttsj, could you give an example of the Internet and the database?

  5. #5
    VB-aholic & Lovin' It LaVolpe's Avatar
    Join Date
    Oct 2007
    Location
    Beside Waldo
    Posts
    19,541

    Re: VB6 - Program Communication

    Quote Originally Posted by couttsj View Post
    Thanks for the info LaVolpe, but let me explain what I am trying to do. One small program will run all the time and do all the Internet communications. A second program will do all the database work and send requests to the first program to forward information to a server. The second program needs to know if the Internet actions were successful or if there was an error.
    The bolded part is why I suggested testing. Run one compiled app as Admin and the other not as Admin. Will the communication still work both ways?

    Edited: Wasn't hard to test this. Failed if one or the other app was run at a different elevation level. The higher elevation could send but not receive from lower elevated apps. The lower elevated one could receive from higher elevated apps, but not send to them.
    Last edited by LaVolpe; Sep 13th, 2017 at 08:02 AM.
    Insomnia is just a byproduct of, "It can't be done"

    Classics Enthusiast? Here's my 1969 Mustang Mach I Fastback. Her sister '67 Coupe has been adopted

    Newbie? Novice? Bored? Spend a few minutes browsing the FAQ section of the forum.
    Read the HitchHiker's Guide to Getting Help on the Forums.
    Here is the list of TAGs you can use to format your posts
    Here are VB6 Help Files online


    {Alpha Image Control} {Memory Leak FAQ} {Unicode Open/Save Dialog} {Resource Image Viewer/Extractor}
    {VB and DPI Tutorial} {Manifest Creator} {UserControl Button Template} {stdPicture Render Usage}

  6. #6
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,940

    Re: VB6 - Program Communication

    Here's my ComCtl32.dll version of the same thing. I didn't give of an example of how to find the hWnd of some receiving program, but others who may want to use this can work that out.

    The piece to subclass the receiving window. This needs to be in a BAS module. The only thing Public about it is the SubclassFormToReceiveStringMsg procedure. Just call it, and your set. No need to worry about un-subclassing.

    Code:
    Option Explicit
    '
    Private Const WM_DESTROY As Long = &H2&
    '
    Private Declare Function SetWindowSubclass Lib "comctl32.dll" Alias "#410" (ByVal hWnd As Long, ByVal pfnSubclass As Long, ByVal uIdSubclass As Long, Optional ByVal dwRefData As Long) As Long
    Private Declare Function GetWindowSubclass Lib "comctl32.dll" Alias "#411" (ByVal hWnd As Long, ByVal pfnSubclass As Long, ByVal uIdSubclass As Long, pdwRefData As Long) As Long
    Private Declare Function RemoveWindowSubclass Lib "comctl32.dll" Alias "#412" (ByVal hWnd As Long, ByVal pfnSubclass As Long, ByVal uIdSubclass As Long) As Long
    Private Declare Function NextSubclassProcOnChain Lib "comctl32.dll" Alias "#413" (ByVal hWnd As Long, ByVal uMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
    'Private Declare Function DefSubclassProc Lib "comctl32.dll" Alias "#413" (ByVal hWnd As Long, ByVal uMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
    '
    Dim bSetWhenSubclassing_UsedByIdeStop As Boolean ' Never goes false once set by first subclassing, unless IDE Stop button is clicked.
    '
    Private Type POINTAPI
        x As Long
        y As Long
    End Type
    '
    Private Type MINMAXINFO
        ptReserved As POINTAPI
        ptMaxSize As POINTAPI
        ptMaxPosition As POINTAPI
        ptMinTrackSize As POINTAPI
        ptMaxTrackSize As POINTAPI
    End Type
    '
    Private Type COPYDATASTRUCT
        dwData As Long
        cbData As Long
        lpData As Long
    End Type
    '
    Private Declare Sub CopyMemory Lib "kernel32.dll" Alias "RtlMoveMemory" (ByRef Dest As Any, ByRef Source As Any, ByVal Bytes As Long)
    Private Declare Function GetMem4 Lib "msvbvm60.dll" (ByRef Source As Any, ByRef Dest As Any) As Long
    '
    
    Public Sub SubclassFormToReceiveStringMsg(frm As VB.Form)
        ' See SendStringToAnotherWindow for sending a message (which doesn't require subclassing).
        SubclassSomeWindow frm.hWnd, AddressOf StringMessage_Proc, ObjPtr(frm)
    End Sub
    
    Private Function StringMessage_Proc(ByVal hWnd As Long, ByVal uMsg As Long, ByVal wParam As Long, ByVal lParam As Long, ByVal uIdSubclass As Long, ByVal dwRefData As Long) As Long
        If uMsg = WM_DESTROY Then
            UnSubclassSomeWindow hWnd, AddressOf_StringMessage_Proc
            StringMessage_Proc = NextSubclassProcOnChain(hWnd, uMsg, wParam, lParam)
            Exit Function
        End If
        If IdeStopButtonClicked Then ' Protect the IDE.  Don't execute any specific stuff if we're stopping.  We may run into COM objects or other variables that no longer exist.
            StringMessage_Proc = NextSubclassProcOnChain(hWnd, uMsg, wParam, lParam)
            Exit Function
        End If
        '
        ' On this one, we use dwRefData to save the ObjPtr(SomeForm) of the form that is to receive the message.
        '
        ' Called as follows:
        '       SubclassSomeWindow Me.hWnd, AddressOf StringMessage_Proc, ObjPtr(Me)
        '
        ' NOTE: Best done in the Form_Load event, but doesn't really matter so long as it's done before the message is sent.
        '
        ' This can simultaneously be used by as many forms as will need it,
        ' but it can only be done once per form.
        '
        ' See SendStringToAnotherWindow for sending a message (which doesn't require subclassing).
        '
        Dim cds As COPYDATASTRUCT
        Dim Buf() As Byte
        Dim sMsg As String
        Dim frmStolen As VB.Form
        Dim frm As VB.Form
        Const WM_COPYDATA As Long = &H4A&
        '
        If uMsg = WM_COPYDATA Then
            Call CopyMemory(cds, ByVal lParam, Len(cds))
            ReDim Buf(1 To cds.cbData)
            Call CopyMemory(Buf(1), ByVal cds.lpData, cds.cbData)
            sMsg = StrConv(Buf, vbUnicode)
            sMsg = RTrimNull(sMsg)
            '
            ' Now, we can do something with the message.
            ' First, we've got to "steal" a reference to our form, using it's ObjPtr (in dwRefData).
            ' We'll create a "good" reference just to be safe.
            '
            GetMem4 dwRefData, frmStolen    ' Steal reference.
            Set frm = frmStolen             ' Make good reference.
            GetMem4 0&, frmStolen           ' Un-steal reference.
            frm.HereIsYourMessage sMsg  ' HereIsYourMessage MUST be public, or we can't find it this way.
        End If
        '
        ' Give control to other hooks, if they exist.
        StringMessage_Proc = NextSubclassProcOnChain(hWnd, uMsg, wParam, lParam)
    End Function
    
    Private Function AddressOf_StringMessage_Proc() As Long
        AddressOf_StringMessage_Proc = ProcedureAddress(AddressOf StringMessage_Proc)
    End Function
    
    Private Function RTrimNull(s As String) As String
        Dim i As Integer
        i = InStr(s, vbNullChar)
        If i Then
            RTrimNull = Left$(s, i - 1)
        Else
            RTrimNull = s
        End If
    End Function
    
    Private Sub SubclassSomeWindow(hWnd As Long, AddressOf_ProcToHook As Long, Optional dwRefData As Long)
        ' This just always uses hWnd for uIdSubclass, as we never have a need to subclass the same window to the same proc.
        ' The uniqueness is pfnSubclass and uIdSubclass (second and third argument below).
        '
        ' This can be called AFTER the initial subclassing to update dwRefData.
        '
        bSetWhenSubclassing_UsedByIdeStop = True
        Call SetWindowSubclass(hWnd, AddressOf_ProcToHook, hWnd, dwRefData)
    End Sub
    
    Private Sub UnSubclassSomeWindow(hWnd As Long, AddressOf_ProcToHook As Long)
        ' Only needed if we specifically want to un-subclass before we're closing the form (or control),
        ' otherwise, it's automatically taken care of when the window closes.
        '
        ' Be careful, some subclassing may require additional cleanup that's not done here.
        Call RemoveWindowSubclass(hWnd, AddressOf_ProcToHook, hWnd)
    End Sub
    
    Private Function ProcedureAddress(AddressOf_TheProc As Long)
        ' A private "helper" function for writing the AddressOf_... functions (see above notes).
        ProcedureAddress = AddressOf_TheProc
    End Function
    
    Private Function IdeStopButtonClicked() As Boolean
        ' The following works because all variables are cleared when the STOP button is clicked,
        ' even though other code may still execute such as Windows calling some of the subclassing procedures below.
        IdeStopButtonClicked = Not bSetWhenSubclassing_UsedByIdeStop
    End Function
    And here's the piece to send messages. It can be in a BAS module or a FRM module, doesn't matter:

    Code:
    Option Explicit
    '
    Private Type COPYDATASTRUCT
        dwData As Long
        cbData As Long
        lpData As Long
    End Type
    '
    Private Declare Sub CopyMemory Lib "kernel32.dll" Alias "RtlMoveMemory" (ByRef Dest As Any, ByRef Source As Any, ByVal Bytes As Long)
    Private Declare Function SendMessageTimeout Lib "user32" Alias "SendMessageTimeoutA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any, ByVal fuFlags As Long, ByVal uTimeout As Long, lpdwResult As Long) As Long
    '
    
    Public Sub SendStringToAnotherWindow(hWndSender As Long, hWndTarget As Long, sMsg As String)
        ' This can be used to send a message (string) to another window, possibly in another VB6 program.
        ' The other VB6 program MUST be expecting the message.  And it will need to be subclassed (i.e., hooked).
        ' See the StringMessageHook, StringMessageUnhook, and StringMessageWindowProc for details on how
        ' the receiving program must be set up.
        '
        Dim cds As COPYDATASTRUCT
        Dim lpdwResult As Long
        Dim Buf() As Byte
        Const WM_COPYDATA = &H4A
        '
        If hWndTarget Then
            ReDim Buf(1 To Len(sMsg) + 1)
            Call CopyMemory(Buf(1), ByVal sMsg, Len(sMsg)) ' Copy the string into a byte array, converting it to ASCII.
            cds.dwData = 3
            cds.cbData = Len(sMsg) + 1
            cds.lpData = VarPtr(Buf(1))
            'Call SendMessage(hWndTarget, WM_COPYDATA, Me.hwnd, cds)
            SendMessageTimeout hWndTarget, WM_COPYDATA, hWndSender, cds, 0, 5000, lpdwResult ' Return after 5 seconds even if receiver didn't acknowledge.
        End If
    End Sub
    Enjoy,
    Elroy

    EDIT1: LaVolpe's caveats probably apply to my code as well, as he's the one who gave me the original ideas on how to do this.

    EDIT2: Also, the receiving form must have a public "HereIsYourMessage" method. That's how it'll actually receive the message.
    Last edited by Elroy; Sep 12th, 2017 at 03:51 PM.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  7. #7

    Thread Starter
    Frenzied Member
    Join Date
    Dec 2012
    Posts
    1,477

    Re: VB6 - Program Communication

    Quote Originally Posted by dreammanor View Post
    Hi couttsj, could you give an example of the Internet and the database?
    This is part of a private mail system, which requires authentication and everything is encrypted. The Internet program logs into the server using a UserID and encrypted password. When two authenticated parties are connected to the server, they can communicate with each other. The purpose of the server is to provide the two parties with each other's public ECC key, so they can generate a new key. The encrypted messages are passed through the server, but the server has no knowledge of the encryption key used, and cannot decrypt the messages. Because it is using ECC, the key is different for every message. The messages themselves are stored encrypted in an Access database. The only way to read the message and the attachments is through the database program.

    I have working programs already (the Client part is currently one large program), but I need to refine them. As long as a User is logged in, he/she will remain connected to the server via the Internet part of the program. That part will receive any messages and add them to the database, and the User will be informed that a new message has arrived. Activating the database part of the program will allow the user to view those messages. To send a message, the database portion will create the message unencrypted and add it to the database. It will then send a message to the Internet portion to send the message. The Internet portion will encrypt the message, send it, and update the database with the encrypted message.

    Sorry for the long winded explanation.

    J.A. Coutts

  8. #8

    Thread Starter
    Frenzied Member
    Join Date
    Dec 2012
    Posts
    1,477

    Re: VB6 - Program Communication

    Quote Originally Posted by Elroy View Post
    Here's my ComCtl32.dll version of the same thing.
    What is the advantage of using ComCtl32.dll over user32.dll?

    J.A. Coutts

  9. #9
    PowerPoster
    Join Date
    Jun 2015
    Posts
    2,224

    Re: VB6 - Program Communication

    Quote Originally Posted by couttsj View Post
    What is the advantage of using ComCtl32.dll over user32.dll?

    J.A. Coutts
    ComCtl32.dll automatically handles out of order tear down of multiple subclasses.

  10. #10
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,940

    Re: VB6 - Program Communication

    Quote Originally Posted by couttsj View Post
    What is the advantage of using ComCtl32.dll over user32.dll?
    Also, as I did in the above code, the ComCtl32.dll can be used to store a bit of data for each subclass you do. I use this feature (above) to store a pointer to the form being subclassed to receive the messages. And then, when a message comes in, I retrieve this data which allows me to get the message to the correct form.

    Alternatively (with user32.dll), if I wish to have several forms in my application that may receive messages, I'd have to set up some kind of array that kept track of things. With ComCtl32.dll, no array needed.

    Best Regards,
    Elroy

    EDIT1: With different subclassing needs, that bit of data comes in extremely handy. For instance, I have some subclassing that changes the backcolor of the DTPicker control. And, I may do this simultaneously on several DTPickers. I just shove the backcolor into that subclassing storage, and then retrieve it when the DTPicker is setting its backcolor, and override. It's really quite nifty. Currently, none of my subclassing requires any arrays, and they're all capable of simultaneously subclassing multiple hWnds.
    Last edited by Elroy; Sep 13th, 2017 at 10:35 AM.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  11. #11
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,940

    Re: VB6 - Program Communication

    Ohhh, and yet another advantage.

    You can re-subclass and/or un-subclass as many times as you like, with no fear of inserting multiple links into the subclass chain for a particular hWnd. In other words, if you call ComCtl32.dll subclassing twice (or 100 times), no harm done. If you call user32.dll subclassing twice (for same hWnd), you've very likely just crashed (or soon will).

    Same principles hold for un-subclassing.

    Best Regards,
    Elroy

    EDIT1: Also, just as a further FYI, if you need to subclass the same hWnd twice, but for two different purposes, that's not a problem either. With ComCtl32.dll subclassing, it's the combination of the hWnd and the subclass procedure's address that make for a unique subclassing. In other words, it's not just the hWnd that defines a unique subclass occurrence.
    EDIT2: Actually, it's the combination of pfnSubclass and uIdSubclass that define a unique subclass. However, I just typically use the hWnd for uIdSubclass.
    Last edited by Elroy; Sep 13th, 2017 at 10:57 AM.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  12. #12
    Fanatic Member
    Join Date
    Aug 2013
    Posts
    806

    Re: VB6 - Program Communication

    If it's helpful, this Raymond Chen article is a great answer to the question, "What is the advantage of using ComCtl32.dll over user32.dll?"

    Do not assume that subclasses are added and removed in a purely stack-like manner. If you want to unsubclass and find that you are not the window procedure at the top of the chain you cannot safely unsubclass. You will have to leave your subclass attached until it becomes safe to unsubclass. Until that time, you just have to keep passing the messages through to the previous procedure.

    This is quite a cumbersome process, so the shell team wrote some helper functions to do all this for you. The SetWindowSubclass function does all the grunt work of installing a subclass procedure, remembering the previous one, and passing reference data to the subclass procedure you provide. You use the DefSubclassProc function to forward the message to the previous subclass procedure, and when you're done, you use the RemoveWindowSubclass function to remove yourself from the chain. RemoveWindowSubclass does all the work to do the right thing if you are not the window procedure at the top of the chain.
    Check out PhotoDemon, a pro-grade photo editor written completely in VB6. (Full source available at GitHub.)

  13. #13

    Thread Starter
    Frenzied Member
    Join Date
    Dec 2012
    Posts
    1,477

    Re: VB6 - Program Communication

    After evaluating both ComCtl32.dll and user32.dll, for my purposes I decided that the advantages of ComCtl32.dll did not outweigh the disadvantages. There were just too many problems working with ComCtl32.dll in the IDE.

    Since use of a module is required, I combined as much code as I could in a single module that could be used in multiple applications without modification. . It contains the functions used for sending the message, as well as those for receiving the message. The form doing the subclassing is passed to the module, and the received messages are passed back to the same form for processing.
    Code:
    Option Explicit
    
    Private lpPrevWndProc As Long
    
    Public Const GWL_WNDPROC = (-4)
    Public Const WM_COPYDATA = &H4A
    
    Private frmMsg As Form
    
    Public Type COPYDATASTRUCT
        dwData As Long
        cbData As Long
        lpData As Long
    End Type
    
    Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (hpvDest As Any, hpvSource As Any, ByVal cbCopy As Long)
    Private Declare Function CallWindowProc Lib "user32" Alias "CallWindowProcA" (ByVal lpPrevWndFunc As Long, ByVal hWnd As Long, ByVal Msg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
    Private Declare Function SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hWnd As Long, ByVal nIndex As Long, ByVal dwNewLong As Long) As Long
    Public Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
    Public Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) As Long
    
    Private Function MsgProc(ByVal hw As Long, ByVal uMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
        'Message callback routine called by Windows
        If uMsg = WM_COPYDATA Then Call RcvMsg(lParam)
        'Forward message to next window in chain
        MsgProc = CallWindowProc(lpPrevWndProc, hw, uMsg, wParam, lParam)
    End Function
    
    Public Sub HookMsg(frm As Form)
        'Sub class the form to trap for Windows messages.
        lpPrevWndProc = SetWindowLong(frm.hWnd, GWL_WNDPROC, AddressOf MsgProc)
        Set frmMsg = frm
    End Sub
    
    Private Sub RcvMsg(lParam As Long)
        Dim cds         As COPYDATASTRUCT
        Dim sStr        As String
        'Copy the data sent to this application into a local structure.
        Call CopyMemory(cds, ByVal lParam, Len(cds))
        sStr = String$(cds.cbData / 2, Chr$(0))
        CopyMemory ByVal StrPtr(sStr), ByVal cds.lpData, cds.cbData
        'Transfer Message & Type back to main form for processing
        Call frmMsg.ProcMsg(cds.dwData, sStr)
    End Sub
    
    Public Sub UnhookMsg(frm As Form)
        Call SetWindowLong(frm.hWnd, GWL_WNDPROC, lpPrevWndProc)
    End Sub
    Below is a generalized example of using the above module.

    Code:
    Option Explicit
    
    Const Target = "Form1"
    
    Private mPass As Form
    
    Public Sub ProcMsg(MsgType As Long, strMsg As String)
        Select Case MsgType
            Case 1
            Case 2
            Case 3
            Case 4
            Case 5
            Case Else
        End Select
    End Sub
    
    Private Sub SendData(sOut As String)
        Dim lHwnd   As Long
        Dim lLen As Long
        Dim cds     As COPYDATASTRUCT
        Dim lResult As Long
        lLen = LenB(sOut)
        If lLen = 0 Then Exit Sub
        ' Get the handle of the target application's visible window.
        lHwnd = FindWindow(vbNullString, Target)
        If lHwnd = 0 Then Exit Sub
        With cds
            .dwData = 0
            .cbData = lLen
            .lpData = StrPtr(sOut)
        End With
        ' Send the string.
        lResult = SendMessage(lHwnd, WM_COPYDATA, Me.hWnd, cds)
    End Sub
    
    Private Sub Form_Load()
        Set mPass = Me
        Call HookMsg(mPass)
    End Sub
    
    Private Sub Form_Unload(Cancel As Integer)
        Call UnhookMsg(mPass)
    End Sub
    J.A. Coutts
    Last edited by couttsj; Sep 24th, 2017 at 02:27 PM.

  14. #14
    PowerPoster
    Join Date
    Jun 2015
    Posts
    2,224

    Re: VB6 - Program Communication

    Feel free to try out my subclassing framework. It basically uses a reference implementation of the ComCtl32 subclassing. it's doing what you already do, except without the tear down issues, which means you can combine it with multiple subclassing on the same form.

    we would love to know what were any of the problems you encountered using that method. The only one I can think of is the memory leak that happens with repeated subclassing using different static MsgProc routines. (which is mitigated using a single forwarder similar to what you've shown)
    CTRansData.cls
    Code:
    Option Explicit
    
    Public Event Receive(ByVal MsgType As Long, ByRef Message As String, ByVal hWndSrc As Long)
    
    Private Enum API
        [False]
        [True]
    End Enum
    Private Type TCOPYDATASTRUCT
        dwData As Long
        cbData As Long
        lpData As Long
    End Type
    Private Const WM_COPYDATA As Long = &H4A&
    Private Declare Function SendMessage Lib "user32" Alias "SendMessageW" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) As Long
    Private Declare Function CopyBytes Lib "msvbvm60" Alias "__vbaCopyBytes" (ByVal Length As Long, Destination As Any, Source As Any) As Long
    Private Declare Function SysAllocStringByteLen Lib "oleaut32" (ByVal psz As Long, ByVal cbLen As Long) As Long
    
    Implements ISubclass
    
    Private m_hWnd As Long
    
    Private Sub Class_Terminate()
        If m_hWnd Then RemoveSubclass m_hWnd, Me
    End Sub
    
    Private Function ISubclass_SubclassProc(ByVal hWnd As Long, _
                                            ByVal uMsg As Long, _
                                            ByVal wParam As Long, _
                                            ByVal lParam As Long, _
                                            ByVal dwRefData As Long _
                                            ) As Long
        Dim cds As TCOPYDATASTRUCT
        Dim Message As String
        
        If uMsg = WM_COPYDATA Then
            CopyBytes LenB(cds), cds, ByVal lParam
            If cds.lpData And cds.cbData Then
                CopyBytes 4&, ByVal VarPtr(Message), _
                          SysAllocStringByteLen(cds.lpData, cds.cbData)
            End If
            RaiseEvent Receive(cds.dwData, Message, wParam)
            ISubclass_SubclassProc = API.True
        Else
            ISubclass_SubclassProc = DefSubclassProc(hWnd, uMsg, wParam, lParam)
        End If
    End Function
    
    Public Function Init(ByVal hWnd As Long) As Boolean
        If SetSubclass(hWnd, Me) Then m_hWnd = hWnd: Init = True
    End Function
    
    Public Function Send(ByVal hWnd, _
                         ByVal MsgType As Long, _
                         ByRef Message As String _
                         ) As Boolean
        Dim cds As TCOPYDATASTRUCT
        
        cds.dwData = MsgType
        cds.cbData = LenB(Message)
        cds.lpData = StrPtr(Message)
        Send = SendMessage(hWnd, WM_COPYDATA, m_hWnd, cds)
    End Function
    Form1.frm
    Code:
    Option Explicit
    
    Private WithEvents Msg As CTransData
    
    Private Sub Command1_Click()
        Msg.Send hWnd, 1, "Test Message"
    End Sub
    
    Private Sub Form_Load()
        Set Msg = New CTransData
        Msg.Init hWnd
    End Sub
    
    Private Sub Msg_Receive(ByVal MsgType As Long, Message As String, ByVal hWndSrc As Long)
        MsgBox "Received: " & MsgType & " " & Message
    End Sub
    Attached Files Attached Files

  15. #15

    Thread Starter
    Frenzied Member
    Join Date
    Dec 2012
    Posts
    1,477

    Re: VB6 - Program Communication

    Quote Originally Posted by DEXWERX View Post
    we would love to know what were any of the problems you encountered using that method. The only one I can think of is the memory leak that happens with repeated subclassing using different static MsgProc routines. (which is mitigated using a single forwarder similar to what you've shown)
    The difficulties I ran into were constant crashing of the IDE while trying to troubleshoot code. Granted, I was not using anything like your subclassing DLL, which I presume protects the IDE. I briefly considered doing that myself, but time did not permit. I will take a closer look at your code.

    J.A. Coutts

  16. #16
    PowerPoster
    Join Date
    Jun 2015
    Posts
    2,224

    Re: VB6 - Program Communication

    Quote Originally Posted by couttsj View Post
    The difficulties I ran into were constant crashing of the IDE while trying to troubleshoot code. Granted, I was not using anything like your subclassing DLL, which I presume protects the IDE. I briefly considered doing that myself, but time did not permit. I will take a closer look at your code.

    J.A. Coutts
    actually that's a good reason / issue I overlooked. Thanks to Elroy/Lavolpe (and previous experts) we have a good handle on the stability of the IDE using different subclassing methodologies. This particular instability is caused by your static callback (in the .bas module) continuously being called even when the IDE is paused. Elroy has some strategies he uses for mitigating this. My version of comctl32 subclassing would crash similarly to what you encountered. Your current method / standard subclassing is also not completely stable, but definitely crashes less so (at least it seems stable enough for you to get to root cause of a problem).

    Thanks for elaborating!
    Last edited by DEXWERX; Sep 26th, 2017 at 07:17 AM.

  17. #17
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,940

    Re: VB6 - Program Communication

    Hi Couttsj,

    I'll just check into this thread one last time as well. I certainly didn't intend to suggest that the ComCtl32 approach to subclassing is always superior to the SetWindowLong approach to subclassing. Also, I recognize that, with the use of assembly-thunks and/or supporting DLLs, that the SetWindowLong approach can become very close to IDE safe in all circumstances.

    It's just a personal philosophy, but I do try my best to stay away from both thunks and third-party DLLs wherever possible. Also, through testing, I've become confident that I know the areas where the ComCtl32 approach isn't safe. The two areas of which I'm aware are: 1) Clicking the IDE's End button when a modal form is open, 2) Clicking the End button on the pop-up message for a run-time error. Also, I recognize that line-by-line tracing is partially disabled when using the ComCtl32 approach, and that we must resort to Debug.Print to debug our subclass procedures.

    However, if just on a non-modal form, the IDE's End button seems to be safe when using ComCtl32, so long as we monitor for WM_DESTROY in the subclass procedure and do our un-subclassing. This actually correctly executes even after the IDE's End button is clicked.

    Also, as outlined above, I just love the ComCtl32's ability to store data with each subclassing, not having to worry about un-subclassing teardown order, and the ability to re-subclass without needing to worry about un-subclassing first (so long as we correctly monitor WM_DESTROY for an eventual un-subclass).

    Best Regards,
    Elroy
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •  



Click Here to Expand Forum to Full Width