Announcement

Collapse
No announcement yet.

Popup Menu Glitch??

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

  • Popup Menu Glitch??

    Compile program and hover over a folder on your desktop, and it
    should display files in that folder in a popup menu but the
    problem is that sometimes when you click it, it doesn't register
    that you click it. Is this a glitch or is it with my code?

    3 files
    Code:
    ---------------------------- CLIP
    #COMPILE EXE
    #REGISTER NONE
    #DIM ALL
    #INCLUDE "Win32Api.Inc"
    #INCLUDE "reg.inc"
    
    TYPE COPYDATASTRUCT
        dwData AS DWORD PTR
        cbData AS DWORD
        lpData AS ASCIIZ PTR
    END TYPE
    DECLARE FUNCTION SetHookMouseWindow LIB "HookMs.Dll" _
        ALIAS "SetHookMouseWindow" (hWnd AS LONG) AS LONG
    DECLARE FUNCTION UnHookMouseWindow  LIB "HookMs.Dll" _
        ALIAS "UnHookMouseWindow" AS LONG
    DECLARE FUNCTION GetSetting(BYVAL AppName AS STRING, BYVAL Section AS STRING, BYVAL Key AS STRING, BYVAL DEFAULT AS STRING) AS STRING
    
    %IDT_TIMER1 = 100
    GLOBAL glDesktopPath$
    GLOBAL gloldmenu$
    GLOBAL gldisappear&
    
    FUNCTION Exist(InString$) AS LONG
    STATIC b$
        IF B$ = InString$ THEN
           FUNCTION = 0
            ELSE
           b$ = Instring$
           FUNCTION = 1
        END IF
    END FUNCTION
    
    
    CALLBACK FUNCTION DlgProc
    LOCAL g&
    LOCAL hPopup&
    STATIC pt AS PointApi, Msg AS STRING
        SELECT CASE CBMSG
            CASE %WM_INITDIALOG: SetHookMouseWindow CBHNDL
            CASE %WM_ERASEBKGND: ShowWindow CBHNDL, 0
            CASE %WM_DESTROY   : UnHookMouseWindow
            CASE %WM_USER + 1  : Msg = "": PostMessage CBHNDL, %WM_CANCELMODE, 0, 0
                                 KillTimer CBHNDL, %IDT_TIMER1
                                 gldisappear& = 1
            CASE %WM_COPYDATA  :
                                 LOCAL cdt AS COPYDATASTRUCT PTR
                                 cdt = CBLPARAM
                                 Msg = MID$(@[email protected], 9): GetCursorPos pt
                                 PostMessage CBHNDL, %WM_CANCELMODE, 0, 0
                                 FUNCTION = 1:
                                 EXIT FUNCTION
            CASE %WM_CANCELMODE: PostMessage CBHNDL, %WM_USER + 2, 0, 0
            CASE %WM_TIMER     : SELECT CASE CBWPARAM
                                    CASE %IDT_TIMER1 : Msg = "": PostMessage CBHNDL, %WM_CANCELMODE, 0, 0
                                                       gldisappear& = 1
                                 END SELECT
            CASE %WM_USER + 2  :
                IF Msg <> "" THEN
                    IF Exist(Msg) = 1 THEN
                        IF CBMSG = 28 THEN EXIT FUNCTION
                        IF CBMSG = 70 THEN EXIT FUNCTION
                        IF CBMSG = %WM_USER + 1 THEN EXIT FUNCTION
    LOCAL rz&
    LOCAL gPopup&
    LOCAL attribute&
                        SELECT CASE LEN(msg)
                            CASE > 0
                                attribute& = GETATTR(gldesktoppath$ & "\" & Msg)
                                SELECT CASE attribute&
                                    CASE 16
    DIM sfilename$
    DIM popupindex&
    DIM sfiles(0 TO 2000) AS STRING
                                      MENU NEW POPUP TO hPopup
                                      sfiles(0) = "-"
                                      sfiles(1) = DIR$(gldesktoppath$ & "\" & Msg & "\*.*")
                                      popupindex& = 1
                                      sfilename$ = "1"
                                      DO UNTIL sfilename$ = ""
                                          popupindex& = popupindex& + 1
                                          sfilename$ = DIR$
                                          sfiles(popupindex&) = sfilename$
                                      LOOP
                                      sfiles(popupindex&) = "-"
                                      sfiles(popupindex&+1) = "Options"
                                      sfiles(popupindex&+2) = "Unload"
                                      sfiles(popupindex&+3) = "Visit Website"
                                      sfiles(popupindex&+4) = "Purchase"
                                      popupindex& = popupindex& + 4
    REDIM PRESERVE sfiles(0 TO popupindex&)
    DIM icounter&
                                      FOR icounter& = 0 TO popupindex& - 1
                                          MENU ADD STRING, hPopup, sfiles(icounter&), icounter&, %MF_ENABLED
                                      NEXT
                                      SetTimer  CBHNDL, %IDT_TIMER1,  6000, BYVAL %NULL
                                      rz = TrackPopupMenuEx (hPopup, %TPM_RETURNCMD OR %TPM_LEFTALIGN OR %TPM_RIGHTBUTTON, pt.x, pt.y, CBHNDL, BYVAL 0)
                                      KillTimer CBHNDL, %IDT_TIMER1
                                      IF gldisappear& = 1 THEN
                                          gldisappear& = 0
                                              ELSE
                                          IF sfiles(rz) = "-" THEN EXIT FUNCTION
                                          IF sfiles(rz) = "Unload" THEN PostMessage CBHNDL, %WM_SYSCOMMAND, %SC_CLOSE, 0
    DIM NewFile AS ASCIIZ * 255
                                          NewFile = gldesktoppath$ & "\" & Msg & "\" & sfiles(rz)
                                          ShellExecute %HWND_DESKTOP, "Open", NewFile, BYVAL 0, BYVAL 0, %SW_SHOWNORMAL
                                      END IF
                                END SELECT
                        END SELECT
                    END IF
                END IF
            CASE ELSE
        END SELECT
    END FUNCTION
    
    FUNCTION PBMAIN
    glDesktopPath$ = GetSetting("Microsoft", "Windows\CurrentVersion\Explorer\Shell Folders", "Desktop", "")
    
    LOCAL hDlg AS LONG
        DIALOG NEW 0, "Icons", , , 150, 70, %WS_POPUP OR %WS_BORDER, %WS_EX_TOPMOST OR %WS_EX_TOOLWINDOW TO hDlg
        DIALOG SHOW MODAL hDlg CALL DlgProc
    END FUNCTION
    
    --------------------------- CLIP
    
    'reg.inc
    '------------------------------------------------------------------------------
    '
    ' GetSetting - Retrieves application entry in the Windows registry.
    '
    ' Syntax:
    ' Value = GetSetting(AppName, Section, Key)
    '
    ' Where:
    '
    ' AppName = String expression containing the name of the application.
    ' Section = String expression containing the name of the section where the
    ' key setting is being saved.
    ' Key = String expression containing the name of the key setting being
    ' saved.
    ' Default = Default value if no registry value is found.
    '
    ' Returns:
    '
    ' Value = Value from the registry. If the value is DWORD, use the CVL()
    ' or CVDWD() functions to convert from string to numeric.
    '
    FUNCTION GetSetting(BYVAL AppName AS STRING, BYVAL Section AS STRING, _
    BYVAL Key AS STRING, BYVAL DEFAULT AS STRING) AS STRING
    LOCAL hKey AS LONG
    LOCAL Result AS LONG
    LOCAL KeyType AS LONG
    LOCAL Buffer AS STRING * 2048
    LOCAL SIZE AS LONG
    ' ** Exit is AppName, Section or Key are null
    IF (LEN(AppName) * LEN(Section) * LEN(Key)) = 0 THEN
    FUNCTION = DEFAULT
    EXIT FUNCTION
    END IF
    ' ** Open the section
    IF RegOpenKeyEx(%HK, "SOFTWARE\"+AppName+"\"+Section, 0, %KEY_ALL_ACCESS, _
    hKey) <> %ERROR_SUCCESS THEN
    FUNCTION = DEFAULT
    EXIT FUNCTION
    END IF
    ' ** Get the key value
    SIZE = SIZEOF(Buffer)
    Result = RegQueryValueEx(hKey, Key+CHR$(0), 0, KeyType, Buffer, SIZE)
    ' ** Close the registry
    RegCloseKey hKey
    ' ** Exit if not successful or nothing there
    IF (Result <> %ERROR_SUCCESS) OR (SIZE = 0) THEN
    FUNCTION = DEFAULT
    EXIT FUNCTION
    END IF
    ' ** Return the data
    IF KeyType = %REG_SZ THEN
    FUNCTION = LEFT$(Buffer, SIZE - 1)
    ELSE
    FUNCTION = LEFT$(Buffer, SIZE)
    END IF
    END FUNCTION
    
    -------------------------------- CLIP
    'HookMs.DLL
    #COMPILE DLL "HookMs.Dll"
    #REGISTER NONE
    #DIM ALL
    #INCLUDE "Win32Api.Inc"
    #INCLUDE "COMMCTRL.INC"
    TYPE COPYDATASTRUCT
        dwData AS DWORD PTR
        cbData AS DWORD
        lpData AS DWORD
    END TYPE
    GLOBAL LastInfo AS LONG
    $HookFile = "C:\HookMs.Id"
    GLOBAL hInstDll AS LONG, TmpAsciiz AS ASCIIZ * %MAX_PATH
    GLOBAL tRectExp AS RECT, hWndLV AS LONG, hDlg AS LONG, hHook AS LONG
    
    FUNCTION LibMain(BYVAL hInstance AS LONG, BYVAL fwdReason AS LONG, _
    BYVAL lpvReserved AS LONG) EXPORT AS LONG
    STATIC hWnd AS LONG
    SELECT CASE fwdReason
        CASE %DLL_PROCESS_ATTACH: hInstDll = hInstance: LibMain = 1
        CASE %DLL_PROCESS_DETACH: LibMain = 1
    END SELECT
    END FUNCTION
    
    FUNCTION HookProc(BYVAL nCode AS LONG, BYVAL wParam AS LONG, BYVAL lParam AS LONG) EXPORT AS LONG
    STATIC id AS LONG, i AS LONG, hWnd AS LONG
    STATIC TmpAsciizC AS ASCIIZ * %MAX_PATH
    STATIC pt AS PointApi, ptc AS pointApi, Cdt AS COPYDATASTRUCT
        FUNCTION = CallNextHookEx(hHook, nCode, wParam, BYVAL lParam)
        IF nCode < 0 THEN EXIT FUNCTION
        IF hDlg = 0 THEN OPEN $HookFile FOR INPUT SHARED AS #1: _
        INPUT #1, hDlg, hWndLv: CLOSE #1: ptc.x = -1000
        IF IsWindow(hDlg) = %False THEN FreeLibrary hInstDLL: EXIT FUNCTION
        GetCursorPos pt: IF pt.x = ptc.x AND pt.y = ptc.y THEN EXIT FUNCTION
        ptc.x = pt.x: ptc.y = pt.y: hWnd = WindowFromPoint (pt.x,pt.y)
        IF hWndLV = 0 THEN EXIT FUNCTION
        IF hWnd <> hWndLV THEN
            IF LastInfo <> 1 THEN PostMessage hDlg, %WM_USER + 1, 0, 0: LastInfo = 1
            EXIT FUNCTION
        END IF
        IF GetWindowThreadProcessId(hWndLv, BYVAL 0) <> GetCurrentThreadId THEN EXIT FUNCTION
        ScreenToClient hWndLv, pt
        id = -1
        FOR i = 0 TO ListView_GetItemCount(hWndLv) - 1
            tRectExp.nLeft = %LVIR_BOUNDS
            ListView_GetItemRect hwndLv, i, tRectExp, %LVIR_BOUNDS
            IF pt.x >= tRectExp.nLeft AND pt.x < tRectExp.nRight AND _
                pt.y >= tRectExp.nTop AND pt.y < tRectExp.nBottom THEN id = i
        NEXT
        ListView_GetItemText hwndLv, id, 0, TmpAsciiz, SIZEOF(TmpAsciiz)
        IF LastInfo <> 2 OR TmpAsciiz <> TmpAsciizC THEN
            TmpAsciizC = TmpAsciiz
    LOCAL Msg AS STRING
            Msg = HEX$(id, 8) + TmpAsciiz
            Cdt.cbdata = LEN(Msg) + 1
            Cdt.lpData = STRPTR(Msg)
            SendMessage hDlg, %WM_COPYDATA, 0, VARPTR(Cdt)
            LastInfo = 2
        END IF
    END FUNCTION
    
    FUNCTION ENCW(BYVAL hWnd AS LONG, BYVAL lParam AS LONG) AS LONG
    STATIC tRect AS RECT
        GetClassName hWnd, TmpAsciiz, SIZEOF(TmpAsciiz): FUNCTION = 1
        IF UCASE$(TmpAsciiz) <> "SYSLISTVIEW32" THEN
                ELSE
            GetClientRect hWnd, tRect
            IF (tRect.nRight - tRect.nLeft) = (tRectExp.nRight - tRectExp.nLeft) AND _
            (tRect.nBottom - tRect.nTop) = (tRectExp.nBottom - tRectExp.nTop) THEN _
            hWndLV = hWnd: FUNCTION = 0
        END IF
    END FUNCTION
    
    FUNCTION SetHookMouseWindow ALIAS "SetHookMouseWindow" (hWnd AS LONG) EXPORT AS LONG
        InitCommonControls
        SystemParametersInfo %SPI_GETWORKAREA, 0, BYVAL VARPTR(tRectExp), 0
        EnumChildWindows FindWindow ("Progman", ""), CODEPTR(ENCW), 0
        hHook = SetWindowsHookEx (%WH_MOUSE, CODEPTR(HookProc), BYVAL hInstDLL, BYVAL 0)
        OPEN $HookFile FOR OUTPUT AS #1: PRINT #1, hWnd, hWndLv;: CLOSE
    END FUNCTION
    
    FUNCTION UnHookMouseWindow ALIAS "UnHookMouseWindow" EXPORT AS LONG
        UnhookWindowsHookEx hHook: KILL $HookFile
    END FUNCTION


    ------------------
    -Greg
    -Greg
    [email protected]
    MCP,MCSA,MCSE,MCSD

  • #2
    Greg --
    I didn't test your code, but I'm sure that you have performance problems.

    1) it's necessary to optimize a work of global hook.

    I didn't want to make it complicate for understanding, but if to worry about performance, it's necessary to do following.
    Exe starts a global mouse hook. This DLL should be small (like now).
    When DLL will be integrated in the same process as Desktop, it should "terminate" Exe and to load another "big" DLL.
    New DLL will start invisible dialog modeless with LOCAL mouse hook and will show popup menues.

    2) Sure - and here I see the main reason - that your add-ons take a lot of time.
    If user continue to move mouse, you should immediatelly terminate your previous "Dir".
    Probably, if you describe your task more detail, it will be possible to give more certain advice.


    ------------------
    E-MAIL: [email protected]

    Comment


    • #3
      Semen,

      Semen,

      This application simply runs and when a user hovers over an icon
      that is in the desktop that happens to be a folder then it will
      popup with the files that are in that folder. It saves the user
      from having to open the folder to view the files.

      - Once it pops up it should remain popped up until a user clicks
      on the desktop or switches tasks

      - User clicks on a command in the popup menu (which sometimes
      doesn't register)

      Actually I have no performance problems. Its amazingly fast, just
      some glitches here and there that I still need to work out and
      the last time I checked the memory is under 2 megs so I'm
      very happy with the performance at this time.

      I will try to work the structure the way you are describing.
      I don't know if I quite understand the difference betweem
      EXE ->> DLL -->> DLL method verses EXE --> DLL method and
      what performance gain I'll achieve.


      ------------------
      -Greg
      -Greg
      [email protected]
      MCP,MCSA,MCSE,MCSD

      Comment


      • #4
        Semen,

        Do you have any examples of how to see all messages for a
        particular object? Kinda like in Spy++ with VS6.0?

        I'm wanting to trap all messages that are on the ListView control
        on the desktop any ideas?

        Thanks,


        ------------------
        -Greg
        -Greg
        [email protected]
        MCP,MCSA,MCSE,MCSD

        Comment


        • #5
          Greg --
          I executed your code.
          There are some problems (on my PC obviously not linked with performance).
          Anyway I think that it's better to stop global hook asap (too "expensive") and to start new DLL with local mouse hook.
          I don't like that popup menu and listview are located in different threads.
          Probably today evening or tomorrow I will reconstruct Exe/Dll.

          BTW, I found obvious logical trouble.
          I download zip on desktop and extract a folder here.
          Both sometimes has the same name and your code thinks that zip is a folder.

          > I'm wanting to trap all messages that are on the ListView control
          on the desktop any ideas?

          I think it's possible even now, w/o reconstruction.
          Look fragment in Dll after
          If GetWindowThreadProcessId(hWndLv, BYVAL 0) <> GetCurrentThreadId
          When this fragment is executing first time you can set own CallBack for hWndLv (because DLL is located in the same thread).

          ------------------
          E-MAIL: [email protected]

          Comment


          • #6
            Forgot to add.
            You need to correct logic of gldisappear&.
            Look fragment
            rz = TrackPopupMenuEx (hPopup, %TPM_RETURNCMD OR %TPM_LEFTALIGN OR %TPM_RIGHTBUTTON, pt.x, pt.y, CBHNDL, BYVAL 0)
            KillTimer CBHNDL, %IDT_TIMER1
            IF gldisappear& = 1 THEN ' <---------
            gldisappear& = 0
            ELSE
            ...
            End if
            W/o this testing all "works".


            ------------------
            E-MAIL: [email protected]

            Comment


            • #7
              Semen,

              Code:
              ...
                                                rz = TrackPopupMenuEx (hPopup, %TPM_RETURNCMD OR %TPM_LEFTALIGN OR %TPM_RIGHTBUTTON, pt.x, pt.y, CBHNDL, BYVAL 0)
                                                KillTimer CBHNDL, %IDT_TIMER1
                                                IF gldisappear& = 1 THEN
                                                    gldisappear& = 0
                                                        ELSE
                                                    IF sfiles(rz) = "-" THEN EXIT FUNCTION
                                                    IF sfiles(rz) = "Unload" THEN PostMessage CBHNDL, %WM_SYSCOMMAND, %SC_CLOSE, 0
              DIM NewFile AS ASCIIZ * 255
                                                    NewFile = gldesktoppath$ & "\" & Msg & "\" & sfiles(rz)
                                                    ShellExecute %HWND_DESKTOP, "Open", NewFile, BYVAL 0, BYVAL 0, %SW_SHOWNORMAL
                                                END IF          
              ...
              I found that I had to include the IF statment because
              I found that when you have a popup menu and then you move your
              mouse to the task bar and then back it will RANDOMLY select
              the first item in the list for no reason at all so I then
              put "-" (seperator) as the first item in the list and I just
              ignore it if it is selected.

              I don't really know if I understand the differences of a local
              hook or a global hook. Why is it to expensive to have a global
              hook, which I have right now? Are the weird errors caused by
              this global hook problem?

              Thanks


              ------------------
              -Greg
              -Greg
              [email protected]
              MCP,MCSA,MCSE,MCSD

              Comment


              • #8
                Greg --
                I tried to combine initial code with your add-ons.
                Remains logical mistake (zip-file and folder have the same names on desktop).
                It seems to me that new code works better than you posted above.
                But I didn't realize "correct" approach (I'm lazy).
                Global hook is expensive, because, like rule, it wants inter-process communication (to send messages to windows, located in another processes).
                In code, posted bellow, no. of IPC messages is minimized (LastInfo), but ...

                Dll:
                Code:
                   #Compile Dll "HookMs.Dll"
                   #Register None
                   #Dim All
                   #Include "Win32Api.Inc"
                   #Include "COMMCTRL.INC"
                   Type COPYDATASTRUCT
                    dwData As Dword Ptr
                    cbData As Dword
                    lpData As Dword
                   End Type
                   Global LastInfo As Long
                   $HookFile = "C:\HookMs.Id"
                   Global hInstDll As Long, TmpAsciiz As Asciiz * %MAX_PATH
                   Global tRectExp As RECT, hWndLV As Long, hDlg As Long, hHook As Long
                   Function LibMain(ByVal hInstance As Long, ByVal fwdReason As Long, _
                      ByVal lpvReserved As Long) Export As Long
                      Static hWnd As Long
                      Select Case fwdReason
                         Case %DLL_PROCESS_ATTACH: hInstDll = hInstance: LibMain = 1
                         Case %DLL_PROCESS_DETACH: LibMain = 1
                      End Select
                   End Function
                   Function HookProc(ByVal nCode As Long, ByVal wParam As Long, ByVal lParam As Long) Export As Long
                      Static id As Long, i As Long, hWnd As Long
                      Static TmpAsciizC As Asciiz * %MAX_PATH
                      Static pt As PointApi, ptc As pointApi, Cdt As COPYDATASTRUCT
                      Function = CallNextHookEx(hHook, nCode, wParam, ByVal lParam)
                      If nCode < 0 Then Exit Function
                      If hDlg = 0 Then Open $HookFile For Input Shared As #1: _
                         Input #1, hDlg, hWndLv: Close #1: ptc.x = -1000
                      If IsWindow(hDlg) = %False Then FreeLibrary hInstDLL: Exit Function
                      GetCursorPos pt: If pt.x = ptc.x And pt.y = ptc.y Then Exit Function
                      ptc.x = pt.x: ptc.y = pt.y: hWnd = WindowFromPoint (pt.x,pt.y)
                      If hWndLV = 0 Then Exit Function
                      If hWnd <> hWndLV Then
                         If LastInfo = 2 And pt.x >= tRectExp.nLeft And pt.x < tRectExp.nRight And _
                            pt.y >= tRectExp.nTop And pt.y < tRectExp.nBottom Then
                         ElseIf LastInfo <> 1 Then
                            PostMessage hDlg, %WM_USER + 1, pt.x, pt.y: LastInfo = 1
                         End If
                         Exit Function
                      End If
                      If GetWindowThreadProcessId(hWndLv, ByVal 0) <> GetCurrentThreadId Then Exit Function
                      ScreenToClient hWndLv, pt
                      id = -1
                      For i = 0 To ListView_GetItemCount(hWndLv) - 1
                         tRectExp.nLeft = %LVIR_BOUNDS
                         ListView_GetItemRect hwndLv, i, tRectExp, %LVIR_BOUNDS
                         If pt.x >= tRectExp.nLeft And pt.x < tRectExp.nRight And _
                            pt.y >= tRectExp.nTop And pt.y < tRectExp.nBottom Then id = i: Exit For
                      Next
                      ListView_GetItemText hwndLv, id, 0, TmpAsciiz, SizeOf(TmpAsciiz)
                      If LastInfo <> 2 Or TmpAsciiz <> TmpAsciizC Then
                         TmpAsciizC = TmpAsciiz
                         Local Msg As String
                         Msg = Hex$(tRectExp.nLeft, 4) + Hex$(tRectExp.nRight, 4) + _
                               Hex$(tRectExp.nTop, 4) + Hex$(tRectExp.nBottom, 4) + TmpAsciiz
                         Cdt.cbdata = Len(Msg) + 1
                         Cdt.lpData  = StrPtr(Msg)
                         SendMessage hDlg, %WM_COPYDATA, 0, VarPtr(Cdt)
                         LastInfo = 2
                      End If
                   End Function
                   Function ENCW(ByVal hWnd As Long, ByVal lParam As Long) As Long
                      Static tRect As RECT
                      GetClassName hWnd, TmpAsciiz, SizeOf(TmpAsciiz): Function = 1
                      If UCase$(TmpAsciiz) <> "SYSLISTVIEW32" Then
                      Else
                         GetClientRect hWnd, tRect
                         If (tRect.nRight - tRect.nLeft) = (tRectExp.nRight - tRectExp.nLeft) And _
                            (tRect.nBottom - tRect.nTop) = (tRectExp.nBottom - tRectExp.nTop) Then _
                            hWndLV = hWnd: Function = 0
                      End If
                   End Function
                   Function SetHookMouseWindow Alias "SetHookMouseWindow" (hWnd As Long) Export As Long
                      InitCommonControls
                      SystemParametersInfo %SPI_GETWORKAREA, 0, ByVal VarPtr(tRectExp), 0
                      EnumChildWindows FindWindow ("Progman", ""), CodePtr(ENCW), 0
                      hHook = SetWindowsHookEx (%WH_MOUSE, CodePtr(HookProc), ByVal hInstDLL, ByVal 0)
                      Open $HookFile For Output As #1: Print #1, hWnd, hWndLv;: Close
                   End Function
                   Function UnHookMouseWindow Alias "UnHookMouseWindow" Export As Long
                      UnhookWindowsHookEx hHook: Kill $HookFile
                   End Function

                Exe:
                Code:
                   #Compile Exe
                   #Register None
                   #Dim All
                   #Include "Win32Api.Inc"
                
                   Type COPYDATASTRUCT
                       dwData As Dword Ptr
                       cbData As Dword
                       lpData As Asciiz Ptr
                   End Type
                
                   Declare Function SetHookMouseWindow Lib "HookMs.Dll" _
                      Alias "SetHookMouseWindow" (hWnd As Long) As Long
                   Declare Function UnHookMouseWindow  Lib "HookMs.Dll" _
                      Alias "UnHookMouseWindow" As Long
                   Declare Sub CoTaskMemFree Lib "ole32.dll" Alias "CoTaskMemFree" (pv As Dword)
                
                   %MaxFiles = 1000
                   
                   CallBack Function DlgProc
                      Static DesktopPath As Asciiz * %MAX_PATH
                      Static pt As PointApi, Msg As String, LastMsg As String, hPopup As Long
                      Local i As Long
                      Dim nFiles As Static Long, sFiles(1 To %MaxFiles) As Static String, sFile As String
                      Select Case CbMsg
                         Case %WM_INITDIALOG
                            SetHookMouseWindow CbHndl
                            If IsFalse(SHGetSpecialFolderLocation(%HWND_DESKTOP, ByVal %CSIDL_DESKTOP, ByVal VarPtr(i))) Then
                               SHGetPathFromIDList ByVal i, DesktopPath
                               CoTaskMemFree ByVal i
                            End If
                         Case %WM_ERASEBKGND: ShowWindow CbHndl, 0
                         Case %WM_DESTROY   : UnHookMouseWindow
                         Case %WM_USER + 1
                            If Msg <> "" And (CbWparam < Val("&H" + Mid$(LastMsg,  1, 4)) Or _
                               CbWparam >= Val("&H" + Mid$(LastMsg,  5, 4)) Or _
                               CbLparam < Val("&H" + Mid$(LastMsg,  9, 4)) Or _
                               CbLparam  >= Val("&H" + Mid$(LastMsg,  13, 4))) Then _
                               Msg = "": LastMsg = "": PostMessage CbHndl, %WM_CANCELMODE, 0, 0
                         Case %WM_COPYDATA
                            Local cdt As COPYDATASTRUCT Ptr
                            cdt = CbLparam
                            If LastMsg <> @[email protected] Then LastMsg = @[email protected]: Msg = Mid$(@[email protected], 17): _
                               GetCursorPos pt: PostMessage CbHndl, %WM_CANCELMODE, 0, 0: Function = 1: Exit Function
                         Case %WM_CANCELMODE: PostMessage CbHndl, %WM_USER + 2, 0, 0: nFiles = 0
                         Case %WM_USER + 2
                            Do
                               If Msg = "" Then Exit Do
                               ErrClear: i = GetAttr(DesktopPath + "\" + Msg)
                               If (i And 16) <> 16 Then Exit Do
                               sFile = Dir$(DesktopPath + "\" + Msg + "\*.*"): nFiles = 0
                               While sFile <> ""
                                  If nFiles < %maxFiles Then Incr nFiles: sFiles(nFiles) = sFile
                                  sFile = Dir$
                               Loop
                               If nFiles = 0 Then Msg = "": Exit Do
                
                               If hPopup Then DestroyMenu hPopup
                               Menu New Popup To hPopup
                               Menu Add String, hPopup, "Contents of " + UCase$(Msg) + ":", 1, %MF_DISABLED
                               Menu Add String, hPopup, "-", 2, %MF_DISABLED
                               For i = 1 To nFiles
                                  Menu Add String, hPopup, sFiles(i), i + 2, %MF_ENABLED
                               Next
                               Menu Add String, hPopup, "-", nFiles + 3, %MF_DISABLED
                               Menu Add String, hPopup, "Options", nFiles + 4, %MF_ENABLED
                               Menu Add String, hPopup, "Unload", nFiles + 5, %MF_ENABLED
                               Menu Add String, hPopup, "Visit Website", nFiles + 6, %MF_ENABLED
                               Menu Add String, hPopup, "Purchase", nFiles + 7, %MF_ENABLED
                               i = TrackPopupMenuEx (hPopup, %TPM_RETURNCMD Or %TPM_LEFTALIGN Or %TPM_RIGHTBUTTON, pt.x, pt.y, CbHndl, ByVal 0)
                               Select Case i
                                  Case 3 To nFiles + 2
                                     ShellExecute %HWND_DESKTOP, "Open", DesktopPath + "\" + Msg + "\" + sFiles(i - 2), _
                                        ByVal 0, ByVal 0, %SW_SHOWNORMAL
                                  Case nFiles + 5: PostMessage CbHndl, %WM_SYSCOMMAND, %SC_CLOSE, 0
                               End Select
                               Exit Do
                            Loop
                      End Select
                   End Function
                
                   Function PbMain
                      Local hDlg As Long
                      Dialog New 0, "", 0, 0, 0, 0, %WS_POPUP, %WS_EX_TOPMOST Or %WS_EX_TOOLWINDOW To hDlg
                      Dialog Show Modal hDlg Call DlgProc
                   End Function

                ------------------
                E-MAIL: [email protected]

                Comment


                • #9
                  Semen,

                  Thanks for all your help in this. Something that is really weird is
                  I originally tried the modified code you created at work on a
                  266mhz, Windows 98 Second Edition and it works fine (other then
                  the logical errors) but down at the task bar you once and awhile
                  see a BLANK button popup and flash blue and then disappear.

                  I then went home and tried it expecting the same error on my
                  Windows 2000 Professional Computer, and it runs perfect with no
                  BLANK taskbar button. Do you know what would cause this?

                  Thanks

                  ------------------
                  -Greg
                  -Greg
                  [email protected]
                  MCP,MCSA,MCSE,MCSD

                  Comment


                  • #10
                    Originally posted by Semen Matusovski:
                    I think it's possible even now, w/o reconstruction.
                    Look fragment in Dll after
                    If GetWindowThreadProcessId(hWndLv, BYVAL 0) <> GetCurrentThreadId
                    When this fragment is executing first time you can set own CallBack for hWndLv (because DLL is located in the same thread).
                    [/B]
                    Semen,

                    To trap all messages do I simply do a CODEPTR of the callback I want?

                    I've tried this:

                    Code:
                    DECLARE FUNCTION SubClassProc(BYVAL hWnd&, BYVAL wMsg&, BYVAL wParam&, BYVAL lParam&) AS LONG
                    
                    ...
                    global gOldSubClassProc&
                    ...
                          IF GetWindowThreadProcessId(hWndLv, BYVAL 0) <> GetCurrentThreadId THEN
                            [b]gOldSubClassProc = SetWindowLong(hWndLv, %GWL_WNDPROC, CODEPTR(SubClassProc))[/b]
                            EXIT FUNCTION
                            [b]gOldSubClassProc = SetWindowLong(hWndLv, %GWL_WNDPROC, CODEPTR(SubClassProc))[/b]
                            
                              ELSE
                          END IF
                    
                    ...
                    FUNCTION SubClassProc(BYVAL hWnd&, BYVAL wMsg&, BYVAL wParam&, BYVAL lParam&) AS LONG
                    OPEN "C:\log.dat" FOR APPEND AS #3
                    PRINT #1, STR$(hWnd&) & " " & STR$(wMsg&) & " " & STR$(wParam&) & " " & STR$(lparam&)
                    CLOSE #3
                        FUNCTION = CallWindowProc(gOldSubClassProc, hWnd&, wMsg&, wParam&, lParam&)
                    END FUNCTION
                    
                    ...
                    FUNCTION UnHookMouseWindow ALIAS "UnHookMouseWindow" EXPORT AS LONG
                          SetWindowLong hWndLv, %GWL_WNDPROC, gOldSubClassProc
                          UnhookWindowsHookEx hHook: KILL $HookFile
                    END FUNCTION
                    I tried both those items and it seems that:

                    1) GPF occus both times
                    2) Callback never called

                    Doing something wrong? I'm sorry if I'm bugging you Semen

                    ------------------
                    -Greg



                    [This message has been edited by Gregery D Engle (edited September 12, 2000).]
                    -Greg
                    [email protected]
                    MCP,MCSA,MCSE,MCSD

                    Comment


                    • #11
                      Greg --
                      Probably I was not clear, but you subclassed in another place that I suggested.
                      I wrote "after statement". This means that
                      If GetWindowThreadProcessId(hWndLv, ByVal 0) <> GetCurrentThreadId Then Exit Function
                      ... subclass ...

                      I tested before under Win2000 Pro only.
                      Just now I tested under 98SE and it seems to me that I understood about what you are talking.
                      I fixed a problem with "empty" button on taskbar (DDT' jokes; it's enough to add SetWindowLong ... WS_EXSTYLE ... after Dialog New).
                      Successful subclassed.
                      But I also found my mistake with converting screen/client coordinates of cursor.

                      Now (it seems to me) all works under 98SE like it should be, but I want to clean code.
                      Just now I need to go away. I try to post a code, when I'll come back (through 5-6 hours).

                      ------------------
                      E-MAIL: [email protected]

                      Comment


                      • #12
                        Semen,

                        Ahh I will try that and I will await your awesome changes

                        ------------------
                        -Greg

                        [This message has been edited by Gregery D Engle (edited September 13, 2000).]
                        -Greg
                        [email protected]
                        MCP,MCSA,MCSE,MCSD

                        Comment


                        • #13
                          Greg --
                          Ok, I'm came back and ready to post a code, which I promissed.
                          Just now I'm under Win98SE and don't see troubles, which were before.
                          I found that under Win98SE ListView covers whole screen, unlike Win2000, where this window is "transparent" (icons only belong to it).
                          That's why it was appearence without "task".

                          Note, that Left/Right button down are logged in c:\Log.Txt.

                          Just now I try to realize another ("correct") approach (to integrate DLL and to kill global hook and "master" dialog).
                          I want it to solve one my task. If it will be successful, I will post a code.

                          I didn't test again this code under Win2000, but hope, that I destroyed nothing.

                          If you will notice something wrong, let me know and I'll try to correct.

                          DLL
                          Code:
                             #Compile Dll "HookMs.Dll"
                             #Register None
                             #Dim All
                             #Include "Win32Api.Inc"
                             #Include "COMMCTRL.INC"
                             Type COPYDATASTRUCT
                              dwData As Dword Ptr
                              cbData As Dword
                              lpData As Dword
                             End Type
                             Global LastInfo As Long
                             $HookFile = "C:\HookMs.Id"
                             Global hInstDll As Long, TmpAsciiz As Asciiz * %MAX_PATH
                             Global tRectExp As RECT, hWndLV As Long, hDlg As Long, hHook As Long
                          
                             Global OldSubClassProc As Long
                          
                             Function SubClassProc(ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
                                Local i As Long
                                If wMsg = %WM_LBUTTONDOWN Or wMsg = %WM_RBUTTONDOWN Then _
                                   i = FreeFile: Open "C:\Log.Txt" For Append As #i: _
                                   Print #i, Time$ + Str$(wMsg): Close #i
                                Function = CallWindowProc(OldSubClassProc, hWnd, wMsg, wParam, lParam)
                             End Function
                          
                             Function LibMain(ByVal hInstance As Long, ByVal fwdReason As Long, _
                                ByVal lpvReserved As Long) Export As Long
                                Select Case fwdReason
                                   Case %DLL_PROCESS_ATTACH: hInstDll = hInstance: LibMain = 1
                                   Case %DLL_PROCESS_DETACH:
                                      If OldSubClassProc Then SetWindowLong hWndLv, %GWL_WNDPROC, OldSubClassProc
                                      LibMain = 1
                                End Select
                             End Function
                             Function HookProc(ByVal nCode As Long, ByVal wParam As Long, ByVal lParam As Long) Export As Long
                                Static id As Long, i As Long, hWnd As Long
                                Static TmpAsciizC As Asciiz * %MAX_PATH
                                Static pt As PointApi, ptc As pointApi, Cdt As COPYDATASTRUCT
                                Function = CallNextHookEx(hHook, nCode, wParam, ByVal lParam)
                                If nCode < 0 Then Exit Function
                                If hDlg = 0 Then Open $HookFile For Input Shared As #1: _
                                   Input #1, hDlg, hWndLv: Close #1: ptc.x = -1000
                                If IsWindow(hDlg) = %False Then FreeLibrary hInstDLL: Exit Function
                                GetCursorPos pt: If pt.x = ptc.x And pt.y = ptc.y Then Exit Function
                                ptc.x = pt.x: ptc.y = pt.y: hWnd = WindowFromPoint (pt.x,pt.y)
                                If hWndLV = 0 Then Exit Function
                                If hWnd <> hWndLV Then
                                   If LastInfo = 2 And pt.x >= tRectExp.nLeft And pt.x < tRectExp.nRight And _
                                      pt.y >= tRectExp.nTop And pt.y < tRectExp.nBottom Then
                                   ElseIf LastInfo <> 1 Then
                                      PostMessage hDlg, %WM_USER + 1, pt.x, pt.y: LastInfo = 1
                                   End If
                                   Exit Function
                                End If
                                If GetWindowThreadProcessId(hWndLv, ByVal 0) <> GetCurrentThreadId Then Exit Function
                                If OldSubClassProc = 0 Then _
                                   OldSubClassProc = SetWindowLong(hWndLv, %GWL_WNDPROC, CodePtr(SubClassProc))
                          
                                ScreenToClient hWndLv, pt
                                id = -1
                                For i = 0 To ListView_GetItemCount(hWndLv) - 1
                                   tRectExp.nLeft = %LVIR_BOUNDS
                                   ListView_GetItemRect hwndLv, i, tRectExp, %LVIR_BOUNDS
                                   If pt.x >= tRectExp.nLeft And pt.x < tRectExp.nRight And _
                                      pt.y >= tRectExp.nTop And pt.y < tRectExp.nBottom Then id = i: Exit For
                                Next
                                If id >= 0 Then
                                   ListView_GetItemText hwndLv, id, 0, TmpAsciiz, SizeOf(TmpAsciiz)
                                   If LastInfo <> 2 Or TmpAsciiz <> TmpAsciizC Then
                                      TmpAsciizC = TmpAsciiz
                                      Local Msg As String, pt1 As POINTAPI, pt2 As POINTAPI
                                      pt1.x = tRectExp.nLeft: pt1.y = tRectExp.nTop: ClientToScreen hWndLv, pt1
                                      pt2.x = tRectExp.nRight: pt2.y = tRectExp.nBottom: ClientToScreen hWndLv, pt2
                                      Msg = Hex$(pt1.x, 4) + Hex$(pt2.x, 4) + _
                                            Hex$(pt1.y, 4) + Hex$(pt2.y, 4) + TmpAsciiz
                                      Cdt.cbdata = Len(Msg) + 1
                                      Cdt.lpData  = StrPtr(Msg)
                                      SendMessage hDlg, %WM_COPYDATA, 0, VarPtr(Cdt)
                                      LastInfo = 2
                                   End If
                                Else
                                   If LastInfo <> 1 Then PostMessage hDlg, %WM_USER + 1, ptc.x, ptc.y: LastInfo = 1
                                End If
                             End Function
                             Function ENCW(ByVal hWnd As Long, ByVal lParam As Long) As Long
                                Static tRect As RECT
                                GetClassName hWnd, TmpAsciiz, SizeOf(TmpAsciiz): Function = 1
                                If UCase$(TmpAsciiz) <> "SYSLISTVIEW32" Then
                                Else
                                   GetClientRect hWnd, tRect
                                   If (tRect.nRight - tRect.nLeft) = (tRectExp.nRight - tRectExp.nLeft) And _
                                      (tRect.nBottom - tRect.nTop) = (tRectExp.nBottom - tRectExp.nTop) Then _
                                      hWndLV = hWnd: Function = 0
                                End If
                             End Function
                             Function SetHookMouseWindow Alias "SetHookMouseWindow" (hWnd As Long) Export As Long
                                InitCommonControls
                                SystemParametersInfo %SPI_GETWORKAREA, 0, ByVal VarPtr(tRectExp), 0
                                EnumChildWindows FindWindow ("Progman", ""), CodePtr(ENCW), 0
                                hHook = SetWindowsHookEx (%WH_MOUSE, CodePtr(HookProc), ByVal hInstDLL, ByVal 0)
                                Open $HookFile For Output As #1: Print #1, hWnd, hWndLv;: Close
                             End Function
                             Function UnHookMouseWindow Alias "UnHookMouseWindow" Export As Long
                                UnhookWindowsHookEx hHook: Kill $HookFile
                             End Function
                          Exe
                          Code:
                             #Compile Exe
                             #Dim All
                             #Register None  
                             #Include "Win32Api.Inc"
                          
                             Type COPYDATASTRUCT
                                 dwData As Dword Ptr
                                 cbData As Dword
                                 lpData As Asciiz Ptr
                             End Type
                          
                             Declare Function SetHookMouseWindow Lib "HookMs.Dll" _
                                Alias "SetHookMouseWindow" (hWnd As Long) As Long
                             Declare Function UnHookMouseWindow  Lib "HookMs.Dll" _
                                Alias "UnHookMouseWindow" As Long
                             Declare Sub CoTaskMemFree Lib "ole32.dll" Alias "CoTaskMemFree" (pv As Dword)
                          
                             %MaxFiles = 1000
                          
                             CallBack Function DlgProc
                                Static DesktopPath As Asciiz * %MAX_PATH
                                Static pt As PointApi, Msg As String, LastMsg As String, hPopup As Long
                                Local i As Long
                                Dim nFiles As Static Long, sFiles(1 To %MaxFiles) As Static String, sFile As String
                                Select Case CbMsg
                                   Case %WM_INITDIALOG
                                      SetHookMouseWindow CbHndl
                                      If IsFalse(SHGetSpecialFolderLocation(%HWND_DESKTOP, ByVal %CSIDL_DESKTOP, ByVal VarPtr(i))) Then
                                         SHGetPathFromIDList ByVal i, DesktopPath
                                         CoTaskMemFree ByVal i
                                      End If
                                   Case %WM_ERASEBKGND: ShowWindow CbHndl, 0
                                   Case %WM_DESTROY   : UnHookMouseWindow
                                   Case %WM_USER + 1
                                      If Msg <> "" And (CbWparam < Val("&H" + Mid$(LastMsg,  1, 4)) Or _
                                         CbWparam >= Val("&H" + Mid$(LastMsg,  5, 4)) Or _
                                         CbLparam < Val("&H" + Mid$(LastMsg,  9, 4)) Or _
                                         CbLparam  >= Val("&H" + Mid$(LastMsg,  13, 4))) Then _
                                         Msg = "": LastMsg = "": PostMessage CbHndl, %WM_CANCELMODE, 0, 0
                                   Case %WM_COPYDATA
                                      Local cdt As COPYDATASTRUCT Ptr
                                      cdt = CbLparam
                                      If LastMsg <> @[email protected] Then LastMsg = @[email protected]: Msg = Mid$(@[email protected], 17): _
                                         GetCursorPos pt: PostMessage CbHndl, %WM_CANCELMODE, 0, 0: Function = 1: Exit Function
                                   Case %WM_CANCELMODE: PostMessage CbHndl, %WM_USER + 2, 0, 0: nFiles = 0
                                   Case %WM_USER + 2
                                      Do
                                         If Msg = "" Then Exit Do
                                         ErrClear: i = GetAttr(DesktopPath + "\" + Msg)
                                         If (i And 16) <> 16 Then Exit Do
                                         sFile = Dir$(DesktopPath + "\" + Msg + "\*.*"): nFiles = 0
                                         While sFile <> ""
                                            If nFiles < %maxFiles Then Incr nFiles: sFiles(nFiles) = sFile
                                            sFile = Dir$
                                         Loop
                                         If nFiles = 0 Then Msg = "": Exit Do
                          
                                         If hPopup Then DestroyMenu hPopup
                                         Menu New Popup To hPopup
                                         Menu Add String, hPopup, "Contents of " + UCase$(Msg) + ":", 1, %MF_DISABLED
                                         Menu Add String, hPopup, "-", 2, %MF_DISABLED
                                         For i = 1 To nFiles
                                            Menu Add String, hPopup, sFiles(i), i + 2, %MF_ENABLED
                                         Next
                                         Menu Add String, hPopup, "-", nFiles + 3, %MF_DISABLED
                                         Menu Add String, hPopup, "Options", nFiles + 4, %MF_ENABLED
                                         Menu Add String, hPopup, "Unload", nFiles + 5, %MF_ENABLED
                                         Menu Add String, hPopup, "Visit Website", nFiles + 6, %MF_ENABLED
                                         Menu Add String, hPopup, "Purchase", nFiles + 7, %MF_ENABLED
                                         i = TrackPopupMenuEx (hPopup, %TPM_RETURNCMD Or %TPM_LEFTALIGN Or %TPM_RIGHTBUTTON, pt.x, pt.y, CbHndl, ByVal 0)
                                         Select Case i
                                            Case 3 To nFiles + 2
                                               ShellExecute %HWND_DESKTOP, "Open", DesktopPath + "\" + Msg + "\" + sFiles(i - 2), _
                                                  ByVal 0, ByVal 0, %SW_SHOWNORMAL
                                            Case nFiles + 5: PostMessage CbHndl, %WM_SYSCOMMAND, %SC_CLOSE, 0
                                         End Select
                                         Exit Do
                                      Loop
                                End Select
                             End Function
                          
                             Function PbMain
                                Local hDlg As Long
                                Dialog New 0, "", 0, 0, 0, 0, %WS_POPUP To hDlg
                                SetWindowLong hDlg, %GWL_EXSTYLE, %WS_EX_TOPMOST Or %WS_EX_TOOLWINDOW
                                Dialog Show Modal hDlg Call DlgProc
                             End Function
                          ------------------
                          E-MAIL: [email protected]

                          [This message has been edited by Semen Matusovski (edited September 13, 2000).]

                          Comment


                          • #14
                            Semen,

                            I'm impressed with your changes. It seems to work perfectly on
                            Windows 98 Second Edition. I will later try Win95 and WinNT 4.0
                            And WinPro. I have no doubts on the performance. I really do
                            appreciate your time and effort in this. If you ever want
                            something in return let me know.

                            Thanks,


                            ------------------
                            -Greg
                            -Greg
                            [email protected]
                            MCP,MCSA,MCSE,MCSD

                            Comment

                            Working...
                            X