Announcement

Collapse
No announcement yet.

Intercepting IE statusbar messages - again

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

    Intercepting IE statusbar messages - again

    Not sure this should be under "Programming the Internet", but that's where a previous thread was...

    With reference to code provided by Pierre Bellisle in this post:
    http://www.powerbasic.com/support/pb...1&postcount=12

    I have a new need for this code, but I have not had success with it. I'm on Win XP Pro SP3, and have tried both PBWin 8 and PBWin 9.

    To track down what the code is doing, I inserted calls to write a log file with the enumerated classes, windows, and controls.

    Pierre's code locates IE, but the only controls it finds are:
    BrowserFrameGripperClass
    CommandBarClass
    WorkerW
    TabWindowClass
    InternetToolbarHost

    It never finds the status bar control; always declines to execute the line:
    Code:
    If LCase$(zClass) = "msctls_statusbar32" Then
    In case IE itself is the problem: I'm using IE 7.0 (tabbed "sessions"). It has a Yahoo toolbar installed. I bring up the page that I'm monitoring, and status bar messages flash by as it loads. When I move the mouse over the links I'm concerned with, the link information does show in the status bar. These are the messages I need to capture, parse, and work with.


    I used Borge's PBWinSpy to verify that the IE status bar is visible, and WinSpy reports its class, handle and ID. Indeed, it is identified as: msctls_statusbar32

    If WinSpy can see the status bar in IE, why can't the code by Pierre? I've looked it over (to the best of my abilities), but I see no problems...
    (I have little experience programming controls this way, so I'm floundering.)

    I can only guess if there's an Operating System limitation on being able to access controls??

    I know Pierre is a much more experienced programmer than I am, so I'm assuming I've messed something up, perhaps in my IDE? What should I be looking for? (And I'll pre-empt MCM: yes I am looking for a different job! You KNOW I only program occasionally...)


    Thanks,
    -John
    Last edited by John Montenigro; 5 Oct 2008, 04:13 PM. Reason: corretc a few misspleeings

    #2
    >BrowserFrameGripperClass

    Try spying on this one. Maybe Microsoft decided to eschew "msctrls_statusbar32" and created its own registered window class for this application. The "gripper" thing looks about as promising as anything else, since the standard statusbar control has a 'gripper' style option.
    Michael Mattias
    Tal Systems (retired)
    Port Washington WI USA
    [email protected]
    http://www.talsystems.com

    Comment


      #3
      Thanks for the suggestion, Michael.

      I used WinSpy to detect all IE's visible controls and then tried to use those control names in Pierre's code. No success.

      Conclusion: either I'm not searching properly, or those controls have no detectable child components.


      Then I searched all of IE's executable and DLL files for control names and tried more than a dozen promising-looking candidates. No matches.

      Conclusion: IE isn't using any controls with "status" in their name, or else I've again not searched properly...


      Then just for yuks, I searched all DLL files in the Windows/system32 subdirectory for matches on numerous variations of "statusbar", "msctls_", and even just "sb". The only sensible match came from comctl32.dll

      Conclusion: Since nothing else in sight is using "msctls_statusbar32" except for comctl32.dll, and since WinSpy does identify IE's statusbar as "msctls_statusbar32", then IE does invoke comctl32.dll, but I'm just not smart enough to figure out what the statusbar is called, or what it's parent control is.

      So I went back and searched ALL files in system32, and found that the following files contain the string "msctls_statusbar32":
      setupn.exe
      wbocx.ocx
      actskn43.ocx
      wmpstub.exe
      COMCTL32.OCX

      There are limited ways that IE can be creating the statusbar, and I don't know if it's even helpful to know that. If WinSpy can see the control name, Pierre's code must be doing something different. I would like to compare it to Borge's code, but I can't locate any source. Not sure if it's a commercial product?



      The only success I had with Pierre's code was with the TabWindowClass (under ieframe), which returned the name of the page in the Tab that was active when Pierre's code started. It did not return anything new when I switched the browser to another tab...

      Also under ieframe:
      WorkerW returned "Navigation Ba"
      InternetToolbarHost returned "ITBarHos"

      That's as far I've been able to get, but I don't know how to interpret these results in any meaningful way.

      Anyway, it's been a long night, and I need some sleep...

      I appreciate any further suggestions.

      -John

      Comment


        #4
        I think what you might want to try is going at this from another direction.... search for known text and try to find the class of the window containing it.

        Of course, if the control in use is not storing the text (eg using a callback or some kind of owner-draw technique), you are essentially SOL.

        Then again, I have an application where I deliberately do this as a security measure, because the text 'as displayed' is really the value of the software. I spent many many hours developing that data and I really don't want some jamoke stealing it using only some pukey little 'spy' program.
        Michael Mattias
        Tal Systems (retired)
        Port Washington WI USA
        [email protected]
        http://www.talsystems.com

        Comment


          #5
          Just to check... you ARE using the correct message to get the text of a statusbar control, right? You need to use SB_GETTEXTLEN and SB_GETTEXT, not the "WM_" messages.
          Michael Mattias
          Tal Systems (retired)
          Port Washington WI USA
          [email protected]
          http://www.talsystems.com

          Comment


            #6
            Code:
            ' ########################################################################################
            ' This example finds the handle of a running instance of Internet Explorer, enumerates
            ' its child windows to find the handle of the status bar and retrieve the text of the
            ' first part of it.
            ' ########################################################################################
            
            ' SED_PBWIN - Use the PBWIN compiler
            #COMPILE EXE
            #DIM ALL
            #INCLUDE "win32api.inc"
            #INCLUDE "commctrl.inc"
            
            ' ========================================================================================
            ' Callback for EnumChildWindows
            ' ========================================================================================
            FUNCTION EnumChildProc(BYVAL hwnd AS DWORD, BYVAL lParam AS DWORD PTR) AS LONG
               LOCAL szClassName AS ASCIIZ * %MAX_PATH
               GetClassName (hwnd, szClassName, %MAX_PATH)
               IF szClassName = "msctls_statusbar32" THEN
                  IF lParam <> %NULL THEN @lParam = hWnd
                  FUNCTION = %FALSE
               ELSE
                  FUNCTION = %TRUE
               END IF
            END FUNCTION
            ' ========================================================================================
            
            ' ========================================================================================
            ' Main
            ' ========================================================================================
            FUNCTION PBMAIN () AS LONG
            
               LOCAL hWndExplorer AS DWORD                   ' // Internet Explorer handle
               LOCAL hStatusbar AS DWORD                     ' // Status bar handle
               LOCAL hProc AS DWORD                          ' // Process handle
               LOCAL dwProcID AS DWORD                       ' // Process identifier
               LOCAL pMem AS DWORD                           ' // Virtual memory address
               LOCAL nLen AS LONG                            ' // Text length
               LOCAL buffer AS STRING                        ' // General purpose string buffer
               LOCAL dwResult AS DWORD                       ' // Result code
               LOCAL cbRead AS DWORD                         ' // Bytes read
            
               ' Find the window handle of a running instance of Internet Explorer
               hWndExplorer = FindWindow("IEFrame", BYVAL %NULL)
               IF ISFALSE hWndExplorer THEN
                  ? "Internet Explorer isn't running"
                  EXIT FUNCTION
               END IF
               ' Enumerate its child windows
               EnumChildWindows hWndExplorer, CODEPTR(EnumChildProc), VARPTR(hStatusbar)
               ' If found...
               IF hStatusbar THEN
                  ' Retrieve the text length of the first part (0 based)
                  dwResult = SendMessage (hStatusBar, %SB_GETTEXTLENGTH, 0, 0)
                  nLen = LO(WORD, dwResult)
                  ' Allocate an string buffer
                  buffer = SPACE$((nLen + 1))
                  ' Retrieve the process identifier
                  GetWindowThreadProcessID(hStatusBar, dwProcID)
                  ' Retrieve the process handle
                  ' Note For Windows Vista it should be:
                  ' hProc = OpenProcess(%STANDARD_RIGHTS_REQUIRED OR %SYNCHRONIZE OR &HFFFF, 0, dwProcID)
                  hProc = OpenProcess(%STANDARD_RIGHTS_REQUIRED OR %SYNCHRONIZE OR &H0FFF, 0, dwProcID)
                  ' Allocate memory
                  pMem = VirtualAllocEx(hProc, BYVAL %NULL, LEN(buffer), %MEM_COMMIT, %PAGE_READWRITE)
                  ' Retrieve the text
                  dwResult = SendMessage(hStatusBar, %SB_GETTEXT, 0, pMem)
                  ' Read process memory
                  ReadProcessMemory(hProc, pMem, BYVAL STRPTR(buffer), LEN(buffer), cbRead)
                  ' Remove the ending null character
                  IF cbRead THEN buffer = LEFT$(buffer, cbRead - 1)
                  ' Release memory
                  dwResult = VirtualFreeEx(hProc, BYVAL pMem, 0, %MEM_RELEASE)
                  ' Close process handle
                  IF hProc THEN CloseHandle hProc
                  ' Display the string
                  ? buffer
               END IF
            
            END FUNCTION
            ' ========================================================================================
            Changed

            Code:
            dwResult = VirtualFreeEx(hProc, pMem, 0, %MEM_RELEASE)
            to

            Code:
            dwResult = VirtualFreeEx(hProc, BYVAL pMem, 0, %MEM_RELEASE)
            because the 2nd parameter of the VirtualFreeEx function is declared as BYREF ANY in PB's Win32Api.inc.
            Last edited by José Roca; 6 Oct 2008, 11:53 AM.
            Forum: http://www.jose.it-berater.org/smfforum/index.php

            Comment


              #7
              Thanks, Jose! This is going to help me, not only get the job done, but learn how to do it right!!

              Michael, you may have hit it - I see %WM_GETTEXTLENGTH and not the %SB_ variety. I'll change them tonight and test. Never underestimate the experience of a pro!

              As for being a jamoke and stealing codes, that's not me. I encountered the need to read the status bar messages on an earlier project, and not being able to do it made the work about 10x more expensive, as the HTML had to be parsed.

              This time, parsing isn't workable because I need to see the message AS the user puts the mouse pointer over the link.

              It would have been a LOT easier if the webpage author would have provided the info in popups, but instead it's buried in the statusbar message. I've corresponded with them and discussed the value of this for their users, but I haven't been able to reach anyone with an interest in user interface issues...

              Thanks for all the support! I'm in meetings this afternoon, but will be working on this again tonight. I'll post results tomorrow.

              -JohnM

              Comment


                #8
                >...as the HTML had to be parsed

                You'd think there might be an "HTML parser" library available somewhere, kind of like the "XML Parser" library offered by Microsoft.

                For that matter, Cliff, as long as you are into the new COM stuff...
                Code:
                 CLASS "Cliffs_HTML_PARSER"  
                    METHOD Parse 
                    PROPERTY  something 
                  ...
                ???

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

                Comment


                  #9
                  OK, here's the program so far. Notes and questions follow in subsequent posts.

                  This post contains:
                  1. the resource file (I've tried to attach the .pbr, but in case that doesn't work, you have the resource file, but you'll have to provide your own "sbar.ico" file; mine is a 16-color, 32x32, created in Image Editor...)

                  2. one include file,

                  3. the main file.

                  Areas that I'm still working on are marked by "ZCZC" and enclosed between short dividers (----------)

                  The section I'm having trouble with (explanation in next message) is marked with "ZCZC ZCZC".

                  Your comments are welcomed!

                  (Remember, I'm a hobbyist refugee from DOS. I'm still learning how to program with the API, so COM and Objects are not in my skillset. I only get about 10 hours a month to do any programming. So, PLEASE explain WHAT makes your suggestions work better, so that I can learn!)

                  Thanks,
                  -John


                  First, the resource file:

                  Code:
                  //'StatusbarReader.rc
                  //To compile the PBR, remove the comment slashes from the following line
                  #include "resource.h"
                  
                  VS_VERSION_INFO VERSIONINFO
                  FILEVERSION       0,0,0,1
                  PRODUCTVERSION    1,0,0,0
                  FILEFLAGSMASK      VS_FFI_FILEFLAGSMASK
                  //FILEFLAGS          (VER_PRIVATEBUILD|VER_PRERELEASE|VER_DEBUG)
                  FILEFLAGS          0x0
                  FILEOS            VOS__WINDOWS32
                  //FILETYPE           VFT_DLL
                  FILETYPE          VFT_APP
                  FILESUBTYPE       VFT2_UNKNOWN
                  BEGIN
                      BLOCK "StringFileInfo"
                      BEGIN
                          BLOCK "040904E4"    //US English, Multilingual
                  //        BLOCK "040904B0"      //US English, Unicode
                          BEGIN
                              VALUE "CompanyName",      "PB Support Forum Community\0"
                              VALUE "FileDescription",  "IEStatusbar Reader\0"
                              VALUE "FileVersion",      "0.0.0.1\0"
                              VALUE "InternalName",     "IEStatusbarReader\0"
                              VALUE "LegalCopyright",   "\0"
                  //            VALUE "LegalTrademarks1", " "
                  //            VALUE "LegalTrademarks2", " "
                              VALUE "OriginalFilename", "IEStatusbar Reader.exe\0"
                              VALUE "ProductName",      "IEStatusbar Reader\0"
                              VALUE "ProductVersion",   "1.0\0"
                              VALUE "Comment",          "a group effort\0"
                          END
                      END
                  
                      BLOCK "VarFileInfo"
                      BEGIN
                          VALUE "Translation", 0x409, 0x4E4   //US English, Multilingual
                      END
                  END
                  
                  ICON1 ICON sbar.ICO

                  Next is one include file (PBDateToISO.INC)

                  Code:
                  'PBDateToISO.INC
                  
                  Declare Function PBDateToISO (ByVal PBDate As String) As String
                  
                  Function PBDateToISO (ByVal PBDate As String) As String
                     'PB dates are always in this order: mm dd yy(yy)
                     'We want yyyy-mm-dd
                     Local PBDelims, tmpDate, SavedDelim, YYYY, MM, DD As String
                     PBDelims = "-/"
                  '   SavedDelim = "-"  'default to hyphen
                     tmpDate = PBDate
                  
                     If tmpDate = "" Then tmpDate = Date$
                     SavedDelim = Mid$(tmpDate, InStr(tmpDate, Any PBDelims), 1)
                  
                     MM = Extract$(tmpDate, Any PBDelims)
                     If Len(MM) = 1 Then MM = "0" & MM
                     tmpDate = Remain$(Trim$(tmpDate, Any PBDelims), Any PBDelims)
                     DD = Extract$(tmpDate, Any PBDelims)
                     If Len (DD) = 1 Then DD = "0" & DD
                     YYYY = Remain$(Trim$(tmpDate, Any PBDelims), Any PBDelims)
                     If Len(YYYY) < 4 Then YYYY = String$(4-Len(YYYY), "0") & YYYY
                  
                     Function = YYYY & SavedDelim & MM & SavedDelim & DD
                  End Function


                  And finally, the program:

                  Code:
                  'IEStatusbar Reader.bas
                  '
                  'Using as the base code: Jose Roca's EnumIEChildren.bas from:
                  'http://www.powerbasic.com/support/pbforums/showpost.php?p=298086&postcount=6
                  '
                  'I'm trying to add Pierre Bellisle's listbox code from:
                  'http://www.powerbasic.com/support/pbforums/showpost.php?p=280811&postcount=12
                  '
                  'I'm adding a few small features to make it more useable. (eg, write to file, copy to clipboard, etc.)
                  '===========================================================================
                  
                  'ToDo:
                  'DONE- Add a "Send to File" command button
                  'DONE- Add a "Send to File" FUNCTION
                  '- Process commandline params for: "confirm prompts", filename, other???
                  'DONE- Add a resource file with StringFileInfo and icon
                  '- When user clicks an entry in the listbox, the Clipboard button should get focus...
                  '   (ie, change focus on buttons when a line in listbox is selected for copying to clipboard, reset later..)
                  
                  'NOTES:
                  '1. By default, "Confirm prompts" is OFF
                  '2. This program will only grab the status bar messages for the Tab pane that is open when we start...
                  '3. If a SB message is longer than the first part of the SB, it not might be fully displayed; BUT
                  '     as long as the text is not "physically" truncated by the webpage, we will get the whole text.
                  '4. If the webpage truncated the SB message text, we have no way to obtain the truncated portion (maybe search the HTML?)
                  '
                  
                  
                  ' ########################################################################################
                  ' This example finds the handle of a running instance of Internet Explorer, enumerates
                  ' its child windows to find the handle of the status bar and retrieves the text
                  ' ########################################################################################
                  ' This works even when the status bar is not visible... (turned off in the View menu)
                  
                  #Compile Exe  "c:\tools\IEStatusbarReader.exe"
                  #Dim All
                  #Include "win32api.inc"
                  #Include "commctrl.inc"
                  #Resource "StatusbarReader.pbr"
                  
                  Declare Sub Clipboard_SetText(ByVal Txt As String)
                  
                  #Include "e:\win32api\PBDateToISO.INC"
                  
                  %LISTBOX                = 101
                  %CMD_CopyToClipboard    = 102
                  %CMD_WriteToFile        = 103
                  %CMD_Quit               = 104
                  
                  Global hDlg       As Dword '
                  Global ThreadKill As Long
                  Global hList      As Dword
                  Global gConfirm   As Long  'to enable confirmation prompting, we need to set this somewhere...
                  
                  ' ========================================================================================
                  ' Callback for EnumChildWindows
                  ' ========================================================================================
                  Function EnumChildProc(ByVal hwnd As Dword, ByVal lParam As Dword Ptr) As Long
                     Local szClassName As Asciiz * %MAX_PATH
                     GetClassName (hwnd, szClassName, %MAX_PATH)
                     If szClassName = "msctls_statusbar32" Then
                        If lParam <> %NULL Then @lParam = hWnd
                        Function = %FALSE
                     Else
                        Function = %TRUE
                     End If
                  End Function
                  
                  ' ========================================================================================
                  Function FindIEStatusBarText(ByVal hDlg As Dword) As Dword
                     'for Jose's code:
                     Local hWndExplorer As Dword                   ' // Internet Explorer handle
                     Local hStatusbar As Dword                     ' // Status bar handle
                     Local hProc As Dword                          ' // Process handle
                     Local dwProcID As Dword                       ' // Process identifier
                     Local pMem As Dword                           ' // Virtual memory address
                     Local nLen As Long                            ' // Text length
                     Local buffer As String                        ' // General purpose string buffer
                     Local dwResult As Dword                       ' // Result code
                     Local cbRead As Dword                         ' // Bytes read
                  
                     'for my code:
                     Local AppTitle As String
                     AppTitle = "Statusbar Reader"
                     Local msg As String, retval As Long
                  
                     'for Pierre's Listbox:
                     Local ListboxCount  As Long
                     Local sBuffer       As String
                     Local sOldBuffer    As String
                  
                     ' Find the window handle of a running instance of Internet Explorer
                     hWndExplorer = FindWindow("IEFrame", ByVal %NULL)
                     If IsFalse hWndExplorer Then
                        ? "Internet Explorer isn't running",, "StatusBar Reader"
                        ThreadKill = 1
                        Exit Function
                     End If
                  
                  'ZCZC
                  '----------
                  'Hmmm... what if we're busy working, then user closes IE??
                  'Should the above test be repeated inside the DO loop that comes next?
                  '----------
                  
                     ' Enumerate its child windows
                     EnumChildWindows hWndExplorer, CodePtr(EnumChildProc), VarPtr(hStatusbar)
                     ' If found...
                     If hStatusbar Then
                     Do
                        ' Retrieve text length of the first SB part (0 based)   ("first part" refers to leftmost SB section, if divided)
                        dwResult = SendMessage (hStatusBar, %SB_GETTEXTLENGTH, 0, 0) 'any way to get the whole thing? retrieve all parts
                        nLen = Lo(Word, dwResult)
                        ' Allocate a string buffer
                        buffer = Space$((nLen + 1))
                        ' Retrieve the process identifier
                        GetWindowThreadProcessID(hStatusBar, dwProcID)
                        ' Retrieve the process handle
                        ' Note For Windows Vista it should be:
                        ' hProc = OpenProcess(%STANDARD_RIGHTS_REQUIRED OR %SYNCHRONIZE OR &HFFFF, 0, dwProcID)
                        hProc = OpenProcess(%STANDARD_RIGHTS_REQUIRED Or %SYNCHRONIZE Or &H0FFF, 0, dwProcID)
                        ' Allocate memory
                        pMem = VirtualAllocEx(hProc, ByVal %NULL, Len(buffer), %MEM_COMMIT, %PAGE_READWRITE)
                        ' Retrieve the text
                        dwResult = SendMessage(hStatusBar, %SB_GETTEXT, 0, pMem)
                        ' Read process memory
                        ReadProcessMemory(hProc, pMem, ByVal StrPtr(buffer), Len(buffer), cbRead)
                        ' Remove the ending null character
                        If cbRead Then buffer = Left$(buffer, cbRead - 1)
                        ' Release memory
                        dwResult = VirtualFreeEx(hProc, pMem, 0, %MEM_RELEASE)
                        ' Close process handle
                        If hProc Then CloseHandle hProc
                        ' Display the string
                        '? buffer
                  
                        'If cbRead Then
                        If Len(Trim$(buffer, Any $Spc & Chr$(0))) > 0 Then 'how is it that we are still getting some blank lines????
                           sBuffer = buffer  'to make the transition from Jose's code to Pierre's
                                             ' (not sure if Jose was using buffer for multiple purposes...)
                  
                           'If this message is NOT the same as the last message, then insert the content of buffer into the listbox
                           If sBuffer <> sOldBuffer Then               'Is it different from previous message
                              ListboxCount = SendMessage(hList, %LB_GETCOUNT,  0, 0) 'Ask listbox for items count
                              SendMessage(hList, %LB_ADDSTRING, ListboxCount, StrPtr(sBuffer)) 'Add message to listbox
                              SendMessage hList, %LB_SETCURSEL, ListboxCount, 0 'Go to last listbox position
                           End If
                           sOldBuffer = sBuffer                        'Backup sBuffer to avoid sending same message
                        End If
                        Sleep 25  'needed??   Yes, indeed!! else LOTS of messages are missed!
                     Loop
                     Else
                        MsgBox "No statusbar found.",,AppTitle
                        Exit Function
                     End If
                  End Function
                  
                  ' ========================================================================================
                  Sub Clipboard_SetText(ByVal Txt As String)
                  'swiped from POFFS postings under Windows Compiler (Scott Turchin Mar16, 99) also Mike Trader Apr 5, 06
                     Local lpMem As Asciiz Ptr
                     Local hMem  As Dword
                  
                     ' Allocate global memory block
                     hMem  = GlobalAlloc(%GHND, Len(Txt) + 1)
                     lpMem = GlobalLock(hMem)
                  
                     'THIS CAUSES A GPF IN 32 BIT!
                     ' copy text into memory object
                     @lpMem = Txt
                  
                     ' unlock the memory object
                     GlobalUnlock hMem
                  
                     'Open and Empty clipboard:
                     OpenClipboard 0
                     EmptyClipboard
                  
                     ' add text to the clipboard
                     SetClipboardData %cf_text, hMem
                     CloseClipboard
                  End Sub
                  
                  ' ========================================================================================
                  ' Callback functions
                  ' ========================================================================================
                  CallBack Function DlgProc() As Long
                   Static hThread  As Dword
                   Local  sBuffer  As String
                   Local  Retval   As Long
                  
                   'Placement of this exit code before the SelectCase is CRITICAL to a clean exit when no IE is running...
                   If ThreadKill = 1 Then Dialog End Cb.Hndl, 0 ' Return 0
                  
                   Select Case CbMsg
                  
                     Case %wm_initdialog
                       hList = GetDlgItem(CbHndl, %LISTBOX)                   'Get listbox handle
                       sBuffer = "Waiting for ie statusbar message"           'Prepare message
                       SendMessage(hList, %LB_ADDSTRING, 0, StrPtr(sBuffer))  'Send message to listbox
                  
                       Thread Create FindIEStatusBarText(CbHndl) To hThread   'Create a thread that will loop
                       Thread Close hThread To Retval                         'Release the thread handle
                  
                  'ZCZC ZCZC  Current area I'm having difficulty with!!!
                  '----------
                     Case %wm_command
                        'we let these messages get processed here by not giving the LB a callback...
                        If Cb.CtlMsg = %lbn_selchange Then 'how to get ENTER to activate the button
                  '      if Cb.CtlMsg = %LBN_SELCHANGE or Cb.CtlMsg = %lbn_setfocus Then
                           'When LB gets focus, make CopyToClipboard the default button
                  
                  'is one of these preferred?
                  '         Control Set Focus CbHndl, %CMD_CopyToClipboard
                     '      Control Set Focus hDlg, %CMD_CopyToClipboard
                  
                    '       local hBtn as dword
                    '       hBtn = GetDlgItem(CbHndl, %CMD_CopyToClipboard)
                    '       SendMessage(hBtn, %BN_SETFOCUS, 0, 0)
                           'SendMessage(hBtn, %BM_CLICK, 0, 0)
                           'SendMessage(%CMD_CopyToClipboard, %BM_CLICK, 0, 0)
                           Control Set Focus hDlg, %CMD_CopyToClipboard
                           SendMessage(%CMD_CopyToClipboard, %wm_activate, 0, 0)
                  
                           'SetFocus (%CMD_CopyToClipboard)  'in WIN32API.inc
                  
                           MessageBeep (%mb_iconexclamation) ' just during testing; let's me know when we reach this point...
                  
                           Function = 1 'needs no further processing
                        End If
                  '----------
                  
                     Case %wm_destroy
                      ThreadKill = 1                                          'Tell the thread to end
                      'I think this only had meaning in Pierre's original code... does nothing here? (test by commenting out)
                  
                   End Select
                  End Function
                  
                  ' ========================================================================================
                  CallBack Function CB_WriteToFile() As Long
                     Local lResult, OutBuf, ListboxCount, i, ItemLength As Long
                     Local LogFile, sBuf As String
                     Local msg As String, retval As Long
                  
                     If Cb.Msg = %wm_command And Cb.CtlMsg = %bn_clicked Then
                        ListboxCount = SendMessage(hList, %LB_GETCOUNT,  0, 0) 'Get listbox item count
                  
                        If gConfirm Then
                           lResult = MsgBox ("Dump " & Trim$(Str$(ListboxCount)) & " lines of text from the listbox to a file?",%mb_yesno,"Confirm File Write")
                           If lResult <> %idyes Then Exit Function
                        End If
                  
                        'create a target filename and open it
                        LogFile = Remove$(PBDateToISO (Date$), Any "-/") & " " & Remove$(Time$, Any ".:")& " IEStatusbar Reader" & ".log"
                  
                        OutBuf = FreeFile
                        Open LogFile For Output As #OutBuf
                  'ZCZC
                  '----------
                  'need to add error-checking...
                  '----------
                  
                        For i = 0 To ListboxCount -1 'adjust for 0-based index
                           ItemLength = SendMessage(hList, %LB_GETTEXTLEN, i, 0) 'get the length of the current item
                           sBuf = Space$((ItemLength + 1))
                           SendMessage(hList, %LB_GETTEXT, i, StrPtr(sBuf)) 'retrieve item's text
                           Print #OutBuf, Trim$(sBuf, Any $Spc & Chr$(0))   'output a clean string; no we're not truncating it
                        Next i
                        Close #OutBuf
                  
                        'notify user that the write is done:
                        Sleep 850  'perceptible pause for the user to grasp that the write has occurred...
                        '- change the text on the write button to flash "Done!" (would need to reset it later)
                        '- PB Help says to check out: PlaySound   or   mciSendString
                        ' Shell "c:\WINDOWS\Media\notify.wav"  'can I load this into a memory space, and run it from there? (faster reponse?)
                        MessageBeep (%mb_iconasterisk)    'SystemAsterisk
                        '
                        Function = 1 'tells parent dialog that the event message needs no further processing...
                     End If
                  End Function
                  
                  CallBack Function CB_CopyToClipboard() As Long
                     'we only copy the current line (want more? WriteToFile, then do your own cut&paste)
                     Local CurrentItem, ItemLength As Long
                     Local sBuf As String
                     If Cb.Msg = %wm_command And Cb.CtlMsg = %bn_clicked Then
                        CurrentItem = SendMessage(hList, %LB_GETCURSEL,  0, 0) 'Get 0-based index of current listbox item
                        ItemLength = SendMessage(hList, %LB_GETTEXTLEN, CurrentItem, 0) 'get the length of the current item
                        sBuf = Space$((ItemLength + 1)) 'create a buffer
                        SendMessage(hList, %LB_GETTEXT, CurrentItem, StrPtr(sBuf)) 'retrieve item's text
                        sBuf = Trim$(sBuf, Any $Spc & Chr$(0)) 'clean up the text
                        Clipboard_SetText(sBuf & $CrLf)   'copy sBuf to the clipboard
                        MessageBeep (%mb_iconasterisk)    'make a noise to indicate OK
                        Function = 1 'needs no further processing
                     End If
                  End Function
                  
                  CallBack Function CB_Quit() As Long
                     Local lResult As Long
                     If Cb.Msg = %wm_command And CbCtlMsg = %bn_clicked Then
                        If gConfirm Then
                           lResult = MsgBox ("Are you sure?",%mb_yesno,"Quit?")
                           If lResult = %idno Then Exit Function
                        End If
                        Dialog End Cb.Hndl, 0 ' Return 0
                        Function = 1
                     End If
                  End Function
                  
                  ' ========================================================================================
                  ' Main
                  ' ========================================================================================
                  Function PBMain () As Long
                     'Local hDlg As Dword, Result As Long
                     Local Result As Long
                     Local Cmd As String
                  
                  'ZCZC
                  '----------
                     'check commandline; parse for filespec and Confirm switch
                     'Cmd$ = command$
                     'gConfirm = %TRUE
                  '----------
                  
                     Dialog New %HWND_DESKTOP, "Read IE StatusBar", , , 500, 275, _
                        %ws_caption Or %ws_minimizebox Or %ws_sysmenu, 0 To hDlg
                  
                  
                  'Still puzzling out: how to get my "sbar.ico" to show in the title bar... trying lots of alternatives, no success yet...
                  'ZCZC  
                  '----------
                  '   Control Set Focus hDlg, %LISTBOX  '
                  '   SetClassLong hDlg, %GCL_HICON, LoadIcon(ByVal %NULL, ByVal %IDI_INFORMATION) 'Set dialog icon - this works, but generic
                     '
                     'try pointing to the icon that's in the recource module:
                     Local AppIcon As String
                     AppIcon = "ICON1" & Chr$(0)   'tried both ways; no go
                  '   SetClassLong hDlg, %GCL_HICON, LoadIcon(ByVal %NULL, byval strptr(AppIcon)) 'why not seeing icon from .rc file?
                     '
                     'alternatively, try loading icon via LoadImage:
                  '   LoadImage hDlg, ByVal StrPtr(AppIcon), %IMAGE_ICON, 0, 0, 0
                     '
                     'try loading from file:
                  '   AppIcon = "sbar.ico"& Chr$(0)
                  '   LoadImage hDlg, byval StrPtr(AppIcon), %IMAGE_ICON, 0, 0, %LR_LOADFROMFILE
                     Local IconHndl As Long
                     IconHndl = FindResource (%NULL, ByVal StrPtr(AppIcon), ByVal %RT_GROUP_ICON)
                    '' ? Str$(IconHndl),,"IconHndl"
                     LoadResource(hDlg, IconHndl)
                     SetClassLong hDlg, %GCL_HICON, LoadIcon(ByVal %NULL, ByVal StrPtr(AppIcon)) 'why not seeing icon from .rc file?
                  '   SetClassLong hDlg, %GCL_HICON, IconHndl) 'why not seeing icon from .rc file?
                     DrawIcon (hDlg, 0, 0, ByVal IconHndl)
                  '----------
                  
                     'create buttons in the desired z-order:
                     Control Add ListBox, hDlg, %LISTBOX, , 5, 5, 490, 240, _
                        %ws_child Or %ws_visible Or %ws_tabstop Or %ws_vscroll, %ws_ex_clientedge
                  
                     Control Add Button, hDlg, %CMD_CopyToClipboard, "Copy current line to &Clipboard", 249, 248, 105, 18, %ws_tabstop Call CB_CopyToClipboard
                     Control Add Button, hDlg, %CMD_WriteToFile, "Write all lines to &File", 366, 248, 75, 18, %ws_tabstop Call CB_WriteToFile
                     Control Add Button, hDlg, %CMD_Quit, "&Quit", 453, 248, 35, 18, %ws_tabstop Call CB_Quit
                  
                     Dialog Show Modal hDlg, Call DlgProc To Result
                  
                  End Function
                  Attached Files
                  Last edited by John Montenigro; 8 Oct 2008, 02:48 PM. Reason: fixed 1 line with broken IF, commented out 1 test msgbox

                  Comment


                    #10
                    I know a lot of you folks have long since mastered API programming and COM, and are now into PB with Objects, but I'm still struggling with an old DOS mindset to reach that first level of mastering the API calls.

                    I'm an occasional programmer, not a pro. If I get to spend 10 hours a month on developing my ideas through code, that's usually a lot. (I love the challenge, but I have SUCH a huge learning curve! For me, to make a struggling company profitable is a lot easier!)

                    The situation is this: I am not seeing the proper interaction between certain event triggers and the reactions that are responded to by certain tests in my DlgProc callback. (look around line 207) Perhaps you can help me see the light...



                    This is a simple form with a ListBox and three command buttons. When/if the user clicks on a line in the listbox, I want a particular button to get focus, so all the user has to do is hit Enter and the button will process the selected item from the listbox.

                    I have been pulling my hair out (and there wasn't that much there to begin with)! Seems that when I test for certain conditions, the listbox goes dead, and I just don't understand why. Also, when I have it close to what I want, it takes hitting the TAB key to get the button to highlight.

                    As you can see, I do a lot of trial-and-error coding, testing what I've read to understand what was meant. Sometimes it's easier than others. In this case, it's more difficult.

                    I know I'm dealing with interactions between the z-order in which the controls were placed on the dialog form, the interactions with the callbacks for the individual controls, the callback for the dialog, and I'm not sure but maybe also which control is made the default. Also, I recognize that there are probably more messages that I should pay attention to, and probably some that I'm using that aren't helping. I've read PB and MS online help dox, and pored thru several Win32 books, but I'm just not seeing it.




                    OK, so the project is fairly straightforward: the program captures messages from IE's statusbar.

                    I have taken Jose Roca's code and woven in some of Pierre Belisle's code. I then added a lot of my own code to make the interface more useable for me (and that's where I'm having trouble).

                    The program grabs messages from the statusbar in an open IE frame and copies them to the listbox. One button dumps all items from the listbox to a file, and the other button copies the selected item to the clipboard.

                    There are still a few things I want to add, but I need to get past this particular issue first.

                    Any help you can offer would be greatly appreciated!!

                    Struggling in New Joisey,
                    -John

                    Comment


                      #11
                      Just a thought.....

                      What exactly are you trying to learn from the statusbar message text?

                      Maybe there is another way to accomplish this.
                      Michael Mattias
                      Tal Systems (retired)
                      Port Washington WI USA
                      [email protected]
                      http://www.talsystems.com

                      Comment


                        #12
                        A smorgasbord of hair thinners!
                        Here are a few answers..

                        Remove hThread code elements - was used in Pierre's do - loop to stop the loop running on after the prog ends. No longer needed.

                        Let the compiler take care of the icon (best if 32 x 32)..
                        Code:
                           Dialog Set Icon hDlg, "ICON1"
                           [COLOR=dimgray]Dialog Show Modal hDlg, Call DlgProc To Result[/COLOR]
                        Deal with the default WinXP(+) behaviour which hides keyboard ques - until Alt key pressed, or focused by Tab key.
                        Code:
                        [COLOR=gray]Control Add Button, hDlg, %CMD_CopyToClipboard, "Copy current line to &Clipboard", 249, 248, 105, 18, %ws_tabstop Call CB_CopyToClipboard[/COLOR]
                        Control Send hDlg, %CMD_CopyToClipboard, %WM_UPDATEUISTATE, MAKLNG(%UIS_CLEAR, %UISF_HIDEFOCUS OR %UISF_HIDEACCEL), 0
                        The way you were setting focus was fine - just not visble due to the hidden ques issue. This shows one way to trap the Return key..
                        Code:
                         
                            Case %WM_COMMAND
                              If Cb.Ctl = %LISTBOX Then ' Check which control. Maybe you'll add a second listbox one day ;)
                                If Cb.CtlMsg = %LBN_SELCHANGE Then
                                  Control Set Focus hDlg, %CMD_CopyToClipboard    'Put focus onto button, ready for Space bar or Enter activation
                                End If
                              End If 
                              ' Take advantage of a default dialog behaviour - %IDOK, %Bn_Clicked is sent to a dialog when Enter is pressed
                              If Cb.Ctl = %IDOK And Cb.CtlMsg = %BN_CLICKED Then  'Enter Key has been pressed. Where is the focus?
                                If GetFocus = GetDlgItem(Cb.Hndl, %LISTBOX) Or GetFocus = GetDlgItem(Cb.Hndl, %CMD_CopyToClipboard) Then
                                  ' focus is on the listbox or the clipboard button so simulate a click
                                  Control  Send Cb.Hndl, %CMD_CopyToClipboard, %BM_CLICK, 0, 0
                                  ' doesn't actually 'move' the button but the notification msg is sent as if it had been
                                End If
                              End If
                        HTH
                        Rgds, Dave

                        Comment


                          #13
                          Dave,

                          A smorgasbord, indeed!

                          I REALLY appreciate your feedback. It's going to take me some time to work through each and squeeze out some more tidbits of precious knowledge.

                          Again, Thanks!


                          Michael,

                          As I'm doing research on various topics, I've found that certain websites display critical data in the statusbar and nowhere else, unless I want to grab the HTML and parse it. This isn't always possible, as some pages seem to be built dynamically.

                          For example: at the end of their stories, one news site provides a section of "related links". In deciding whether or not to persue such a link, I need to know the approximate date that the target article was created. For my work, older articles have less significance, and it saves me a lot of time and effort to not go down a lot of dead-ends.

                          On this particular site, the text of the link displays only the name of the article but not the date. (I have asked them repeatedly to include it, but they have not seen any value to THEM for doing so. Nevermind that it would have value to THEIR USERS!?!)

                          At any rate, I discovered that they store their articles by date, and guess what? The date is encoded in the message that shows on the statusbar when the mouse pointer hovers over a link!

                          TaDa! When I get done with this little statusbar reader, I will have a companion window open that will decode the dates and display them (in a sufficiently large font) so that I can make better decisions and stay productive!

                          Other than parsing the whole page, I couldn't think of another way to get the info I need. Besides, that would be a batch process/evaluation, whereas this little utility will be more immediate.

                          I'd be more than happy to learn of other alternatives, but I can't deny how much I learn from this kind of exercise, and it helps me from getting too far behind in programming skills, which I have always enjoyed but don't get to do as much as I used to.

                          Best regards,
                          -John

                          Comment


                            #14
                            You mean like the full link which is displayed in the status bar when you move the mouse over a link like this?

                            Typical Underlined Blue Link Text Here

                            There's got to be an IE function you can tap into to get that.
                            Michael Mattias
                            Tal Systems (retired)
                            Port Washington WI USA
                            [email protected]
                            http://www.talsystems.com

                            Comment


                              #15
                              Dave,

                              OK on the thread and icon... thanks! As for the focus thing - sheesh! I can understand and follow most of that - but wow, what contortions! Shows me how I have to refine my thinking about messages.

                              I had originally created a callback for the listbox that looked similar, but when I ran into problems, I dropped it and moved "up" to the DlcProc and tested wm_command. But I can now see how I was trying to handle everything in one test, where from your code, I can see how the second part needs a separate test.

                              Means that I wasn't seeing how the separate messages were occurring, nor how they had to be handled separately.

                              Good lesson!

                              Also, seeing WM_UPDATEUISTATE in your code, I tried to look it up but it's not in my Win32 Help file. Is that something new?

                              Thanks again,
                              -John

                              Comment


                                #16
                                Michael,

                                Yep! That's it exactly!

                                Maybe there is an IE function, but I haven't been able to find anything on it.

                                -jhm

                                BTW - Here's your text, as found, gathered, copied to the clipboard in this utility, and pasted into this message directly from the clipboard by the forum software:

                                http://this_is_not_an_cctual_link._i...talking_about/
                                Last edited by John Montenigro; 9 Oct 2008, 01:32 PM. Reason: inserted captured statusbar text from clipboard

                                Comment


                                  #17
                                  StatusTextChange Event

                                  --------------------------------------------------------------------------------

                                  Fires when the status bar text of the object has changed.

                                  Syntax

                                  Private Sub object_StatusTextChange( _
                                  ByVal sText As String)
                                  ....
                                  My SDK containg this info is on disk but this info has to be online at the Microsoft web site.

                                  There's a ton of Events and properties available for the Internet Explorer Object, and unless I mistaken with the new compilers you can use em all.

                                  Try your COM BROWSER and look for something with an "InternetExplorer Object"
                                  Michael Mattias
                                  Tal Systems (retired)
                                  Port Washington WI USA
                                  [email protected]
                                  http://www.talsystems.com

                                  Comment


                                    #18
                                    To connect with the events fired by the WebBrowser Control, you first have to retrieve a reference to the IWebBrowser2 interface.

                                    Here is how to do it:


                                    and pray that nobody will close Internet Explorer.

                                    To have everything controlled, the best way is to embed an instance of the WebBrowser Control in your application and navigate to the wanted web page.

                                    There are a couple of examples in my forum:

                                    Mini WebBrowser: http://www.jose.it-berater.org/smffo...p?topic=2826.0

                                    Tabbed MDI WebBrowser: http://www.jose.it-berater.org/smffo...p?topic=2832.0
                                    Forum: http://www.jose.it-berater.org/smfforum/index.php

                                    Comment


                                      #19
                                      Try your COM BROWSER and look for something with an "InternetExplorer Object"
                                      Yikes! You're really gonna nudge me into the new stuff, aincha?

                                      OK, I'll give it try, but I'm just about out of programming time for this month. I promise I'll start reading up on COM in between primary projects, commuting, and waiting for kids at music lessons.

                                      (I may complain, but I know I really do need to take the plunge...)

                                      Any beginner's COM books you can suggest?

                                      Thanks,
                                      -John

                                      Comment


                                        #20
                                        Jose,

                                        Thanks again for your support.

                                        How can I tell if I have MSAA installed, and where can I read up about what it is and what it does?

                                        Seems I don't have the Include files your code needs, so it's going to take me some time to get going with it. Where are they from?



                                        I have to tackle projects that are a good "reach", but not so much as a "leap". While it makes sense to create a browser and add my own functions, I would have to decline your suggestion to build these functions into my own browser:

                                        In the environment I'm doing this, IE is the required tool. I'm thinking I would have to duplicate IE, a task that I can only imagine would be way out of my league. Little utilities I can do; they're limited in scope, give me just enough from which to learn a little more, and they do a useful task.

                                        As things stand now, it will take me awhile to learn all I need just to try the COM stuff that Michael's suggesting.

                                        So, with respect to your superb skills, to my own time and state of ignorance, and to Clint Eastwood: "A man's got to know his limitations."



                                        Just so you know, I'm returning to my primary project on Monday, so I probably won't be able to follow up for a few weeks, anyway.


                                        Where else in the world is there the quality of support like in this PB community? I want all you folks to know how much it means to amateurs like me! And I hope Mr. Zale knows it, too!

                                        Thanks, all!
                                        -John

                                        http://www.powerbasic.com/support/pb...992#post299992
                                        Last edited by John Montenigro; 23 Oct 2008, 09:23 PM. Reason: added link to Source Code posting

                                        Comment

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