Page 3 of 3 FirstFirst 123
Results 21 to 30 of 30

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

  1. #21
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,439
    Rep Power
    10
    This is now post 21
    It was a Second copy from New post #16, 31 Oct 2024, all done on 31 Oct 2024
    #post24890




    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 exactly what event 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
    
    Last edited by DocAElstein; Today at 09:04 PM.

  2. #22
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,439
    Rep Power
    10
    This is now post 22 after a copy of full page 2 got me a new full page 3
    It was 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; Today at 09:07 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!!

  3. #23
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,439
    Rep Power
    10
    This is now post 23, after a copy of full page 2 gave me a full page 3
    It was First copy from New post #16, all done on 31 Oct 2024
    #post24889

    Last edited by DocAElstein; Today at 09:08 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!!

  4. #24
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,439
    Rep Power
    10
    This is a new post 24. It appeared after a copy of full page 2 gave me a full page 3. It is #post24897
    It came from 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 09:12 PM.

  5. #25
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,439
    Rep Power
    10
    This is a new post 25, appeasring after a fcopy of full page 2 got me a new full page 3 It is #post24898
    It came from 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; Today at 09:16 PM.

  6. #26
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,439
    Rep Power
    10
    This is a new post 26, appearing after a copy of a full page 2 gave me a full page 3. It is #post24899
    It came from Second copy from New post #16, 31 Oct 2024, all done on 31 Oct 2024
    #post24890

    Last edited by DocAElstein; Today at 09:18 PM.

  7. #27
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,439
    Rep Power
    10
    This is a new post 27, appearing after a copy of full page 2 gave me a full page 3. It is #post24900
    It was Taken from the Second copy from New post #16, 31 Oct 2024, all done on 31 Oct 2024
    #post24891

    Last edited by DocAElstein; Today at 09:20 PM.

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

    ….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. #29
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,439
    Rep Power
    10
    This was Post #20, but when I copied all of page 2, it became post #29 https://www.excelfox.com/forum/showt...age3#post24892
    https://www.excelfox.com/forum/showthread.php/2227-VBA-Input-Pop-up-Boxes-Application-InputBox-Method-versus-VBA-InputBox-Function/page3#post24892
    https://www.excelfox.com/forum/showt...ll=1#post24892
    https://www.excelfox.com/forum/showthread.php/2227-VBA-Input-Pop-up-Boxes-Application-InputBox-Method-versus-VBA-InputBox-Function?p=24892&viewfull=1#post24892
    The second link still worked, the first needed me to change the page 2 to page 3, which makes sense. (Otherwise it went to the top of page 2)


    Last edited by DocAElstein; Today at 07:38 PM.

  10. #30
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,439
    Rep Power
    10
    This is post 30, it came from post … well …post 29 that was post 20. So effectively it came from the post above
    29 https://www.excelfox.com/forum/showt...age3#post24902
    https://www.excelfox.com/forum/showthread.php/2227-VBA-Input-Pop-up-Boxes-Application-InputBox-Method-versus-VBA-InputBox-Function/page2#post24902
    https://www.excelfox.com/forum/showt...ll=1#post24902
    https://www.excelfox.com/forum/showthread.php/2227-VBA-Input-Pop-up-Boxes-Application-InputBox-Method-versus-VBA-InputBox-Function?p=24902&viewfull=1#post24902
    links are OK


    Last edited by DocAElstein; Today at 08:10 PM.

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
  •