Page 2 of 2 FirstFirst 12
Results 11 to 20 of 20

Thread: VBA Input Pop up Boxes: Application.InputBox Method versus VBA.InputBox Function

  1. #11
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,429
    Rep Power
    10
    Page 2 https://www.excelfox.com/forum/showt...Function/page2
    Original post #11,
    #post10483




    Section 3a) would be your main code in which you wanted to use / call up the Pop Up User pseudo InputBox with range selection thing which is the main issue of the last few posts.
    The simple demo I have done helps illustrate that thing I mentioned about the change of the ByRef to ByVal. If you play around with the code and change that __(By___) at the start of the next code section, then I think you will get the point of what I am suggesting there
    So in section 3a) the main thing related to the issue is the line
    _ Call HangAHookToCatchAPIssinUserDLL_MsgBoxThenBringThat MsgBoxUp(RSel)
    That code line makes the pop up come up, and the selected spreadsheet range is returned as a range object in the variable RSel. The code will wait until you have made the selection, but it will not prevent you from making the selection. So in that respect it works similarly to the Application Input Box Method when you use that Application Input Box Method and choose the last option as , Type:=8.


    Code:
    '  ========================
    Rem 3a) This is just to demo the idea of a Pop Up User InputBox with range selection alternative with API User 32 dll Programs.      ' Normally in this section 3a) there would be other stuff and probably lots of it and if I have anything then it will be very Pretty.. Pretty well disgusting probably.
    Sub MainSubWithAllOtherStuffInIt() ' This would be your main coding and would nornally be a lot bigger, it is just here as part of the demo for a Pop Up User InputBox with range selection alternative with API User 32 dll Programs
    ' Some where in the main code I might want to ask the user to select a range. So to do that I
    Dim RSel As Range ' This is a variable to hold the Pointer to the users range object..        So this variable in VBA is like the Link to the part of a URL string reducing size site where a few things about the actual Final site is informed about. This area in that site, like a pigeon Hole to which the variable refers, ( the "pigeon hole" location address, and all its contents would be defined as the "Pointer". Amongst other things it has a link, a "Pointing part", pointing to actually where all the stuff is
     'Set RSel = Selection ' This line will be needed if you chose to send ByVal. That is necerssary to ensure that you have a range object - If you do not have a range object when you go to HangAHookToCatchAPIssinUserDLL_MsgBoxThenBringThatMsgBoxUp(ByVal RcelsToYou), then you wont have one when you get back neither, as in HangAHookToCatchAPIssinUserDLL_MsgBoxThenBringThatMsgBoxUp you will be Set ing the copy variable, not the actual RSel variable. You put a copy of the Pointer in the new variable. But it is an object. A different object. A Copy object.   https://www.excelforum.com/excel-programming-vba-macros/1138804-help-understanding-class-instancing-cant-set-ws-new-worksheet-intellisense-offers-it-2.html#post4386360
     Call HangAHookToCatchAPIssinUserDLL_MsgBoxThenBringThatMsgBoxUp(RSel)  '                     In a normal application of the main Theme of all this, this would be the main code line you use to cause a the "Pop Up User pseudo InputBox with range selection alternative with API User 32 dll Programs"
     VBA.MsgBox Prompt:="Address check RSel - It is now " & RSel.Address & "" & vbCrLf & "Da .Value of the range object is " & RSel.Value ' Just done to demo that A simple change of the ByRef to ByVal in the signature line of a Called routine allows you to change the value of a range object to that of the selection, but the original range object will not change, that is to say its address remains as before the selection.
    End Sub
    Last edited by DocAElstein; Yesterday at 10:08 PM.

  2. #12
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,429
    Rep Power
    10
    New post #12, 31 Oct 2024, (was copied from Original post #11, when the original posts 11 12 1nd 13 were copied on 31 Oct 2024 so it got edited to change it to have contents of original post # 12),
    #post24886






    Section 3b)-3c) does two main things.
    _ A “Hook” is “Hanged” to both
    __ “catch” events similar to my “Non Modal message box” popping up,
    and then when it does it
    __ triggers off a Function WinSubWinCls_JerkBackOffHooKterd
    I have tried to explain everything in more detail in the ‘Comments
    What actually appears to happen in end effect is that typically as my message box Pops up the function is triggered 6 times before it gets to the one I actually want which is the Message box window being activated


    Code:
    Private Sub HangAHookToCatchAPIssinUserDLL_MsgBoxThenBringThatMsgBoxUp(ByRef RcelsToYou) ' This will by referral To You, (RSel), the actual Pointer of you the original RSel.  This is not too important a point here, but intersting if you consider the next line alternative to this one.....
    ' Public Sub HangAHookToCatchAPIssinUserDLL_MsgBoxThenBringThatMsgBoxUp(ByVal RcelsToYou)     The RSel Pointer aint Gone anywhere if you do this. Just a copy of the Pointer is here. This will allow you to change the value as the Pointer or a copy of it will tell you where to go and do that... But in neither this line or the last line case have you sent the range object. If you use this line then you will find that the address of the range object will not change, as that refers to the range object of the copy variable in this subroutine. But that will not change the range object of RSel
     Set RcelsToYou = Selection ' 3c(-i)                                                          Pointer GoneTo -1 WTF
    Noughty:                    ' 3c(0i)                                                          Pointer GoneTo 0y WTF
    ' 3b) Hang A Hook to catch things like APIssinUserDLL_MsgBox,   ....  HOOK: Hook the pseudo Windows Sub Class Function WinSubWinCls_JerkBackOffHooKerd
    Dim BookMarkClassTeachMeWind As Long: Let BookMarkClassTeachMeWind = 5 ' I do not need this. 5 is Hooktype that I will be using. Using a variable for two reasons: '1_- 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   '2_- Just to avoid confusion later as in this particular case later another option number in Rem 4 happens to be 5. That is checking for a Window opening. So it is similar to the 5 of BookMarkClassTeachMeWind, but it is a narrowed down version of those window happening things. So a bit of aa coincidence really. Using the variable just reminds me of that.
     Let hHookTrapCrapNumber = SetWindowsHooksExample(BookMarkClassTeachMeWind, AddressOf WinSubWinCls_JerkBackOffHooKerd, 0, GetDaFredId)   ' (5-pull before flush,  somehow arranges that the function gets called  ,
    ' 3c) Bring APIssinUserDLL_MsgBox up
    Dim Valyou As Variant: Let Valyou = RcelsToYou.Value: If IsArray(Valyou) Then Valyou = Valyou(1, 1) 'For display Value of Top Left of Selection
    Dim Rpnce As Long '                                                                           Long is very simple to handle, - final memory "size" type is known (123.456 and 000.001 have same "size" computer memory ) , and so a Address suggestion can be given for the next line when the variable is filled in.  '( Long is a Big whole Number limit (-2,147,483,648 to 2,147,483,647) If you need some sort of validation the value should only be within the range of a Byte/Integer otherwise there's no point using anything but Long.--upon/after 32-bit, Integers (Short) need converted internally anyways, so a Long is actually faster. )       https://www.mrexcel.com/forum/excel-questions/803662-byte-backward-loop-4.html
     Let Rpnce = APIssinUserDLL_MsgBox(hWnd:=&H0, Prompt:="Yes,  or No to ReCheck, Cancel for help ", Title:="Selection Check: Address is " & RcelsToYou.Address & "  Value is """ & Valyou & """", Buts:=vbYesNoCancel) ' ' Pseudo Non Modal MsgBox
     Set RcelsToYou = Selection: Let Valyou = RcelsToYou.Value: If IsArray(Valyou) Then Valyou = Valyou(1, 1) 'The code waited until you made one of the three message box options. But in this time you could change the selection object
        If Rpnce = 2 Then Application.Help HelpFile:=ThisWorkbook.Path & "\AnyFileName.chm", HelpContextID:=2 '              -----    download this file:  https://app.box.com/s/bx2pkvtemsppscz60rd6f430wm89c6fj This is a “.chm Microsoft Help file” It has the name _ AnyFileName.chm ---  Put in same folder as this Workbook  ---   Check out possible workarounds  --- http://www.excelfox.com/forum/showthread.php/2146-%E0%A4%AC%E0%A5%8D%E0%A4%B2%E0%A5%89%E0%A4%97-%E0%A4%95%E0%A5%8B%E0%A4%B6%E0%A4%BF%E0%A4%B6-%E0%A4%95%E0%A4%B0-%E0%A4%B0%E0%A4%B9%E0%A4%BE-%E0%A4%B9%E0%A5%88-%D8%A8%D9%84%D8%A7%DA%AF%D8%B2-%DA%A9%DB%8C-%DA%A9*Trying-Blogs?p=10467#post10467   ---  you should get this  HelpGetUpBollox.JPG imgur.com/KdKOYWr
        If Rpnce = 7 Then GoTo Noughty ' Option to update the displayed Address and Value in Top Left cell of that range
    End Sub
    '_-=Rem 4===========..
    Last edited by DocAElstein; Yesterday at 10:13 PM.

  3. #13
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,429
    Rep Power
    10
    Original post #12, it got shifted down one to post #13 when the original posts 11 12 and 13 where copied on 31 Oct 2024, so it got edited to have the contents of the original post # 13
    #post10484








    Section Rem 4 is the Function WinSubWinCls_JerkBackOffHooKterd
    This picks out the specific event I want, my “Non modal message box” being activated, and changes the window dimensions, using the API thing SetWindowPos
    ( You will need to experiment about with, mainly, the 10 50 400 150 The other two numbers 0 40 you may want to adjust as well. Understanding those two numbers fully is a bit beyond me – it took me best part of a week to figure out WTF all the other stuff was about ).
    The last thing this function does is “kill” or “drop” or ““take off” the “Hook”” or ““Unhook” the hook”. If you don’t do that the function seems to be triggered indefinitely.
    A last thing on a similar point: Some other codes doing something similar that I saw, seemed to cause a wild recursion: The size adjustment done in the function seemed to set off the function code again. The stack seemed to be limited to 30. I could not see any reason to do that, and in fact it seemed to cause some weird inconsistent ghostly images to appear on my desktop. My function just does the thing that I think it should do once. It appears more stable. I did have a lot of fun braking things before I got the API stuff correct. But since then the code seems to work well without problems in a number of code situations on different computers and different Excel versions.
    ( In all the situations that I have tried, my code has Exited as I have expected after an If clause detects if the function is on the start of a first recursion run. ( I think it would probably do no harm to unhook directly after the SetWindowPos , just in case the SetWindowPos does not cause recursion. ( It seems to do no harm to unhook a few times) )


    Code:
    '_-=Rem 4=============  Some hidden function / bookmark / bookmarks / cyber Robot thing was brought into life ("I hung or set a hook"). That monitors events like my message box popping up. When it catches one it starts this finction and passes to it three parameters. The first tells me with a number more excactly what even took place,  the next is the window identifying number of that window doing that particular event , the last parameter is something maybe to do with the mouse god knows what exactly probably even Sid don't know...  but looking at his Avatar I probably wouldn't say that to him  as he I don't know if I would want to mess with him...
    Private Function WinSubWinCls_JerkBackOffHooKerd(ByVal lMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long  '    I "set a hook"  which should trigger ( things similar to my Meassage box popping up  , and gave it the AddressOf this function ,  0   ,   and limited it to this "Thread" on my computer that is to say my Excel   )
     Let GlobinalCntChopsLog = GlobinalCntChopsLog + 1 '  The idea of this is that  I add 1 on entering and subtract 1 when leaving the function. So this would be two if I started an other copy of this code before the first had finished. I am expecting that as the SetWindowPosition seemes to trigger it off again.
        If GlobinalCntChopsLog = 2 Then Let GlobinalCntChopsLog = GlobinalCntChopsLog - 1: UnHookWindowsHookCodEx hHookTrapCrapNumber: Exit Function ' If I have 2 then that is an indication that recurtion has taken place, that is to say I started another function run caused by SetWindowPosition triggering it off. So i assume then that SetWindowPosition has done what it should so I can "take the hook off" (as if i did not then the function seems to get triggeredt indefinitely even without recusion), and then I exit the function. So I do expect a second copy of the code to run, but due to this it does not do anything other than take the "hook off". I also reduce the count by 1. It is then at 1. But then the first copy of the function ends from just under SetWindowPosition. So then the count is reduced again and is at the initial 0
        If lMsg = 5 Then Let Booloks = SetWindowPosition(wParam, 0, 10, 50, 400, 150, 40)   '  5 here is the number for a window about to be activated. This is probably the one I want. If I catch it when it is starting , 3, then It might then re set the size and position stuff again to the standard after I have done it
     Let GlobinalCntChopsLog = GlobinalCntChopsLog - 1 '  Every first copy run of the code has the count reduced to 0 so that when it starts again (as the only first copy active) it will be increased to 1 again to indicate it is a run of the function copy 1
    End Function






    _.________________________________________________ __________________________________________________ _________________________________-








    Edit Dec 2018 : check this out http://www.eileenslounge.com/viewtopic.php?f=30&t=31495 If / when I understand it I will post a follow up about this..
    Last edited by DocAElstein; Yesterday at 10:15 PM.

  4. #14
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,429
    Rep Power
    10
    New post #14, 31 Oct 2024, it came from the original post #12 when the original posts 11 12 and 13 where copied on 31 Oct 2024
    #post24887


    Code 'comment breakdown

    Pop Up User pseudo InputBox with range selection alternative with API User 32 dll Programs.
    This is a summary final working codes solution to allow a user to use a simple Pop up ( non UserForm ) to make an Excel range object selection.
    This solution allows you to make a spreadsheet selection whilst the Pop Up is up.
    The Standard stuff currently available
    The VBA Message Box and VBA Input Box Functions are Modal, in other words you cannot do anything to the spreadsheet when they are up.
    The Application Input Box Method should allow you to do this when you choose the last option as , Type:=8. It does allow you to do this, but a couple of things are broken:
    _ The ability to position the Pop up ( appears to be broken since Excel 2007 )
    _ The Microsoft help function does not appear to me to work in Excel 2003 2007 2010. I do not know if it ever worked for the Application Input Box Method
    My Solution
    This solution overcomes these problems, which is the main reason I did it, especially because of the first problem. It also has a few extra things that might be useful
    _ You can choose the size of the Pop up ( width , height )
    _ You can adjust the “z” things… I am not too clear on these options but in simple terms it means that you arrange how it appears in terms of the order of what windows you see, how and in which priority you see it, what windows are “under” or “above” it to see etc..
    _ A simple change of the ByRef to ByVal in the signature line of a Called routine ( Sub HangAHookToCatchAPIssinUserDLL_MsgBoxThenBringThat MsgBoxUp(By___ ) allows you to change the value of a range object to that of the selection, but the original range object will not change, that is to say its address remains as before the selection. That could give you an extra option in how you select and move around in a spreadsheet.

    Here we go then

    The Top Declare/Dim section
    Rem 1 Pseudo Non Modal MsgBox, MessageBoxA API Standard Non Standard Stuff, More Fundamentally complicated UnWRap it and.. "Pseudo Non Modal MsgBox" --- A valid handle, hWnd, other than the Excel spreadsheet window ( Private Declare Function FindWndNumber Lib "user32" Alias "FindWindowA" (Optional ByVal lpClassName As String, Optional ByVal lpWindowName As String) As Long --- hWndParent = FindWndNumber(lpClassName:="XLMAIN", lpWindowName:=vbNullString) ), or even no ( Null ) hWnd results in a pseudo Non Modal MsgBox http://www.excelfox.com/forum/showth...0476#post10470 http://www.tek-tips.com/faqs.cfm?fid=4699 https://eileenslounge.com/viewtopic....321874#p321874
    Code:
    Private Declare Function APIssinUserDLL_MsgBox Lib "user32" Alias "MessageBoxA" (Optional ByVal hWnd As Long, Optional ByVal Prompt As String, Optional ByVal Title As String, Optional ByVal Buts As Long) As Long  '
    .
    '_- ==== The above is all I need to do so that writing APIssinUserDLL_MsgBox in any code in this code module will do something very similar to the VBA MsgBox. The main difference is that when it is up, I can still scroll up and down in my Excel Spreadsheet and also select a range



    Rem 2_b)(ii) == To set/change The positional arguments "Sub Classing a "Window"" As is generally the case with “Window” Functions, A window belongs to a class. The Dynamic Linked Libraries concept allow the small programs in the with windows shipped typically in the User32 Folder programs to be called up / used at runtime, rather than a fixed set of instructions copied or and/ or used as such at some point. This allows for a modification of the class, known as Sub classing. This means that it is possible to modify / add to the “Window” Function and so pseudo create a customised ddl. It does not necessarily mean that a “Window” Function or a used User32 Folder program is directly Sub classes , but it just happens to be in our case as we are intending to mess about with the MessageBoxA ( or MessageBoxTimeoutA ) You can arrange that a used “Window” Function is modified as it is used.
    ' The next four line will tie something on my chain for when you pull it. Similar in the way that a Worksheet_change code is triggered as something happens, you must arrange that a VBA Function is triggered when a Windows “event” occurs. At this point the concept gets a bit vague and I doubt many people really understand anymore how it really works. A good name for the VBA Function might be Function WinSubWinCls_JerkBackOffHooKterd. This VBA Function will itself be a pseudo “Window” Function and “hung” or hooked on a chain of events. Because of the dynamic / volatile nature of the stuff, things will have a habit of going on forever if they not “unhooked” such that a procedure will have to be designed to unhook itself.

    Code:
    Private Declare Function SetWindowsHooksExample Lib "user32" Alias "SetWindowsHookExA" (ByVal Hooktype As Long, ByVal lokprocedureAddress As Long, Optional ByVal hmod As Long, Optional ByVal DaFredId As Long) As Long 
    '   The effect of this will be: In some predetermined set of instructions or planned chain of events
    , a “hook” or “marker” or “clap trap” or “page marker” or “trip trap” was made. This was given an identifying number which was returned by 
    that “API Function” and it was chosen to be placed in the main code in a globial variable hHookTrapCrapNumber.
     I do not think that this number identifies the “page in the book” where the bookmarker is. 
    I think it just is listed somewhere in a list of any active / set up book marks. I guess there might be / could be a few, so you need to distinguish them.
    Private hHookTrapCrapNumber As Long ' "BookmarkClassNumber --- This makes pseudo
      Declare Sub() SetWindowsHooksExample Lib "user32" AliAs "SetWindowsHookExA" (ByVal hHookTrapCrapNumber As Long, ByVal Hooktype As Long, ByVal MyloksPROCedureFukAddress As Long, Optional ByVal RadioButton2Out As Long, Optional ByVal duhFredId As Long) As Long 
        It was also disgussed that possibly the number refers to set instances of a Bookmark class: there may be a few ,
     but they are all effectively connected / activated by the number hHookTrapCrapNumber existing in some register. 
    The bookmarker has a particular type, ( 5 ). The type will be responsible for catching the Message box code line to call the MessageBoxA,
     (like  APIssinUserDLL_MsgBox &H0, "Select Range", "working ApplicationPromptToRangeInputBox", vbYesNoCancel ). 
    That fires my hook PROCedure Function, WinSubWinCls_JerkBackOffHooKterd. 
    Other things may also fire my hook PROCedure Function. They may or may not be also related to the Popping up of my Box.
    '               Dim BookMarkClassTeachMeWind As Long: Let BookMarkClassTeachMeWind = 5 ' 5 is Hooktype that I will be using. Using a variable for two reasons: '1_- 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   '2_- Just to avoid confusion Later as in this particular case later another option number happens to be 5
    Private Declare Function  GetDaFredId Lib "kernel32" Alias "GetCurrentThreadId" () As Long '   The Thread is what is going on,
     I expect that means in this case my VBA. My computer might do something else with or without me knowing. Most things going on will have a Thread number.
     When used in my code, Function GetDaFredId will return an identifying number referring to the Excel instance that that code line is in.     
    It is actually needed in the setting of the Windows hook code line only ( that which is last argument in   SetWindowsHookEx(  ,   ,   , DaFredId As Long) ... 
    ..set a hook, confined to the current thread (so it doesn't get triggered by other things going on) and give it the address of the function that you want to call in response to the hook being triggered. In this I will use 5 CBT hook which is triggered generally by Window messages (activating, creating, destroying, minimizing, maximizing, moving, or sizing a window)
    
    ' This below takes it off the chain. Or wipe the chain clean.  Or remove it from something.   Or cancel it. Or Kill it.   Or whatever. 
     In any case it needs the identifying number of the "hook",  then a simple code line as shown in comment below will do this "Killing"   
     Without doing this the thing seems to go on indefinitely (with or without any recursion. (A recursion is another issue which seems to happen as an additional issue - that occurs when the final API code below (over next line) does its job - that seems to fire  my Hook PROCedure function WinSubWinCls_JerkBackOffHooKterd 
    Private Declare Function  UnHookWindowsHookCodEx Lib "user32" Alias "UnhookWindowsHookEx" (ByVal hHookTrapCrapNumber As Long) As Long '               'Release the Hook           This is used in code in a simple code line like:-      Call UnHookWindowsHookCodEx(hHookTrapCrapNumber)
    
    '_- === All of the above in section Rem 2 is required so that I am able to organise that when I use APIssinUserDLL_MsgBox another program (my windows hookProcedure program WinSubWinCls_JerkBackOffHooKterd) is triggered. (It has a habit of being triggered indefinitely so the API program Decared in the last line above will be used to stop that happening)

    '2(d)=== The Final API program below we need to actually do what we want. (WindowIdentifyinghandle, zorder , x , y , width , height , zFurtherInfo ) '_- Most is obvious, except the z stuff - WindowIdentifyinghandle/wParam is one the parameters passed in some secret process to my Function WinSubWinCls_JerkBackOffHooKterd( , wParam , ) and will be the windows identifying number for my Message box that is popping up. ( ,10 ,50 ,400 ,150 , ) These four numbers are the horizontal and vertical size and positions. ( 0, , , , ,40 ) The two numbers 0 and 40 are chosen after a bit of intuitive guessing based on Microsoft references like https://msdn.microsoft.com/en-us/lib...(v=vs.85).aspx The end effect is to have the window seen as dominantly as wanted. They are likely to be based to some extent on experimenting in a particular requirement.
    Code:
    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
     '    This API prog will be called in my hook PROCedure function. 
     So.. Rem 2a)-c) sets "Bookmark"/ series of "Bookmarks"/ Microsoft Windows cyber Robot monitering events (of "type 5", i.e. my Pop up coming up is one such. 
    When such a event occurs my function is triggered by Windows software monitering Robot, he knows where/which my function WinSubWinCls_JerkBackOffHooKterd is from the  AddressOf  in a "hook setting code line" like  
    (5 ,AddressOf WinSubWinCls_JerkBackOffHooKterd , 0, ThreadID) 
    The monitering Robot program thing passes somehow  (a number from a list of event types to tell me more precisely what event it noticed, wParam-identifying number of the Window doing that event, possibly some other mouse thing info thing am not bothered about)
     
    Code:
    Dim Booloks As Boolean ' I use this in the code line  Booloks = SetWindowPosition(WindowIdentifyinghandle, zorder,x, y, width, height ,zFurtherInfo)  
     I don't seem to need this, but as a function, the SetWindowPos is designed to return a value. In this usage I have not experienced problems using it as a Sub routine Call like    Call SetWindowPosition( , , , , , , )    but to be on the safe side I have used it as a Function returning its return in a Boolean variable, Booloks
    Dim GlobinalCntChopsLog As Long ' I use this to keep track of the copy number of my Hook PROCedure function WinSubWinCls_JerkBackOffHooKterd, that is to say check for when that  = 2. If that is the case I do the "unhooking" and Exit the Function
    '  ========================
     
    Last edited by DocAElstein; Today at 12:14 AM.

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

    The bit appearing in your main main coding. The bit you run to do the final thing

    Original post #13, it got shifted down to post #15 when posts 11 12 and 13 where copied on 31 Oct 2024 #post10485

    Last edited by DocAElstein; Today at 12:38 AM.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  6. #16
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,429
    Rep Power
    10
    New post #16, 31 Oct 2024, it came from the original post #13 when original posts 11 12 and 13 where copied on 31 Oct 2024
    #post24888

    Last edited by DocAElstein; 10-31-2024 at 01:33 PM.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  7. #17
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,429
    Rep Power
    10
    Second copy from New post #16, 31 Oct 2024, all done on 31 Oct 2024
    #post24890

    Last edited by DocAElstein; 10-31-2024 at 01:44 PM.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  8. #18
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,429
    Rep Power
    10
    Taken from the Second copy from New post #16, 31 Oct 2024, all done on 31 Oct 2024
    #post24891




    Archive post, one I updated later. Just kept in case I need it later (Was original post # 4)
    From last post…………..
    Handleing of the MsgBox Pop up
    The below attempts to put some clarity, as far as I am able, on what the handle of the MsgBox, or rather API User32 Windows dll MessageBoxA Function might be about.
    I am able to find A “handle to a Window” that makes the API User32 Windows dll MessageBoxA appear to work as the Standard “non modal” VBA MsgBox.
    In all other cases of either a successfully found handle number ( to which it belongs is not clear to me ) or an unsuccessful found handle number ( hWnd is then 0 as returned from FindWind___ ), I appear to have a “non modal” Pop up box, in which case I have the possibility to make a spreadsheet selection with the Pop Up, popped up
    Some further reading has suggested that the unsuccessful found handle number returns a specific type of Long Null and contradictorily to some other literature suggests that this pop up must not have a owner window. There may be some morae subtle points to it, but for now the use of the special symbol for a Long Null _ &H0 _ would suggest that the major part of the solution can be reduced to a simplified code lines such as in '2e) This will do then
    Code:
    Option Explicit
    '
    Private Declare Function APIssinUserDLL_MsgBox Lib "user32" Alias "MessageBoxA" (Optional ByVal hWnd As Long, Optional ByVal Prompt As String, Optional ByVal Title As String, Optional ByVal buttons As Long) As Long '
    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 TestWndBreaks()    '    http://www.eileenslounge.com/viewtopic.php?f=18&t=28885#p223583
    Dim Response As Long
    Rem 1 ' Standard VBA Message Box
     Let Response = MsgBox(Prompt:="Q_- Where am I, the MsgBox? " & vbCrLf & "A_- locked Middle in Excel spreadsheet") '
    Rem 2 ' Message Box API User32 dll
     Let Response = APIssinUserDLL_MsgBox(Prompt:="Q_- Where am I, the MessageBoxA?" & vbCrLf & " A_- Middle in Active Window") '
    ' 2b) Get a number for hWnd to "lock" the Message box to a window
    ' Locked nowhere?
    Dim WndNumber As Long
     Let WndNumber = FindWndNumber(lpClassName:=vbNullString, lpWindowName:=vbNullString): Debug.Print WndNumber ' -- must be vbNullString not ""  ??
     Let Response = APIssinUserDLL_MsgBox(hWnd:=WndNumber, Prompt:="Q_- Where am I, the MessageBoxA?" & vbCrLf & " A_- Middle in Active Window, hwnd = " & WndNumber & "", Title:="""Non Modal"" Pop Up", buttons:=vbOKOnly) '
    
    ' 2c) working like the Standard VBA Message Box ??        https://www.techrepublic.com/blog/10-things/10-plus-of-my-favorite-windows-api-functions-to-use-in-office-applications/
    Dim hWndParent As Long
     Let hWndParent = FindWndNumber(lpClassName:="XLMAIN", lpWindowName:=vbNullString): Debug.Print hWndParent '
     Let Response = APIssinUserDLL_MsgBox(hWnd:=hWndParent, Prompt:="Q_- Where am I, the MessageBoxA?" & vbCrLf & " A_- locked Middle in Excel spreadsheet, hwnd = " & hWndParent & "", Title:="""Working like"" Microsoft Excel", buttons:=vbOKOnly) '
    ' 2d) Not sure whats gooing on
     Let hWndParent = FindWndNumber(lpClassName:="XLMAIN", lpWindowName:=ThisWorkbook.Name): Debug.Print hWndParent '
     Let Response = APIssinUserDLL_MsgBox(hWnd:=hWndParent, Prompt:="Q_- Where am I, the MessageBoxA?" & vbCrLf & " A_- locked Middle in Active Window??, hwnd = " & hWndParent & "", Title:="""Working like"" Non Modal ??", buttons:=vbOKOnly) '
     Let hWndParent = FindWndNumber(lpClassName:=vbNullString, lpWindowName:=ThisWorkbook.Name): Debug.Print hWndParent '
     Let Response = APIssinUserDLL_MsgBox(hWnd:=hWndParent, Prompt:="Q_- Where am I, the MessageBoxA?" & vbCrLf & " A_- locked Middle in Active Window??, hwnd = " & hWndParent & "", Title:="""Working like"" Non Modal ??", buttons:=vbOKOnly) '
    Dim hWndDskTop As Long
     Let hWndDskTop = FindWindowEx(hWndParent, 0&, "XLDESK", vbNullString): Debug.Print hWndDskTop '  https://msdn.microsoft.com/de-de/library/windows/desktop/ms633500(v=vs.85).aspx
     Let Response = APIssinUserDLL_MsgBox(hWnd:=hWndDskTop, Prompt:="Q_- Where am I, the MessageBoxA?" & vbCrLf & " A_- locked Middle in Active Window??, hwnd = " & hWndDskTop & "", Title:="""Working like"" Non Modal ??", buttons:=vbOKOnly) '
     Let hWndDskTop = FindWindowEx(hWndParent, 0&, "XLDESK", ThisWorkbook.Name): Debug.Print hWndDskTop
     Let Response = APIssinUserDLL_MsgBox(hWnd:=hWndDskTop, Prompt:="Q_- Where am I, the MessageBoxA?" & vbCrLf & " A_- locked Middle in Active Window??, hwnd = " & hWndDskTop & "", Title:="""Working like"" Non Modal ??", buttons:=vbOKOnly) '
    '2e) This will do then
     APIssinUserDLL_MsgBox hWnd:=&H0, Prompt:="This will do", Title:="""Working like"" Non Modal" '
    End Sub

    Using a variation of that can be used to write a short set of codes to allow the user to make a selection which can be shown as an address in the Pop Up which is the current collection, and which can be updated by making a new selection.
    In this code although the Message box itself is not returning a range object, the final range returned a t the end of the routine, Rsel , is based on the user selection. In addition the user on selecting “No” the Pop Up will re Pop up with the current selection displayed

    The end effect is something along the lines of a Pop Up User InputBox with range selection alternativ to the Method _.....
    Application.InputBox( Prompt:= , Title:= , Default:= , Left:= , Top:= , HelpFile:= , HelpContextID:= , Type:=8 )
    _.......with API User 32 dll Programs.
    Code:
    Option Explicit
    Private Declare Function APIssinUserDLL_MsgBox Lib "user32" Alias "MessageBoxA" (Optional ByVal hWnd As Long, Optional ByVal Prompt As String, Optional ByVal Title As String, Optional ByVal Buts As Long) As Long  '                                                                               ' MessageBoxA   http://www.tek-tips.com/faqs.cfm?fid=4699
    '
    Public Sub PopUpInputBoxWithRngSelAPIUser32dll()
    Noughty: 'PopUpInputBoxWithRngSelAPIUser32dll
    Dim Rpnce As Long, Rsel As Range: Set Rsel = Selection
    Dim Valyou As Variant: Let Valyou = Rsel.Value: If IsArray(Valyou) Then Valyou = Valyou(1, 1) 'For display Value of Top Left of Selection
     Let Rpnce = APIssinUserDLL_MsgBox(hWnd:=&H0, Prompt:="Yes,  or No to ReCheck, Cancel for help ", Title:="Selection Check: Address is " & Rsel.Address & "  Value is """ & Valyou & """", Buts:=vbYesNoCancel) ' ' Pseudo Non Modal MsgBox
        If Rpnce = 2 Then Application.Help HelpFile:=ThisWorkbook.Path & "\AnyFileName.chm", HelpContextID:=2 '              -----    download this file:  https://app.box.com/s/bx2pkvtemsppscz60rd6f430wm89c6fj This is a “.chm Microsoft Help file” It has the name _ AnyFileName.chm ---  Put in same folder as this Workbook  ---   Check out possible workarounds  --- http://www.excelfox.com/forum/showthread.php/2146-%E0%A4%AC%E0%A5%8D%E0%A4%B2%E0%A5%89%E0%A4%97-%E0%A4%95%E0%A5%8B%E0%A4%B6%E0%A4%BF%E0%A4%B6-%E0%A4%95%E0%A4%B0-%E0%A4%B0%E0%A4%B9%E0%A4%BE-%E0%A4%B9%E0%A5%88-%D8%A8%D9%84%D8%A7%DA%AF%D8%B2-%DA%A9%DB%8C-%DA%A9*Trying-Blogs?p=10467#post10467   ---  xpu shopuld get this  HelpGetUpBollox.JPG https://imgur.com/KdKOYWr
        If Rpnce = 7 Then GoTo Noughty ' Option to update the displayed Address and Value in Top Left cell of that range
     Set Rsel = Selection
    End Sub
    So the code simply takes the current spreadsheet selection as the required range. The address of this is also displayed as the Pop up caption.
    An option is included for a help file, ( I have checked and found that this works in excel 2003, 2007 and 2010 for a valid .chm file)
    An Option is also included to repeat the process. ( This allows a new selection to be displayed in the caption)
    The end effect is something along the lines of a Pop Up User InputBox with range selection alternative to the Method_..
    Application.InputBox( Prompt:= , Title:= , Default:= , Left:= , Top:= , HelpFile:= , HelpContextID:= , Type:=8 )
    _....... with API User 32 dll Programs.



    Further reading shows that an even more “fundamental” API Function is the MessageBoxTimeoutA. It can be used similarly, and indeed might be an even better option as it used by all other Message Box Functions. Therefore it might be a good option as it is more likely to be maintained in the future ( https://www.excelforum.com/developme...ml#post4822413 )




    The next posts tackle the Window positioning ( and size ) issue, Rem2_b)(ii) the positional arguments

    _._______________________________


    _._______________________________
    Last edited by DocAElstein; 10-31-2024 at 01:58 PM.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  9. #19
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,429
    Rep Power
    10
    First copy from New post #16, all done on 31 Oct 2024
    #post24889

    Last edited by DocAElstein; 10-31-2024 at 01:37 PM.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  10. #20
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,429
    Rep Power
    10
    Post for later

    API notes and tests
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

Similar Threads

  1. How To React To The Cancel Button in a VB (not Application) InputBox
    By Rick Rothstein in forum Rick Rothstein's Corner
    Replies: 2
    Last Post: 02-04-2018, 01:48 AM
  2. Replies: 2
    Last Post: 02-12-2016, 04:32 PM
  3. InputBox OK and Cancel Button Problem
    By mackypogi in forum Excel Help
    Replies: 5
    Last Post: 05-30-2014, 12:20 AM
  4. VBA To Display Pop Up Alert When Duplicate Entry Is Made
    By peter renton in forum Excel Help
    Replies: 20
    Last Post: 07-26-2013, 07:56 PM
  5. Number validation in Text Boxes VBA
    By Admin in forum Excel and VBA Tips and Tricks
    Replies: 2
    Last Post: 05-17-2012, 02:48 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
  •