Page 1 of 3 123 LastLast
Results 1 to 10 of 22

Thread: Rough Notes, and posts to be referenced from elsewhere, on VBA Windows API

Hybrid View

Previous Post Previous Post   Next Post Next Post
  1. #1
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,468
    Rep Power
    10

    Rough Notes, and posts to be referenced from elsewhere, on VBA Windows API

    Rough Notes on VBA Windows API Introduction Part 1


    If, for now we restrict ourselves, to the subject area of Excel VBA Windows API, we can consider us to be talking most often about another, and/or similar to other ways, ( such as the so called External shared libraries ), to control or communicate with things outside of Excel, or even sometimes in Excel.
    More broadly speaking we are controlling or communicating with windows. (An existing window is often seen as based on a Class, and we are messing with the window/ manipulating the window, so what we are doing may sometimes be regarded as Sub Classing)

    Manipulating "Windows”.
    It would appear initially that the word “Windows” is a name for a programming idea which might result in something we “see” as what we conceive as Windows. But, a window is a vague concept. It includes what we see as windows and other things.
    Manipulating of the actual “Windows” seems the key to pseudo “making my own” Class or of a API Function or a Window thing from it
    Doing this in any language is a task for a computer genius, and in Visual Basic, (In particular Visual Basic for Applications), the documentation is very sparse. But “ API User 32 dll Programs” would appear to make this possible.
    It would appear that direct linked libraries (dll) are available to run as and when required, hence the wording of direct link: They are used as an efficient means to organise Microsoft’s software generally allowing different Applications to share smaller programs which are shipped as standard with the Microsoft Windows Operating system. They are however also available to programmers, programming the applications. Hence Application Programming Interface
    There are some similarities between a .dll file and a .exe file. The main difference is that we usually need to organise how and when it is used in Windows, hence I say Manipulating "Windows"

    API , “API Calls
    Such things get bundled up in an imprecise intimidating term API, for Application Programming Interface. They are usually contained in a Folder with a name similar to User 32.
    Another seemingly intimidating phrase is “API call”. You may hear the term “I am using API calls”. It just means usually that you are using those things and related “Windows” concept
    I have been told by some professionals that in actual fact these Library programs are organised in a similar way to the Libraries that one can pseudo Import by “checking a reference” in the list of available to VBA code libraries. However by some subtlety that they are not sure about they cannot be used in a code in the way of through declaring ( Dim ing ) them and then after assigning a variable using that variable to “get at” the various Methods / Functions inside them. Perhaps they are slightly more run time things, even though I have heard that the other Libraries are as well. Perhaps it can depend on the exact thing.
    When we are involved with VBA, it is difficult sometimes perhaps to distinguish between an end user and a professional programmer. The so called External shared libraries may be regarded as for the end user, whereas the API things could be regarded as intended for a programmer.
    In place of the normal declaring ( Dim ing ) that would be within a routine, in the case of the Library programs being used here, you must do a sort of initial globial type Declaration.

    Declareing Declare Type Functions
    You don’t always need the AliAs bit in these things. ( It just means _ this Lib "user32" _ Ali As ¬_ that _ (that is the Microsoft name , this is any name that I choose to use) ). Occasionally something can only be done to the AliAs where numbers and variable used to refer to things are concerned. It is subtle general point in computing that you might get problems when a number is used to refer to something that might take or give a number at some point. But you might need to do that, so having an intermediate word is a workaround for that so that the number is set to a word which is then related to a word that might be being referred to or returning a number.
    Function = Word
    Word = 873248
    So the Function can be referred to by a number indirectly, --- occasionally this may not be possible directly, --- Function =837547 might error for subtle computer reasons.

    It seems to do no harm to use an AliAs when you don’t need it and it helps to make a code prettier.

    Once Declared you can think of them to a first approximation as a function written in a code module in the Folder on your computer with the name something like “User32” or “User32dll” or similar. You then use them to a very crude approximation as you would any conventional function that you may have made and which is typically in a VBA code module, like pseudo
    _ x = SetWindowsHookExample( 3 , y , _..__… etc )
    x would need to be a variable declared at the top of the module I think, as would possibly be some of the signature line arguments in the Function, but note those arguments could also be a pseudo function, - pseudo as the address/ location of the function is given. (That function may, for example, be set off by something going on in a window at some point). The possibilities and construction of the signature line in a API Declare Function line are not as simply defined as in a standard VBA Function


    For use in a normal code you can use Private or Pubic. As in convectional VBA Functions Pubic will not confine the use of the function to the macro module in which it is in.
    For a class code module, such as a worksheet code module ( To get there, right click the worksheet's tab and select View Code ), these Declare type functions must be Private

    Owned “Windows”, and/ or z order.
    It is well above my knowledge to explain all concepts here, and as noted some things will have to be read as “on the tin” or in other words its faecile value.
    A Pop up is apparently always the one on top of to be seen ( “above on the screen “z axis” “ , - as a approximation the z axis is in the direction looking at it ) of the Window to which they belong and they always “belong”” to a parent window… well maybe something is not quite clear there…
    It is not always clear what “z option” does what, and even professionals sometimes seem to choose it from trial and error .
    But anyway these are two things that will need to be taken into the equation… or rather the “API calls” that we do..

    Hooking a “Window” to Handle it ..Computer Bollox terminology.
    I have needed to get some terms undefined correctly. Words like Handle and Hook are computer terms similar to the word Bollox in normal language and can be used alone or in conjunction with other words to have some meaning possibly in the context in which they are used but cannot have any precise meaning. Defining them as some computer bollox to do with handling and identifying Windows is a useful way to understand these terms.
    Some handle bollox will need to be taken into the equation… or rather the “API calls” that I do..
    Some published literature even supports my somewhat naive and critical resume, saying the words can mean a number of things. In our case the handle can be thought a number identifying a Window. A Hook can be thought of as hook or trip trap placed in some run or chain of events cause shuddering or jerking off of a procedure.


    Handleing
    When doing VBA Windows API coding, a "handle" seems to play a major role. It is an identification number / address/ pointer , or similar, which is required in much coding, as one might reasonably expect, in order that a coding knows which window or windows that we want to manipulate. One problem/s is that, although a window may have some known fixed name, this number is more often what is required in coding, and those numbers are not fixed, but rather are somehow generated and given each time to a software when it us running so that that software can access the windows, without us knowing any specific memory location/ address of things. Possibly that is done to make it more difficult to hack things . We are not privy to exactly how the numbers are generated, so we can consider them as random. ( Not all possible numbers are used, so it is possible that the same number is re used, but it is random chance if it is).
    To make things worse,
    _ getting the number seems to be not always reliable, and not all things that should do work.
    _ to get at most windows would require some sort of navigating of an explorer tree like structure.
    There are several API functions, that is to say Declareation Functions available to get the handle, and one or more may need to be used for a particular coding situation.
    So getting the handle/ using handle related Declareation Functions can be a good start point when learning VBA Windows
    Last edited by DocAElstein; 11-11-2024 at 01:05 PM.

  2. #2
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,468
    Rep Power
    10

    Dumping Logs. Recurring Excample

    Dumping Logs for support of this Thread Post:
    http://www.excelfox.com/forum/showth...0476#post10476

    Test Function used to produce the Log below

    Code:
    'Going a HoldYaBackCalledYaBackClapTrapRuc - Copy number_GlobinalCntChopsLog - a few copies of this are made and run. (Recursion)
    '_-=Rem 4===================??? Got me hook lochprocedue in my code ,                5 times simple run then  another + 29 new copies of it are run  = 5+30=35 times  in total                     calling it it a few times  http://www.excelfox.com/forum/showthread.php/1324-Loop-Through-Files-In-A-Folder-Using-VBA#post10421   .... wanking myself up and down a few times
    Private Function HoldYaBackCalledYaBackClapTrapRuc(ByVal lMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long   '                                   ByVal CopyNumberFroNxtLvl As Long) As Long
                                Let GlobinalCntChopsLog = GlobinalCntChopsLog + 1: Debug.Print " Going a HoldYaBackCalledYaBackClapTrapRuc"; GlobinalCntChopsLog; "(1Msg"; lMsg; ", wParam"; wParam; ", lParam"; lParam; ") Function Copy Number_"; GlobinalCntChopsLog
                                'If GlobinalCntChopsLog = 2 Then Let GlobinalCntChopsLog = GlobinalCntChopsLog - 1: UnHookWindowsHookCodEx hHookTrapCrapNumber: Exit Function
        If lMsg = 5 Then '_-.... ( Hook type: HCBT_ACTIVATE = 5 but not here?) ... this runs a further 29 copies of HoldYaBackCalledYaBackClapTrap all coming here, so 30 times in total
                                Debug.Print "Expose Interface"; Tab(30); GlobinalCntChopsLog
         SetWindowPosition wParam, 0, poX, pussY, 400, 150, 40 '             SWP_NOZORDER is 4 ..  but not here?? 'SWP_NOSIZE + SWP_NOZORDER ' Pull the Chainge position ...
         UnHookWindowsHookCodEx hHookTrapCrapNumber         ' Release the Hook 30 times this is done
        Else
                                Debug.Print "No InterOfCourse"; Tab(30); GlobinalCntChopsLog; Tab(50); hHookTrapCrapNumber
        End If ' 5 times here then '_-....
                                Debug.Print "Wipe chain WRap"; Tab(30); GlobinalCntChopsLog; Tab(50); hHookTrapCrapNumber
        Let HoldYaBackCalledYaBackClapTrapRuc = 0 '  Done  5+30=35 times in total  '0 (or False) makes it work, all other numbers and I get no Message box
                                Let GlobinalCntChopsLog = GlobinalCntChopsLog - 1
    End Function ' HoldYaBackCalledYaBackClapTrapRuc


    Code:
    ---------------------------
    MutsNuts AkaApi working ApplicationPromptToRangeInputBox
    ---------------------------
    Select Range
    ---------------------------
    OK   
    ---------------------------
    
    WndNumber 66770    HandleWndOfMyParent 983700    hWndDskTop 66204    hHookTrapCrapNumber
    State of Much Such Penialtration's Number   HookCodeXcretion's
    ================== AliAs Pull of my chain   AliAs my long Hook
                                                                               0 
     Going a HoldYaBackCalledYaBackClapTrapRuc 1 (1Msg 3 , wParam 2623104 , lParam 2353392 ) Function Copy Number_ 1 
    No InterOfCourse              1                   276039693 
    Wipe chain WRap               1                   276039693 
     Going a HoldYaBackCalledYaBackClapTrapRuc 1 (1Msg 3 , wParam 1377832 , lParam 2353500 ) Function Copy Number_ 1 
    No InterOfCourse              1                   276039693 
    Wipe chain WRap               1                   276039693 
     Going a HoldYaBackCalledYaBackClapTrapRuc 1 (1Msg 3 , wParam 3934358 , lParam 2353500 ) Function Copy Number_ 1 
    No InterOfCourse              1                   276039693 
    Wipe chain WRap               1                   276039693 
     Going a HoldYaBackCalledYaBackClapTrapRuc 1 (1Msg 3 , wParam 984706 , lParam 2353480 ) Function Copy Number_ 1 
    No InterOfCourse              1                   276039693 
    Wipe chain WRap               1                   276039693 
     Going a HoldYaBackCalledYaBackClapTrapRuc 1 (1Msg 9 , wParam 3934358 , lParam 66766 ) Function Copy Number_ 1 
    No InterOfCourse              1                   276039693 
    Wipe chain WRap               1                   276039693 
     Going a HoldYaBackCalledYaBackClapTrapRuc 1 (1Msg 5 , wParam 2623104 , lParam 2353812 ) Function Copy Number_ 1 
    Expose Interface              1 
     Going a HoldYaBackCalledYaBackClapTrapRuc 2 (1Msg 5 , wParam 2623104 , lParam 2353500 ) Function Copy Number_ 2 
    Expose Interface              2 
     Going a HoldYaBackCalledYaBackClapTrapRuc 3 (1Msg 5 , wParam 2623104 , lParam 2353188 ) Function Copy Number_ 3 
    Expose Interface              3 
     Going a HoldYaBackCalledYaBackClapTrapRuc 4 (1Msg 5 , wParam 2623104 , lParam 2352876 ) Function Copy Number_ 4 
    Expose Interface              4 
     Going a HoldYaBackCalledYaBackClapTrapRuc 5 (1Msg 5 , wParam 2623104 , lParam 2352564 ) Function Copy Number_ 5 
    Expose Interface              5 
     Going a HoldYaBackCalledYaBackClapTrapRuc 6 (1Msg 5 , wParam 2623104 , lParam 2352252 ) Function Copy Number_ 6 
    Expose Interface              6 
     Going a HoldYaBackCalledYaBackClapTrapRuc 7 (1Msg 5 , wParam 2623104 , lParam 2351940 ) Function Copy Number_ 7 
    Expose Interface              7 
     Going a HoldYaBackCalledYaBackClapTrapRuc 8 (1Msg 5 , wParam 2623104 , lParam 2351628 ) Function Copy Number_ 8 
    Expose Interface              8 
     Going a HoldYaBackCalledYaBackClapTrapRuc 9 (1Msg 5 , wParam 2623104 , lParam 2351316 ) Function Copy Number_ 9 
    Expose Interface              9 
     Going a HoldYaBackCalledYaBackClapTrapRuc 10 (1Msg 5 , wParam 2623104 , lParam 2351004 ) Function Copy Number_ 10 
    Expose Interface              10 
     Going a HoldYaBackCalledYaBackClapTrapRuc 11 (1Msg 5 , wParam 2623104 , lParam 2350692 ) Function Copy Number_ 11 
    Expose Interface              11 
     Going a HoldYaBackCalledYaBackClapTrapRuc 12 (1Msg 5 , wParam 2623104 , lParam 2350380 ) Function Copy Number_ 12 
    Expose Interface              12 
     Going a HoldYaBackCalledYaBackClapTrapRuc 13 (1Msg 5 , wParam 2623104 , lParam 2350068 ) Function Copy Number_ 13 
    Expose Interface              13 
     Going a HoldYaBackCalledYaBackClapTrapRuc 14 (1Msg 5 , wParam 2623104 , lParam 2349756 ) Function Copy Number_ 14 
    Expose Interface              14 
     Going a HoldYaBackCalledYaBackClapTrapRuc 15 (1Msg 5 , wParam 2623104 , lParam 2349444 ) Function Copy Number_ 15 
    Expose Interface              15 
     Going a HoldYaBackCalledYaBackClapTrapRuc 16 (1Msg 5 , wParam 2623104 , lParam 2349132 ) Function Copy Number_ 16 
    Expose Interface              16 
     Going a HoldYaBackCalledYaBackClapTrapRuc 17 (1Msg 5 , wParam 2623104 , lParam 2348820 ) Function Copy Number_ 17 
    Expose Interface              17 
     Going a HoldYaBackCalledYaBackClapTrapRuc 18 (1Msg 5 , wParam 2623104 , lParam 2348508 ) Function Copy Number_ 18 
    Expose Interface              18 
     Going a HoldYaBackCalledYaBackClapTrapRuc 19 (1Msg 5 , wParam 2623104 , lParam 2348196 ) Function Copy Number_ 19 
    Expose Interface              19 
     Going a HoldYaBackCalledYaBackClapTrapRuc 20 (1Msg 5 , wParam 2623104 , lParam 2347884 ) Function Copy Number_ 20 
    Expose Interface              20 
     Going a HoldYaBackCalledYaBackClapTrapRuc 21 (1Msg 5 , wParam 2623104 , lParam 2347572 ) Function Copy Number_ 21 
    Expose Interface              21 
     Going a HoldYaBackCalledYaBackClapTrapRuc 22 (1Msg 5 , wParam 2623104 , lParam 2347260 ) Function Copy Number_ 22 
    Expose Interface              22 
     Going a HoldYaBackCalledYaBackClapTrapRuc 23 (1Msg 5 , wParam 2623104 , lParam 2346948 ) Function Copy Number_ 23 
    Expose Interface              23 
     Going a HoldYaBackCalledYaBackClapTrapRuc 24 (1Msg 5 , wParam 2623104 , lParam 2346636 ) Function Copy Number_ 24 
    Expose Interface              24 
     Going a HoldYaBackCalledYaBackClapTrapRuc 25 (1Msg 5 , wParam 2623104 , lParam 2346324 ) Function Copy Number_ 25 
    Expose Interface              25 
     Going a HoldYaBackCalledYaBackClapTrapRuc 26 (1Msg 5 , wParam 2623104 , lParam 2346012 ) Function Copy Number_ 26 
    Expose Interface              26 
     Going a HoldYaBackCalledYaBackClapTrapRuc 27 (1Msg 5 , wParam 2623104 , lParam 2345700 ) Function Copy Number_ 27 
    Expose Interface              27 
     Going a HoldYaBackCalledYaBackClapTrapRuc 28 (1Msg 5 , wParam 2623104 , lParam 2345388 ) Function Copy Number_ 28 
    Expose Interface              28 
     Going a HoldYaBackCalledYaBackClapTrapRuc 29 (1Msg 5 , wParam 2623104 , lParam 2345076 ) Function Copy Number_ 29 
    Expose Interface              29 
     Going a HoldYaBackCalledYaBackClapTrapRuc 30 (1Msg 5 , wParam 2623104 , lParam 2344764 ) Function Copy Number_ 30 
    Expose Interface              30 
    Wipe chain WRap               30                  276039693 
    Wipe chain WRap               29                  276039693 
    Wipe chain WRap               28                  276039693 
    Wipe chain WRap               27                  276039693 
    Wipe chain WRap               26                  276039693 
    Wipe chain WRap               25                  276039693 
    Wipe chain WRap               24                  276039693 
    Wipe chain WRap               23                  276039693 
    Wipe chain WRap               22                  276039693 
    Wipe chain WRap               21                  276039693 
    Wipe chain WRap               20                  276039693 
    Wipe chain WRap               19                  276039693 
    Wipe chain WRap               18                  276039693 
    Wipe chain WRap               17                  276039693 
    Wipe chain WRap               16                  276039693 
    Wipe chain WRap               15                  276039693 
    Wipe chain WRap               14                  276039693 
    Wipe chain WRap               13                  276039693 
    Wipe chain WRap               12                  276039693 
    Wipe chain WRap               11                  276039693 
    Wipe chain WRap               10                  276039693 
    Wipe chain WRap               9                   276039693 
    Wipe chain WRap               8                   276039693 
    Wipe chain WRap               7                   276039693 
    Wipe chain WRap               6                   276039693 
    Wipe chain WRap               5                   276039693 
    Wipe chain WRap               4                   276039693 
    Wipe chain WRap               3                   276039693 
    Wipe chain WRap               2                   276039693 
    Wipe chain WRap               1                   276039693
    _-.__________________________________

    Windows Handleing Info:
    Code:
    ' 1b)        To hang in the Excel Window malking it effectively a Excel Msgbox... Normally if I did not do this  ... don't do this .. that is to say leave it at 0 , specifically no window is 0 , and it "hanging in mid air so isn't even if it is   imaginatively speaking
    Public Declare Function FindWndNumber Lib "user32" Alias "FindWindowA" (Optional ByVal lpClassName As String, Optional ByVal lpWindowName As String) As Long
    Dim HandleWndOfMyParent As Long      ' I wanted to comment  this  1b)(i) and ( 1b(ii) later )   out to leave it hanging in mid air in a virtual  inadvirtual not thereness  ... but somehow this complicated hook stuff does hang it somwhere but not in my Excel Window                                                                                                            but I don't know what my parent's fart has to do with anything
    ' 1d)        For some Misc experiments
    Private Declare Function FindWindowExtremeNutty Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As Long, ByVal hWnd2 As Long, ByVal lpsz1 As String, ByVal lpsz2 As String) As Long
    Dim WndNumber As Long, hWndDskTop As Long
    Code:
    Sub AkaApiApplicationPromptToRangeInputBox()  ' This one works.. but HTF
            ' 1b(ii)  This section is some how over written in / by the section part or some strange Addressing of HoldYaBackCalledYaBackClapTrap
             Let WndNumber = FindWndNumber(lpClassName:=vbNullString, lpWindowName:=vbNullString)
             Let HandleWndOfMyParent = FindWndNumber(lpClassName:="XLMAIN", lpWindowName:=vbNullString) ' This is a case where vbNullstring is important - that signifies that I am not giving it, which i do not have to. The second option is a bit flaky and does not often work. it certainly won't work if you make it "" as that is a specific string of zero.  Null  is a special idea in computing of not set yet / not defined - that is required if I do not want to give it
            ' 1d) Just some experiments, I forgot why as my brain has goine comfortably numb
             Dim HeavyWindBreak As Long: Let HeavyWindBreak = HandleWndOfMyParent
             Let hWndDskTop = FindWindowExtremeNutty(HandleWndOfMyParent, 0&, "XLDESK", vbNullString)
                                Debug.Print "WndNumber"; WndNumber; "   HandleWndOfMyParent"; HandleWndOfMyParent; "   hWndDskTop"; hWndDskTop; "   hHookTrapCrapNumber"
    Rem 3                                   Mess with me hook? God knows what this all does and it seems to make no difference if the proXYs poX or pussY are before or after SetWindowsHooksExample

  3. #3
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,468
    Rep Power
    10
    Per PM request: One full working example of above code:

    Code:
    Option Explicit
    Rem 1 ' This I understand. it is a simple more basic version of the VBA Message Box Function                                       http://www.eileenslounge.com/viewtopic.php?f=18&t=28885#p223629
    ' 1a)          UnWRap it and..
    Private Declare Function APIssinUserDLL_MsgBox Lib "user32" Alias "MessageBoxA" (Optional ByVal HowManyFartsCanYouHandle As Long, Optional ByVal Prompt As String, Optional ByVal Title As String, Optional ByVal buttons As Long) As Long '
    ' 1b)        To hang in the Excel Window malking it effectively a Excel Msgbox... Normally if I did not do this  ... don't do this .. that is to say leave it at 0 , specifically no window is 0 , and it "hanging in mid air so isn't even if it is   imaginatively speaking
    Public Declare Function FindWndNumber Lib "user32" Alias "FindWindowA" (Optional ByVal lpClassName As String, Optional ByVal lpWindowName As String) As Long
    Dim HandleWndOfMyParent As Long      ' I wanted to comment  this  1b)(i) and ( 1b(ii) later )   out to leave it hanging in mid air in a virtual  inadvirtual not thereness  ... but somehow this complicated hook stuff does hang it somwhere but not in my Excel Window                                                                                                            but I don't know what my parent's fart has to do with anything
    ' 1d)        For some Misc experiments
    Private Declare Function FindWindowExtremeNutty Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As Long, ByVal hWnd2 As Long, ByVal lpsz1 As String, ByVal lpsz2 As String) As Long
    Dim WndNumber As Long, hWndDskTop As Long
    Dim Booloks As Boolean
    '_-_._______________________________________________-
    '_-=================??? main Declarations that I don't really understand
    Rem 2 Position my box --- From here on I do not really have a clue
    ' 2(a)                                        This will tie something on the chain for when you pull it                                                                                                      https://msdn.microsoft.com/en-us/library/windows/desktop/ms644990(v=vs.85).aspx
    Private Declare Function SetWindowsHooksExample Lib "user32" Alias "SetWindowsHookExA" (ByVal Hooktype As Long, ByVal lokprocedureAddress As Long, Optional ByVal hmod As Long, Optional ByVal dwThreadId As Long) As Long
    ' 2(b)                                        Wipe the chain clean
    Private Declare Function UnHookWindowsHookCodEx Lib "user32" Alias "UnhookWindowsHookEx" (ByVal hHookTrapCrapNumber As Long) As Long
    ' 2(c)                                        Don't loose the Thread? - This seems to have no effect , - maybe it would if something else was going on at the time. You don't want to loose the Thread I guess
    'Public Declare Function GetCurrentThreadId Lib "kernel32" () As Long ' Effectively long Null acttuall not ?? -
    Public Declare Function GetCurrentFredId Lib "kernel32" Alias "GetCurrentThreadId" () As Long ' Effectively long Null acttuall not ?? -
    ' 2(d)                                        This looks understandable almost, z(0 for top), posLeft, posTop, x pixels, y pixels,
    Private Declare Function SetWindowPosition Lib "user32" Alias "SetWindowPos" (ByVal hWnd As Long, ByVal zNumber As Long, ByVal CoedX As Long, ByVal CoedY As Long, ByVal xPiXel As Long, ByVal yPiYel As Long, ByVal wFlags As Long) As Long
    ' 2e)
    Private hHookTrapCrapNumber As Long                         ' Handle to the Hook procedure
    ' 2f)
    Private poX As Long: Private pussY As Long    ' Positional By proXYs
                                Dim GlobinalCntChopsLog As Long   ' Only used in this test code to keep track of the copies of a Function(HoldYaBackCalledYaBackClapTrap) used in a recursion process
    ' 2g) bits to do with 1 that i am resonably happy with
    Sub AkaApiApplicationPromptToRangeInputBox()  ' This one works.. but HTF
            ' 1b(ii)  This section is some how over written in / by the section part or some strange Addressing of HoldYaBackCalledYaBackClapTrap
             Let WndNumber = FindWndNumber(lpClassName:=vbNullString, lpWindowName:=vbNullString)
             Let HandleWndOfMyParent = FindWndNumber(lpClassName:="XLMAIN", lpWindowName:=vbNullString) ' This is a case where vbNullstring is important - that signifies that I am not giving it, which i do not have to. The second option is a bit flaky and does not often work. it certainly won't work if you make it "" as that is a specific string of zero.  Null  is a special idea in computing of not set yet / not defined - that is required if I do not want to give it
            ' 1d) Just some experiments, I forgot why as my brain has goine comfortably numb
             Dim HeavyWindBreak As Long: Let HeavyWindBreak = HandleWndOfMyParent
             Let hWndDskTop = FindWindowExtremeNutty(HandleWndOfMyParent, 0&, "XLDESK", vbNullString)
                                Debug.Print "WndNumber"; WndNumber; "   HandleWndOfMyParent"; HandleWndOfMyParent; "   hWndDskTop"; hWndDskTop; "   hHookTrapCrapNumber"
    Rem 3                                   Mess with me hook? God knows what this all does and it seems to make no difference if the proXYs poX or pussY are before or after SetWindowsHooksExample
                                Debug.Print "State of Much Such"; Tab(20); "Penialtration's Number"; Tab(45); "HookCodeXcretion's"
                                Debug.Print "=================="; Tab(20); "AliAs Pull of my chain"; Tab(45); "AliAs my long Hook"
                                Let GlobinalCntChopsLog = 0:
    '_-======================== Weird thing with an AddressOf ???
    Let poX = 10: pussY = 50 ' These can go before or after the next line, makes no diffference.. -                                                    I bet no Pro noticed that...
    'Let hHookTrapCrapNumber = SetWindowsHooksExample(5, AddressOf HoldYaBackCalledYaBackClapTrap, 0, GetCurrentThreadId)   ' (5-pull before flush,  somehow arranges that the function gets called  ,
                                Debug.Print ; Tab(75); hHookTrapCrapNumber '                                                                                           'APIssinUserDLL_MsgBox HeavyWindBreak, "Excel MsgBox", "This is Center Position", vbOKOnly ' This breaks Wnd in Excel Window
     Call HookAPIssinUserDLL_MsgBoxThenDropIt
     'APIssinUserDLL_MsgBox &H0, "Select Range", "MutsNuts AkaApi working ApplicationPromptToRangeInputBox", vbOKOnly ' Pseudo Non Modal
     'APIssinUserDLL_MsgBox &H0, "Select Range", "MutsNuts AkaApi working ApplicationPromptToRangeInputBox", vbOKOnly ' Pseudo Non Modal
     'HookAPIssinUserDLL_MsgBoxThenDropIt
                                                                                                              
                                                                                                              Dim Rng As Range: Set Rng = Selection
    ' (Optional ByVal hwnd As Long, Optional ByVal Prompt As String, Optional ByVal Title As String, Optional ByVal buttons As Long) As Long '
    End Sub ' AkaApiApplicationPromptToRangeInputBox
    Sub HookAPIssinUserDLL_MsgBoxThenDropIt()
    Code:
    Sub HookAPIssinUserDLL_MsgBoxThenDropIt()
    ' a) HOOK Hook the pseudo Windows Sub Class Function WinSubWinCls_JerkBackOffHooKerd
    Dim BookMarkClassTeachMeWind As Long: Let BookMarkClassTeachMeWind = 5
     'Let hHookTrapCrapNumber = SetWindowsHooksExample(BookMarkClassTeachMeWind, AddressOf HoldYaBackCalledYaBackClapTraped, 0, GetCurrentThreadId)   ' (5-pull before flush,  somehow arranges that the function gets called  ,
     'Let hHookTrapCrapNumber = SetWindowsHooksExample(BookMarkClassTeachMeWind, AddressOf HoldYaBackCalledYaBackClapTrapRuc, 0, GetCurrentThreadId)   ' (5-pull before flush,  somehow arranges that the function gets called  ,
     Let hHookTrapCrapNumber = SetWindowsHooksExample(BookMarkClassTeachMeWind, AddressOf HoldYaBackCalledYaBackClapTrapRuc, 0, GetCurrentFredId)   ' (5-pull before flush,  somehow arranges that the function gets called  ,
    ' b) Call the MessageBoxA
     APIssinUserDLL_MsgBox &H0, "Select Range", "MutsNuts AkaApi working ApplicationPromptToRangeInputBox", vbOKOnly ' Pseudo Non Modal
    End Sub
    '_-=Rem 4===================??? Got me hook lochprocedue in my code ,                5 times simple run then  another + 29 new copies of it are run  = 6+29=35 times  in total                     calling it it a few times  http://www.excelfox.com/forum/showthread.php/1324-Loop-Through-Files-In-A-Folder-Using-VBA#post10421   .... wanking myself up and down a few times
    Code:
    '_-=Rem 4===================??? Got me hook lochprocedue in my code ,                5 times simple run then  another + 29 new copies of it are run  = 5+30=35 times  in total                     calling it it a few times  http://www.excelfox.com/forum/showthread.php/1324-Loop-Through-Files-In-A-Folder-Using-VBA#post10421   .... wanking myself up and down a few times
    Private Function HoldYaBackCalledYaBackClapTrapRuc(ByVal lMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long   '                                   ByVal CopyNumberFroNxtLvl As Long) As Long
                                Let GlobinalCntChopsLog = GlobinalCntChopsLog + 1: Debug.Print " Going a HoldYaBackCalledYaBackClapTrapRuc"; GlobinalCntChopsLog; "(1Msg"; lMsg; ", wParam"; wParam; ", lParam"; lParam; ") Function Copy Number_"; GlobinalCntChopsLog
                                'If GlobinalCntChopsLog = 2 Then Let GlobinalCntChopsLog = GlobinalCntChopsLog - 1: UnHookWindowsHookCodEx hHookTrapCrapNumber: Exit Function
        If lMsg = 5 Then '_-.... ( Hook type: HCBT_ACTIVATE = 5 but not here?) ... this runs a further 29 copies of HoldYaBackCalledYaBackClapTrap all coming here, so 30 times in total
                                Debug.Print "Expose Interface"; Tab(30); GlobinalCntChopsLog
         Call SetWindowPosition(wParam, 0, poX, pussY, 400, 150, 40) '             SWP_NOZORDER is 4 ..  but not here?? 'SWP_NOSIZE + SWP_NOZORDER ' Pull the Chainge position ...
         UnHookWindowsHookCodEx hHookTrapCrapNumber         ' Release the Hook 30 times this is done
        Else
                                Debug.Print "No InterOfCourse"; Tab(30); GlobinalCntChopsLog; Tab(50); hHookTrapCrapNumber
        End If ' 5 times here then '_-....
                                Debug.Print "Wipe chain WRap"; Tab(30); GlobinalCntChopsLog; Tab(50); hHookTrapCrapNumber
        Let HoldYaBackCalledYaBackClapTrapRuc = 0 '  Done  5+30=35 times in total  '0 (or False) makes it work, all other numbers and I get no Message box
                                Let GlobinalCntChopsLog = GlobinalCntChopsLog - 1
    End Function ' HoldYaBackCalledYaBackClapTrapRuc

  4. #4
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,468
    Rep Power
    10

    test

    lcnascn
    Last edited by DocAElstein; 12-02-2024 at 01:54 AM.

  5. #5
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,468
    Rep Power
    10

    Handles, hwnd stuff examples

    "FindWindowA"
    When discussing handles, the API function "FindWindowA" is perhaps one of the most common, and since obtaining a handle is a very common action in API coding, then it is perhaps one of the most common API functions.
    Let us remind ourselves what this handle, hwnd is about, in particular with API VBA coding: Knowing this unique identifying number, we can interact in many ways with a window via API functions: we can do many things to, or get properties from, a window, but we will usually need to give the API function the identifying number so it knows which window.
    We could get this number via Third party software and use that in any coding to get directly at any window, but that is of limited use since a different handle number will be given for any window every time it is open.
    If we want to use a coding to consistently interact with a window, the coding will need to get the handle, or handles that we need, (and an important side issue to remember is that we generally can only get a handle with an immediate relation to another handle, so if we want a handle some way down the hierarchy, then we will have to do it in a multi-line stepping process, sometimes referred to as "walking the tree" )
    All three of the code lines below will get the handle of a window in the current level , typically in such an example, the current level is the desktop. – So I am not "walking the tree" here, - I am simply showing three argument choice alternatives for the same single code line. For this to work you will need to have open Notepad with a file named Neues Textdokument.txt . It doesn’t matter where that file is stored but it does need to be open, showing on the desktop , and note importantly, if using the argument lpWindowName, then you must use the window name you see, and that may be a bit different to the file name. In this example it is Neues Textdokument.txt - Editor
    If you do not have the text file open, then the code lines will not error, but you will just get 0 for the handle number.
    With that ext file open, If the coding works as it should, you will see in the Immediate window, similar numbers to those I have indicated in the 'comments, but they are unlikely to be exactly the same
    Code:
    Option Explicit
    Private Declare Function FindWndNumber Lib "user32" Alias "FindWindowA" (Optional ByVal lpClassName As String, Optional ByVal lpWindowName As String) As Long
    Sub TextAPI()  '
    Dim HdlTextFile As Long, MsgRef As Long
     Let HdlTextFile = FindWndNumber(lpClassName:="Notepad", lpWindowName:=vbNullString): Debug.Print HdlTextFile & " " & Hex(HdlTextFile)  '  224003622 D5A0626
     Let HdlTextFile = FindWndNumber(lpClassName:="Notepad", lpWindowName:="Neues Textdokument.txt - Editor"): Debug.Print HdlTextFile & " " & Hex(HdlTextFile) '  224003622 D5A0626
     Let HdlTextFile = FindWndNumber(lpClassName:=vbNullString, lpWindowName:="Neues Textdokument.txt - Editor"): Debug.Print HdlTextFile & " " & Hex(HdlTextFile) '  224003622 D5A0626
    End Sub
    In that coding the lpWindowName is what typically is seen as the window title, lpClassName is technically a Class of sorts , it can sometimes be easily related to the thing running, in this case Notepad, but the name is not always so obvious, for example Excel is XLMAIN and Word is really weird, OpusApp
    https://www.eileenslounge.com/viewto...322424#p322424



    There are two ( three ** ) main things to be learnt from the next coding below, one is new, the other is something important already touched on a few times, the "walking the tree" idea.
    (** An extra thing to clarify another point made few times, has come I by chance: In between the next coding and the last coding, the Laptop was restarted. I opened windows/ software similarly to how they had previously been. Never the less, none of the handles obtained in the last coding are any use to us: Even though the first main code line actually is identical to one in the previous coding, the handle obtained is different : A different handle number is given for any window every time it is open.)


    FindWindowEx
    Hopefully this new coding will get one ( two** ) important point finally clear at this early stage: Although we can directly reference any window anywhere if we know its handle, we will usually need to determine it in the same coding that uses it, and functions are only available to find the handle in close relation to another, so we must ("walk the tree”).
    FindWindowEx is one of the commonest functions to do that. As often with such a function , the first argument required is the handle of the nearby window to that which we want.
    ( A phenomena ( Null , Empty , Long zero 0& , vbNullString etc ) , will also briefly be mentioned that we see for the first time in one of its guises here )
    As example, we consider the same open text file that we considered. Here is a view ( using portable winspy ), opening up all + to revel the full "tree"
    https://imgur.com/6Cq1Dj7
    The first thing we see, seems to be something like the main window we might be familiar with. So that might be a useful one to have the handle of, https://i.postimg.cc/LX5Q1c5W/Notepad-Edit-window.jpg
    In the coding below, the first main line is the code line of the last coding, and note the handle I obtained is shown in the ' comments, is different to that previously obtained.
    https://i.postimg.cc/CL3LBDpc/Sub-Text-API.jpg Sub TextAPI().jpg
    Code:
    Option Explicit
    Private Declare Function FindWndNumber Lib "user32" Alias "FindWindowA" (Optional ByVal lpClassName As String, Optional ByVal lpWindowName As String) As Long
    Private Declare Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As Long, ByVal hWnd2 As Long, ByVal lpsz1 As String, ByVal lpsz2 As String) As Long
    Sub TextAPI()  '
    Dim HdlTextFile As Long, MsgRef As Long
     Let HdlTextFile = FindWndNumber(lpClassName:="Notepad", lpWindowName:="Neues Textdokument.txt - Editor"): Debug.Print HdlTextFile & " " & Hex(HdlTextFile) '  984776 F06C8
    Dim HdlEdit As Long
     Let HdlEdit = FindWindowEx(hWnd1:=HdlTextFile, hWnd2:=0, lpsz1:="Edit", lpsz2:=""): Debug.Print HdlEdit & " " & Hex(HdlEdit)  '  6030920 5C0648
     Let HdlEdit = FindWindowEx(hWnd1:=0, hWnd2:=0, lpsz1:="Notepad", lpsz2:="Neues Textdokument.txt - Editor"): Debug.Print "0, 0,      " & HdlEdit & " " & Hex(HdlEdit) '  0, 0,      984776 F06C8
    End Sub
    This will be required for the first argument of FindWindowEx, since I am "walking the tree", in this case one step
    I will only talk around some of the important argument issues I will only talk around some of the important argument issues
    Its best to get a good look at the Function and argument descriptions, for example here currently,
    http://allapi.mentalis.org/apilist/FindWindowEx.shtml
    , and remember that the original allapi.net site is very well archived at Archive org wayback machine, so most things can be found by trying something corresponding like this http://allapi.net/apilist/FindWindowEx.shtml
    In the Wayback machine you would search for that http://allapi.net/apilist/FindWindowEx.shtml, like this https://imgur.com/35EeKLP https://i.postimg.cc/0N8B8MsP/Archiv...-Window-Ex.jpg

    In fact, Archive org wayback machine seems to have the whole site very well archived so you can start at an archived main page, then use the links which seem to work to take you further. I will only talk around some of the important argument issues
    The second main line, HdlEdit = FindWindowEx(hWnd1:=HdlTextFile, hWnd2:=0, lpsz1:="Edit", lpsz2:="") is demonstrating the common use of FindWindowEx

    Phenomenon Null , Empty , Long zero 0& , vbNullString etc.
    The third line is intended to give an indication of a phenomena that later will be noticed more significantly later: A Null . Empty , Long zero 0& , normal simple zero in some cases, can often have a specific meaning, and cannot always be treated so carelessly. This is yet another example of the more "dangerous" aspect of API which things like normal VBA and VB were designed to help protect us from.
    This first example seems relatively harmless: I note that a simple 0 is satisfactory, whereas in other cases a 0& would be required


    As noted I will not always give detailed explanation of all arguments, as having the list with explanations to hand is perhaps more useful/more efficient. The second hwnd argument is clearly an order in similar level things , type qualifier, and so its reasonable that a form of nothing given , 0, will likely still give us something useful, in this case perhaps the first or most important. It is difficult to be sure about these things. (For one reason people claiming to know seem a bit reluctant to give simple clear but detailed explanations.) The main argument, the first, being left at a form of nothing, 0, could be thought perhaps of dong a step of not step, in other words staying where you are. So it perhaps makes sense that we then get the handle returned of the main text file window, the same value as in the first main code line. Possibly what ever process moves a bit to find something and then give the answer, was called into play, but then not moved, so found the thing again that it last did, the thing in the current position.


    Attached Files Attached Files
    Last edited by DocAElstein; 12-02-2024 at 03:16 PM.

  6. #6
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,468
    Rep Power
    10
    Coding and some extra notes to go with the last post and these main forum Threads
    https://eileenslounge.com/viewtopic.php?f=30&t=41659

    Don’t run this – it crashes Cures below
    Code:
    Option Explicit
    Private Declare Function FindWndNumber Lib "user32" Alias "FindWindowA" (Optional ByVal lpClassName As String, Optional ByVal lpWindowName As String) As Long
    Private Declare Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As Long, ByVal hWnd2 As Long, ByVal lpsz1 As String, ByVal lpsz2 As String) As Long ' To "walk a step down in the tree" from the code line above
    Private Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) As Long
    Const WM_GETTEXTLENGTH As Long = &HE  '  14   Hex(14) is E
    Const WM_GETTEXT As Long = &HD        '  13   Hex(13) is E
    Sub TextAPI()  '
    1 Dim HdlTextFile As Long: Let HdlTextFile = FindWndNumber(lpClassName:="Notepad", lpWindowName:="TextFile.txt - Editor"): Debug.Print HdlTextFile & " " & Hex(HdlTextFile) '  984776 F06C8
    2 Dim HdlEdit As Long: Let HdlEdit = FindWindowEx(hWnd1:=HdlTextFile, hWnd2:=0, lpsz1:="Edit", lpsz2:=""): Debug.Print HdlEdit & " " & Hex(HdlEdit)                        '  6030920 5C0648    '    ' To "walk a step down in the tree" from the code line above
    3 Dim Lenf As Long: Let Lenf = SendMessage(HdlEdit, WM_GETTEXTLENGTH, 0&, 0&): Debug.Print Lenf
    4 Dim Biffa As String: Let Biffa$ = Space$(Lenf): Debug.Print Biffa$
    5 Dim FuncReturn As Long: Let FuncReturn = SendMessage(HdlEdit, WM_GETTEXT, 5, Biffa$): Debug.Print FuncReturn
    6 Debug.Print Biffa & "  Length Biffa is " & Len(Biffa$)
    End Sub
    Cure 1
    Here is cure 1(i) and 1(ii): add ByVal in the SendMessagA Declare line, but then also: _1(ii) Somehow related is something, a similar phenomena that I have seen before: I must now change in line 3, the last 0 to 0&
    Code:
     Option Explicit
    Private Declare Function FindWndNumber Lib "user32" Alias "FindWindowA" (Optional ByVal lpClassName As String, Optional ByVal lpWindowName As String) As Long
    Private Declare Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As Long, ByVal hWnd2 As Long, ByVal lpsz1 As String, ByVal lpsz2 As String) As Long ' To "walk a step down in the tree" from the code line above
    Private Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Any) As Long
    Const WM_GETTEXTLENGTH As Long = &HE  '  14   Hex(14) is E
    Const WM_GETTEXT As Long = &HD        '  13   Hex(13) is E
    Sub TextAPI()  '
    1 Dim HdlTextFile As Long: Let HdlTextFile = FindWndNumber(lpClassName:="Notepad", lpWindowName:="TextFile.txt - Editor"): Debug.Print HdlTextFile & " " & Hex(HdlTextFile) '  984776 F06C8
    2 Dim HdlEdit As Long: Let HdlEdit = FindWindowEx(hWnd1:=HdlTextFile, hWnd2:=0, lpsz1:="Edit", lpsz2:=""): Debug.Print HdlEdit & " " & Hex(HdlEdit)                        '  6030920 5C0648    '    ' To "walk a step down in the tree" from the code line above
    3 Dim Lenf As Long: Let Lenf = SendMessage(HdlEdit, WM_GETTEXTLENGTH, 0, 0&): Debug.Print Lenf
    4 Dim Biffa As String: Let Biffa$ = Space$(Lenf): Debug.Print Biffa$
    5 Dim FuncReturn As Long: Let FuncReturn = SendMessage(HdlEdit, WM_GETTEXT, 5, Biffa$): Debug.Print FuncReturn
    6 Debug.Print Biffa & "  (Length Biffa is " & Len(Biffa$) & ")"
    End Sub
    Cure 2
    _2 I can forget _1(i) and _1(ii), making just one change, by adding a ByVal at line 5
    Code:
    Option Explicit
    Private Declare Function FindWndNumber Lib "user32" Alias "FindWindowA" (Optional ByVal lpClassName As String, Optional ByVal lpWindowName As String) As Long
    Private Declare Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As Long, ByVal hWnd2 As Long, ByVal lpsz1 As String, ByVal lpsz2 As String) As Long ' To "walk a step down in the tree" from the code line above
    Private Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) As Long
    Const WM_GETTEXTLENGTH As Long = &HE  '  14   Hex(14) is E
    Const WM_GETTEXT As Long = &HD        '  13   Hex(13) is E
    Sub TextAPI()  '
    1 Dim HdlTextFile As Long: Let HdlTextFile = FindWndNumber(lpClassName:="Notepad", lpWindowName:="TextFile.txt - Editor"): Debug.Print HdlTextFile & " " & Hex(HdlTextFile) '  984776 F06C8
    2 Dim HdlEdit As Long: Let HdlEdit = FindWindowEx(hWnd1:=HdlTextFile, hWnd2:=0, lpsz1:="Edit", lpsz2:=""): Debug.Print HdlEdit & " " & Hex(HdlEdit)                        '  6030920 5C0648    '    ' To "walk a step down in the tree" from the code line above
    3 Dim Lenf As Long: Let Lenf = SendMessage(HdlEdit, WM_GETTEXTLENGTH, 0, 0): Debug.Print Lenf
    4 Dim Biffa As String: Let Biffa$ = Space$(Lenf): Debug.Print Biffa$
    5 Dim FuncReturn As Long: Let FuncReturn = SendMessage(HdlEdit, WM_GETTEXT, 5, ByVal Biffa$): Debug.Print FuncReturn
    6 Debug.Print Biffa & "  (Length Biffa is " & Len(Biffa$) & ")"
    End Sub

    Attached Files Attached Files
    Last edited by DocAElstein; 12-03-2024 at 02:18 AM.

  7. #7
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,468
    Rep Power
    10
    This is post #7
    https://www.excelfox.com/forum/showt...ll=1#post24876
    https://www.excelfox.com/forum/showthread.php/2824-Tests-Copying-pasting-Cliipboard-issues?p=24876&viewfull=1#pst24876




    This is post #552
    https://www.excelfox.com/forum/showt...ge56#post24323
    https://www.excelfox.com/forum/showthread.php/2824-Tests-Copying-pasting-Cliipboard-issues/page56#post24323
    https://www.excelfox.com/forum/showt...ll=1#post24323
    https://www.excelfox.com/forum/showthread.php/2824-Tests-Copying-pasting-Cliipboard-issues?p=24317&viewfull=1#post24323





    Edit: I gave up with this post after getting so many quirky results in Windows 10 and windows 11, so I started this Thread


    Some functions and rough notes on Versions on some computers used in the testings from this page 56 and page 55 and a few other related forum postings

    Its useful to keep track of some of your computer specs, and Office versions when playing around with the codings on this page.
    The macro below, Sub WhatAmI() ( along with the functions under it which go with it) may help to get some of that info. Run it and some info should appear in the Immediate Window. (From the VB Editor, hold the Ctrl key down and then hit key g to get that Immediate Window up)
    Note there are a few bugs and quirks :
    _ Application.OperatingSystem can give quirky answers in windows 11 , so the operating system result may be wrong for if you have Windows 11. In fact currently it seems a bit wonky everywhere
    _I don’t know if that macro gets it correct in Office versions 2016, 2019,2021, 2024 or 365, since I don’t have them versions to check. My guess is that it might be a bit iffy for 2016 2019,2024 or 365

    Code:
    Sub WhatAmI()   '     https://www.excelfox.com/forum/showthread.php/2824-Tests-Copying-pasting-Cliipboard-issues?p=24323&viewfull=1#post24323     https://www.excelfox.com/forum/showthread.php/2824-Tests-Copying-pasting-Cliipboard-issues/page56#post24323
    Debug.Print ExcelVersion & "    " & Application.OperatingSystem & "     (ApplicationVersion " & CLng(Val(Application.Version)) & ")     Computer named " & CreateObject("WScript.Network").ComputerName                      '  Environ$("computername")      Nigel Heffernan  https://stackoverflow.com/questions/3551055/how-to-get-name-of-the-computer-in-vba/10108951#10108951
    '    Windows 11 (2021)                  ...
    '    Windows 10 S (2017) ...
    '    Windows 10 (2015) - MS Version 6.4. ...
    '    Windows 8/8.1 (2012-2013) - MS Version 6.2/6.3. ...
    '    Windows 7 (2009) - MS Version 6.1. ...
    '    Windows Vista (2006) - MS Version 6.0. ...
    '    Windows XP (2001) - MS Version 5.1. ...
    '    Windows 2000 (2000) - MS Version 5.0.
    End Sub
    
    Private Function ExcelVersion() As String ' From Rory somewhere, then a blind mod for above 2016 from https://excelguru.ca/check-the-application-version-in-modern-office/  , which probably does not work too well - https://excelguru.ca/check-the-application-version-in-modern-office/#comment-358558
    Dim Temp    As String
        'On Error Resume Next
        #If Mac Then
            Select Case CLng(Val(Application.Version))
             Case 11: Temp = "Excel 2004"
             Case 12: Temp = "Excel 2008" ' this should NEVER happen!
             Case 14: Temp = "Excel 2011"
             Case 15: Temp = "Excel 2016 (Mac)"
             Case Else: Temp = "Unknown"
            End Select
        #Else
            Select Case CLng(Val(Application.Version))
             Case 9: Temp = "Excel 2000"
             Case 10: Temp = "Excel 2002"
             Case 11: Temp = "Excel 2003"
             Case 12: Temp = "Excel 2007"
             Case 14: Temp = "Excel 2010"
             Case 15: Temp = "Excel 2013"
             Case 16:  '    https://excelguru.ca/check-the-application-version-in-modern-office/
              Let Temp = ForVersion16()         '
             Case Else: Temp = "Unknown"
            End Select
        #End If
        #If Win64 Then
         Let Temp = Temp & " 64 bit"
        #Else
         Let Temp = Temp & " 32 bit"
        #End If
    
     Let ExcelVersion = Temp
    End Function
    Function ForVersion16() As String  '    https://excelguru.ca/check-the-application-version-in-modern-office/  This may be crap - https://excelguru.ca/check-the-application-version-in-modern-office/#comment-358558
    'Test the Office application version,   'Written by Ken Puls (www.excelguru.ca)   '  ...."From Office 2016 onwards, Microsoft has not revved the Application.Version number - they all show as 16.0 - giving you no way to differentiate between versions."....
    Dim registryObject As Object
    Dim rootDirectory As String, keyPath As String
    Dim arrEntryNames As Variant, arrValueTypes As Variant
    Dim x As Long
    'Check for existence of Licensing key
     Let keyPath = "Software\Microsoft\Office\" & CStr(Application.Version) & "\Common\Licensing\LicensingNext"
     Let rootDirectory = "."
     Set registryObject = GetObject("winmgmts:{impersonationLevel=impersonate}!\\" & rootDirectory & "\root\default:StdRegProv")
    registryObject.EnumValues &H80000001, keyPath, arrEntryNames, arrValueTypes
    On Error GoTo ErrorExit
        For x = 0 To UBound(arrEntryNames)
            If InStr(arrEntryNames(x), "365") > 0 Then
             Let ForVersion16 = 365
            Exit Function
            End If
            If InStr(arrEntryNames(x), "2019") > 0 Then
             Let ForVersion16 = 2019
            Exit Function
            End If
            If InStr(arrEntryNames(x), "2021") > 0 Then
             Let ForVersion16 = 2021
            Exit Function
            If InStr(arrEntryNames(x), "2024") > 0 Then
             Let ForVersion16 = 2024
            Exit Function
            End If
        Next x
    Exit Function
    ErrorExit:
    'Version 16, but no licensing key. Must be Office 2016
     Let ForVersion16 = 2016
    End Function
    







    'Some typical results of my computers for future reference for me because I keep forgetting which versions I have where
    Code:
     '  ExcelVersion      Application.OperatingSystem        (CLng(Val(Application.Version)   CreateObject("WScript.Network").ComputerName                    '  Environ$("computername")      Nigel Heffernan  https://stackoverflow.com/questions/3551055/how-to-get-name-of-the-computer-in-vba/10108951#10108951
    '(based on App.version)
    '  Excel 2007 32 bit      Windows (32-bit) NT 6.00              (ApplicationVersion 12)     Alan's Computer named ELSTON-LAPTOP   KB Vista     Office 2007
    '  Excel 2010 32 bit      Windows (32-bit) NT 6.00              (ApplicationVersion 14)     Computer named ELSTON-PC              Alan's Computer GB Vista     Office 10
    
    
    '  Excel 2003 32 bit      Windows (32-bit) NT 6.01              (ApplicationVersion 11)     Computer named ALAN-PC                 Martin Windows 7 Pro   Office 2003
    '  Excel 2010 32 bit      Windows (32-bit) NT 6.01              (ApplicationVersion 14)     Computer named ALAN-PC                Martin Windows 7 pro   Office 2010
    
    
    '  Excel 2010 32 bit      Windows (32-bit) NT 6.02              (ApplicationVersion 14)     Computer named TM5730G                Alan's Computer Verranda Windows 10 Office 10
    '  Excel 2013 32 bit      Windows (32-bit) NT :.00              (ApplicationVersion 15)     Computer named DESKTOP-G7BIH1B        Alan's Computer SerSzuD2 Windows 10 Office 13
    '  Excel 2016 (Windows) 32 bit    Windows (32-bit) NT 10.00     (ApplicationVersion 16)     Alan's Computer named DESKTOP-14C4HCR   Torrox Windows 10  Office 2016
    
    
    
    '  Excel 2010 32 bit      Windows (32-bit) NT 6.02              (ApplicationVersion 14)     Computer named ASPIRE7730G     Elfy Windows 11    Office 10
    '

  8. #8
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,468
    Rep Power
    10

    Rough Notes on VBA Windows API Introduction Part 2 Handles, hwnd number

    Rough Notes on VBA Windows API Introduction Part 2 Handles, hwnd number
    Arguably one of the most important things in VBA Windows API to get familiar with is this number, the number that gets given to a window when it opens**, or probably better said, most windows associated with a software get given their own one of these unique identifying numbers, - note: - they get a new one every time the software starts
    The subject we are considering here is controlling windows, and in order to do this, the API functions we are using will almost certainly need this number, and sometimes a few of them. Typically, the Long type variable used is given the name hwnd - It is very common to see this variable name, but only because it is often used, - it is not some reserved word, or it might be somewhere other than VBA. (So in writings, even mine, it may be referring specifically to a variable, or just a handle(s) in general ,so it might get carelessly written like hwnd or hwnd, although generally I try to keep the hwnd format for coding

    Perhaps 3 important points should be made clear right from the start
    1_ Whilst this number can, for any window, be used in our coding, ( or anything else communicating with windows ), to refer to / get / communicate etc. with that window directly, the particular number used is not fixed forever for that window. **It is given when the window comes into existence, and if the software creating it is then closed and re-opened, a new number will be given. It can be thought of as a semi random number given when the window is created, ( semi because the process giving the number follows certain rules ), and that particular number will only be valid for the duration of the software running. So generally, we cannot get that number somehow and then have a fixed number in our coding to always use. Instead we must either
    __ use a third party software to get the number, and then each time we run our VBA coding we must enter that in
    , or
    __ the coding itself will need to get/find that number by some means, ( for example using a API function that uses some other property of the window to return the hwnd, or using some combination of API functions to loop through some windows and use some criteria to select the one we want)

    2_ Similarly again, whilst this number can, for any window, be used in our coding, ( or anything else communicating with windows ), to refer to / get / communicate etc. with that window directly, point 2_ is that windows are generally organised in a explorer/ hierarchical way, and for some low level windows software innards reasons, if we want to get the handle with our VBA coding, we may need to "walk the tree" or go in steps to get it. This means that we often see a hwnd argument in a API function that we might use to get the handle, and the handle in that variable will likely be that of a window somewhere "near" the one which is being found by that API function. So if we were wanting the handle of a window that is a few "levels down" in the hierarchy, we would likely have a few API function lines, and the handle got from one line would be fed to the next, pseudo like
    hwnd2 = Function(hwnd1, arga, argb)
    hwnd3 = Function(hwnd2, argx, argy)
    hwnd4 = Function(hwnd3, argz, argy)

    ( Since a VBA coding works from right to left, and because we are usually only interested in the final hwnd, you will often see such code lines simplified to use the same variable, hwnd, pseudo like
    hwnd = Function(hwnd, arga, argb)
    hwnd = Function(hwnd, argx, argy)
    hwnd = Function(hwnd, argz, argy)
    )

    It is important not to get those last two points mixed up: We don’t have to delve into the hierarchy to reference a window if we have the hwnd; but we may need to do so if we want to get that hwnd with our coding. This latter point is often missed when learning or initially using simple API codings, since we may be just working at the same "level" on our desktop, ( although this "level" word needs to be used lightly/ carefully , - we may conceive it to be things we "see", whereas we may have "invisible" windows and also there may be other "level -type" organisations of the windows not strictly part of the hierarchical windows structure, for example the "z – order" which is the order in which windows are "seen on top of eachother" ). In some blogs and documentation we would sometimes say we usually begin at the top-level window if writing coding, although smart people with good deep down knowledge of computers might not like the sound of that.
    I think in most all day use we can generally regard, at least in Layman terms, that the desktop is "where we mostly are" and that this desktop is the top level, so the hierarchical nature and this strange need to "walk the tree" is often over looked. Its perhaps worth noting that one of the few simple APi functions taking no arguments, that the average user may come across is the GetDesktopWindow which returns the handle of the desktop. Most other handle getting API functions require arguments that often need some thinking about


    3_ I forgot the third point, I will add it later


    The hierarchical structure, Spy software and other third party software/ lists/ explanations
    Before getting into some demonstrative coding, we can look at some useful third party tools

    _ API function lists and explanations:
    https://eileenslounge.com/viewtopic....322050#p322050
    ApiViewer 2004 https://app.box.com/s/qbz657wp505n4vdgp3rg67dltksma5wx
    https://eileenslounge.com/viewtopic....322151#p322151
    http://allapi.mentalis.org/apilist/apilist.php http://allapi.mentalis.org/apilist/apilist.php
    API-Gude 3.7
    https://app.box.com/s/3orl65g0rzwktbi39ser8qdu46rshp0y
    https://app.box.com/s/bufdyf643jujd86iuloztwhscvicwb34
    https://app.box.com/s/ckt6a0p57245j879wvuit7s4vi9n0oxt
    https://app.box.com/s/jr5aoc3nsdzziqb2spgmtxnyinuxseui


    _Spys
    These crawl the operating system: It gives a view of your systems processes, Threads, Windows and other messages
    The main thing the commonly called spy programs are used for is a graphical view of the window things and window like things, - remember the term is not restricted to the obvious rectangular things we experience:
    There are a few. You have a graphical view of your systems processes, Threads, Windows and other messages
    ( https://youtu.be/C43btudYyzA?list=PL...fDnMdnOs&t=178 )
    The standard one is Microsoft Spy++. I have not figured out yet how to get it working without Visual Studio bloat. (I will try later). It does give nice view of the Hierarchical structure.
    At the other extreme there is a small portable, winspy, ( https://app.box.com/s/kmkjg0djef8je9lpcrp2ufm80sjv5l4y ) , with a slightly different view.
    https://i.postimg.cc/nhPrHqYr/winspy...rosoft-Spy.jpg winspy and Microsoft Spy++.JPG
    https://i.postimg.cc/k5R4DDfc/winspy...rosoft-Spy.jpg


    I am not sure yet of advantages / disadvantages, of either, but I have a feeling that Microsoft Spy++ and some of the installable larger alternatives my sometimes cause some problems / crashes.

    It can be useful to use the Spys ++ initially early on so as to see the hierarchical structure, as a self made coding for that might come at a later intermediate level or advanced level. However for an intermediate / beginner level, we can look at the top-level window, as long as we bear in mind the points made about the hierarchical structure and the likely need to "walk the tree", we can get some useful beginner information and understanding if we write a coding for that. The danger can be doing this simple codings before the points about the hierarchical structure and the likely need to "walk the tree", as I did originally, but 6 years later, 2024, I am making better progress, amongst other reasons due to some better more enlightened help. ( https://eileenslounge.com/viewtopic....322075#p322075 )

    A "Top level" window handle getting program
    This one has had a few discussions and versions
    https://eileenslounge.com/viewtopic.php?f=30&t=41610
    https://www.excelfox.com/forum/showt...ll=1#post24921
    https://www.excelfox.com/forum/showt...ll=1#post24925

    Here is another version
    https://www.excelfox.com/forum/showt...ll=1#post24926
    The main new or changed features of this version are a few more explaining comments, and in the first column, the hwnd number is additionally given in Hexagonorrhoea and (2' compliment) binary. For the normal column width these extra numbers are not visible, but they are there for reference because:
    _ Spy's typically have Hexagonorrhoea so it is convenient for comparisons
    _ I want to jeep my eye on the binary to see if there are any typical values / patterns

    If I run that coding at a time and conditions on my computer, similar to those as I made those Screenshots above, and compare for example the numbers for an open Notepad text file, then we can see some good correlation with the top level results
    https://i.postimg.cc/BbtGWnqr/Good-c...-my-coding.jpg ( Full handle numbers: 224003622 D5A0626 00001101010110100000011000100110 )
    Good correlation with Spys and my coding.JPG
    The window Title also seems in agreement
    _____ Workbook: GetHwndClassNameCaptionHwnd.xls ( Using Excel 2013 32 bit )
    224003622 D5A0626 00001101010110100000011000100110 Notepad Neues Textdokument.txt - Editor
    224003622
    Worksheet: GetDesktopClassNames

    We can see however that the coding only gets us the top level information. We can often get at that information with coding, we must just remember the important point that in coding we must do it in steps, "walking the tree"




    In the coding and associated forum Thread posts there is some general top level coding with explanations.

    In the next post we will do some shorter simple coding, getting and using handles for that text file
    Last edited by DocAElstein; 12-02-2024 at 02:17 PM.

  9. #9
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,468
    Rep Power
    10

    Messaging window.

    Messaging window.
    Microsoft windows is controlled by messaging, and this messaging is a major part of the VBA Windows API subject.

    Example: ShowWindow ( Example, maximise and Minimise) http://allapi.mentalis.org/apilist/ShowWindow.shtml
    A look at the function description makes this fairly simple to understand. Two arguments, the first, necessarily requiring the hwnd of the window to be controlled in some way/ shown I some way, as specified by the second argument. In effect the second argument is just a number, from a set of numbers which determine what will be done
    We are using for the first time in this example the API constants. Using these is more of a conventional practice: Although there are some parallels with Early Binding of the available Library functions , we do not have available any named constants in VBA API work, in the same way that we do sometimes after Early Binding.
    But rather than using a number, we define a constant, and use that instead. The constant can have any name we like, ( and in fact, we can also be a simple variable rather than a Constant, but conventionally we use the recognised naming and assigning way. So we will use these sort of conventions also
    Const SW_MINIMIZE As Long = 6
    Const SW_MAXIMIZE As Long = 3

    https://i.postimg.cc/4y94MXh1/API-Constants.jpg https://i.postimg.cc/RqxCx27x/API-Constants.jpg
    The following demonstration coding works on a same text file as the previous coding and is self explanatory if run in debug mode
    https://i.postimg.cc/DZdPG4g9/Show-W...x-Min-Norm.jpg
    Code:
    Option Explicit
    Private Declare Function FindWndNumber Lib "user32" Alias "FindWindowA" (Optional ByVal lpClassName As String, Optional ByVal lpWindowName As String) As Long
    Private Const SW_MINIMIZE As Long = 6
    Private Const SW_MAXIMIZE As Long = 3
    Private Declare Function ShowWindow Lib "user32.dll" (ByVal hwnd As Long, ByVal nCmdShow As Long) As Long
    Private Const SW_NORMAL As Long = 1
    Sub TextAPI()
    Dim HdlTextFile As Long, MsgRef As Long
     Let HdlTextFile = FindWndNumber(lpClassName:="Notepad", lpWindowName:="Neues Textdokument.txt - Editor"): Debug.Print HdlTextFile & " " & Hex(HdlTextFile) '  984776 F06C8
    Dim FuncReturn As Variant
     Let FuncReturn = ShowWindow(HdlTextFile, SW_MINIMIZE): Debug.Print FuncReturn ' 24
     Let FuncReturn = ShowWindow(HdlTextFile, SW_MAXIMIZE): Debug.Print FuncReturn ' 24
     Let FuncReturn = ShowWindow(HdlTextFile, SW_NORMAL): Debug.Print FuncReturn   ' 24
    End Sub
    
    Example: ShowWindow ( Example Hide Unhide)
    This example follows on directly from the last, and perhaps requires little explanation. This perhaps borders on the area of "dangerous".
    Using the same text file as example I hide and unhide the window. I deliberately do this in the pair so as to hopefully leave all back in the previous normal
    Code:
    Option Explicit
    Private Declare Function FindWndNumber Lib "user32" Alias "FindWindowA" (Optional ByVal lpClassName As String, Optional ByVal lpWindowName As String) As Long
    Private Const SW_HIDE As Long = 0
    Private Declare Function ShowWindow Lib "user32.dll" (ByVal hwnd As Long, ByVal nCmdShow As Long) As Long
    Private Const SW_SHOW As Long = 5
    Sub TextAPI()
    Dim HdlTextFile As Long, MsgRef As Long
     Let HdlTextFile = FindWndNumber(lpClassName:="Notepad", lpWindowName:="Neues Textdokument.txt - Editor"): Debug.Print HdlTextFile & " " & Hex(HdlTextFile) '  984776 F06C8
    Dim FuncReturn As Variant
     Let FuncReturn = ShowWindow(HdlTextFile, SW_HIDE): Debug.Print FuncReturn ' 24
     Let FuncReturn = ShowWindow(HdlTextFile, SW_SHOW): Debug.Print FuncReturn ' 0     -    ' If the window was previously hidden, the return value is zero.
    End Sub
    Example, close window ( SendMessageA )
    Code:
    Option Explicit
    Private Declare Function FindWndNumber Lib "user32" Alias "FindWindowA" (Optional ByVal lpClassName As String, Optional ByVal lpWindowName As String) As Long
    Private Declare Function SendMessage Lib "user32.dll" Alias "SendMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByRef lParam As Any) As Long
    Const WM_CLOSE As Long = &H10
    
    Sub TextAPI()
    Dim HdlTextFile As Long
     Let HdlTextFile = FindWndNumber(lpClassName:="Notepad", lpWindowName:="Neues Textdokument.txt - Editor"): Debug.Print HdlTextFile & " " & Hex(HdlTextFile) '  984776 F06C8
    Dim FuncReturn As Variant
     Let FuncReturn = SendMessage(HdlTextFile, WM_CLOSE, 0, 0): Debug.Print FuncReturn '
    End Sub
    
    Example, Capture window text ( SendMessageA )
    These API things can be a bit obscure in their functioning and somewhat difficult to define, group or order in terms of what they are about. This example demonstrates that.
    In this example we remain with our text file examples, and look again at a text file and the corresponding winspy view centred around the "second level" Edit window, whose handle we found in an initial second handle getting coding above . We noted that it looked like it might be the window that we typically concern ourselves with when working on such a text file.
    In fact, as a confirmation, if we restart the winspy from new , we will initially have a small winspy window , and if we leave it initially small, but drag the small target/sight thing into the main part of the text file, then it expands and gives what it thinks is the window we dragged it into, in this case, indeed the Edit window with the actual text form the text file somehow showing in winspy.
    https://i.postimg.cc/sx3Fqktw/Draged...ext-editor.jpg


    Now it all gets a bit hit and miss and god knows if anyone really knows of any logic to the seemingly hap hazard way of doing things here…
    The last two arguments for the SendMessageA are not so well defined: - Specifies additional message-specific information. , and the documentation to the returned values is just as much use: - The return value specifies the result of the message processing and depends on the message sent.
    About as useful as a chocolate Teapot and as welcome as a fart in a space suit.
    Before completing this I took a look in a bit more detail in the next post and here
    Last edited by DocAElstein; 12-02-2024 at 03:47 PM.

  10. #10
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,468
    Rep Power
    10
    The ShellExecute function
    The ShellExecute function opens or prints a specified file in different ways, manipulating window(s) as it goes. The file can be an executable file or a document file. It offers some error indications too. So perhaps it is one of those things where it is the more fundamental and more useful version of something available in VB / VBA, perhaps something similar to like a worksheet function used from Application rather than Application.WorksheetFunction
    In this case the difference between the VBA shell function (execute) and the api shell execute are a bit more significant although the difference in error handling follows the similar trend, in that the VBA shell function would error when the api shell execute might give us some useful information. This perhaps ties up with the idea of us being more protected in the VB VBA normal environment, as some wiring is perhaps in place to take action on an error, rafter than telling us about it. The final terminal error that we then might get is then done when all other important things were done. So as ever, we should be more careful how we tread when using api things. I will keep, things simple for now and just open a text file
    Code:
    '     https://www.excelfox.com/forum/showthread.php/2989-Rough-Notes-and-posts-to-be-referenced-from-elsewhere-on-VBA-Windows-API?p=24915&viewfull=1#post24915
    Private Declare Function FindWndNumber Lib "user32.dll" Alias "FindWindowA" (Optional ByVal lpClassName As String, Optional ByVal lpWindowName As String) As Long
    Private Declare Function ShellExecute Lib "shell32.dll" Alias "ShellExecuteA" (ByVal hwnd As Long, ByVal lpOperation As String, ByVal lpFile As String, ByVal lpParameters As String, ByVal lpDirectory As String, ByVal nShowCmd As Long) As Long
    Const SW_NORMAL As Long = 1
    
    Sub TextAPI()   '
    Dim HdlTextFile As Long
    ' Let HdlTextFile = FindWndNumber(lpClassName:="Notepad", lpWindowName:="Neues Textdokument.txt - Editor"): Debug.Print HdlTextFile & " " & Hex(HdlTextFile) '
     Let HdlTextFile = FindWndNumber(lpClassName:="Notepad", lpWindowName:="TextFile.txt - Editor"): Debug.Print HdlTextFile & " " & Hex(HdlTextFile) '    0 0   
    Dim FuncReturn As Variant
    ' Let FuncReturn = ShellExecute(HdlTextFile, "open", "C:\Users\Elston\Desktop\Neues Textdokument.txt", 0, 0, SW_NORMAL): Debug.Print FuncReturn '
    ' Let FuncReturn = ShellExecute(HdlTextFile, "open", "C:\Users\Elston\Desktop\TextFile.txt", 0, 0, SW_NORMAL): Debug.Print FuncReturn '
     Let FuncReturn = ShellExecute(HdlTextFile, "open", ThisWorkbook.Path & "\TextFile.txt", 0, 0, SW_NORMAL): Debug.Print FuncReturn '        42
    End Sub
    Here we have perhaps another example of the strange varying way that arguments are handled with these api things, as HdlTextFile = FindWndNumber(………. line which we have a lot, is now used in a strange different way. It can’t be getting a handle this time, but never the less, the documentation suggests it somehow in conjunction with the first argument of ShellExecute( organises which parent window is used for displaying a user interface or error messages?? … maybe another case of … I can't think of any logical way to organise all this back end working at the upper user interface level, so just make an argument work however it can, don' tell anyone too much about it with any decent documentation, let a few hacks think they know, even some here who think they are creating or did create windows, and let them tell people about it and then good riddance to it all, I am off with my wife to enjoy the sun in a distant land, at least until she goes mental, as they all do eventually …. Bill Gates, early 80’s, …. I told him , or maybe it was one of his mates trying to sell windows to me, … I was not interested in those pretty coloured square boxes things, they all look like some sort of small child’s video game xmas present
    Attached Files Attached Files
    Last edited by DocAElstein; 12-03-2024 at 01:36 AM.

Similar Threads

  1. Version Info using VBA and registry quirks
    By DocAElstein in forum Test Area
    Replies: 6
    Last Post: 10-23-2024, 01:50 PM
  2. ADS info via VBA 64bit
    By TML59 in forum Excel Help
    Replies: 9
    Last Post: 07-13-2024, 03:43 PM
  3. Replies: 26
    Last Post: 07-17-2013, 11:42 AM
  4. Info: different Value !
    By PcMax in forum Excel Help
    Replies: 2
    Last Post: 04-22-2012, 04:13 PM
  5. Version 2003 to 2007
    By PcMax in forum Excel Help
    Replies: 5
    Last Post: 11-23-2011, 07:52 PM

Posting Permissions

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