Code:
' https://support.microsoft.com/de-de/help/199824/how-to-get-the-address-of-variables-in-visual-basic ' http://vb.mvps.org/tips/varptr/ ' https://www.mrexcel.com/forum/excel-questions/35206-test-inputbox-cancel-3.html
'
' ( Ctrl+Pause will usually stop this program ) https://www.excelforum.com/development-testing-forum/1215283-gimmie-ta-codexamples-call-in-the-appendix-posts-2018-no-reply-needed-but-if-u-2.html#post4828681
Sub UpInputBox() ' Note that you should make the Preparations here: ' https://www.excelforum.com/excel-new-users-basics/1099015-vba-application-inputbox-option-helpfile-helpcontextid.html#post4827572 ' https://www.click2trial.com/sure-thin-garcinia/
Rem 1 ' VBA Input Box Function works in all Excel versions so far. ' Application.Help HelpFile:="G:\Excel0202015Jan2016\ExcelForum\UserForm\HTML Workshop\chmFillesProjectFiles\Jan21\AnyFileName.chm", HelpContextID:=2
Dim strReturned As String ' "Pointer" to a "Blue Print" (or Form, Questionaire not yet filled in, a template etc.)"Pigeon Hole" in Memory, sufficient in construction to house a piece of Paper with code text giving the relevant information for the particular Variable Type. VBA is sent to it when it passes it. In a Routine it may be given a particular “Value”, or (“Values” for Objects). There instructions say then how to do that and handle(store) that(those). At Dim the created Paper is like a Blue Print that has some empty spaces not yet filled in. A String is a a bit tricky. The Blue Print code line Paper in the Pigeon Hole will allow to note the string Length and an Initial start memory Location. This Location well have to change frequently as strings of different length are assigned. Instructiions will tell how to do this. Theoretically a specilal value vbNullString is set to aid in quich checks.. But..http://www.mrexcel.com/forum/excel-questions/361246-vbnullstring-2.html#post44116
Let strReturned = InputBox(Prompt:="") ' This is the minimum option. Here and in the next line you can only put infomation in the box bar
If StrPtr(strReturned) = 0 Then Exit Sub ' If OK is clicked with no entry then a zero length string is returned. If Cancel is selected then the string variable does not yet have an address https://www.mrexcel.com/forum/excel-questions/917689-passing-array-class-byval-byref.html#post4412382 https://www.mrexcel.com/forum/excel-questions/35206-test-inputbox-cancel-2.html?highlight=strptr#post2845398
Dim strReturned2 As String ' ' http://www.excelfox.com/forum/showthread.php/1828-How-To-React-To-The-Cancel-Button-in-a-VB-(not-Application)-InputBox
Let strReturned2 = InputBox(Prompt:="Type Something in", Title:="MyBox", Default:="Something", xPos:=1000, yPos:=1000, HelpFile:=ThisWorkbook.Path & "\AnyFileName.chm", Context:=2)
If StrPtr(strReturned2) = 0 Then Exit Sub
Rem 2 ' Application Input Box Method with limited used optiional parameters
Dim VarReturn As Variant ' Use Variant so as to allow for whatever return that the Application Input Box Method may return https://msdn.microsoft.com/en-us/library/office/gg251422.aspx
Let VarReturn = Application.InputBox(Prompt:="") ' This is the minimum, BUT ALREADY we can now select a range in the worksheet
Let VarReturn = Application.InputBox(Prompt:="", HelpFile:=ThisWorkbook.Path & "\AnyFileName.chm", HelpContextID:=2) ' In Excel 2007+ the help options do not work. Nor do they in Excel 2003
Let VarReturn = Application.InputBox(Prompt:="", HelpFile:="Any Fink you like ", HelpContextID:=346326) ' In Excel 2007+ the help options appear not to be referrenced. Nor do they in Excel 2003
Let VarReturn = Application.InputBox(Prompt:="", Left:=100, Top:=100) ' In Excel 2007+ the positional arguments have no effect and the Input box comes up where it was the last time it came up. In Excel 2003 the positional arguments appear to work
Rem 3 ' Full options in Application InputBox
Dim dicLookupTableMSRD As Object ' For 7 type options in last Optional argument ( and 1 example of a combination )
Set dicLookupTableMSRD = CreateObject("Scripting.Dictionary") 'Late Binding MSRD In this case Dictionary and Scripting.Dictionary are the same. You can be sure of that because removing the reference to the Scripting runtime makes the Dictionary code fail. When you declare a variable as Dictionary, the compiler will check the available references to locate the correct object. There is no native VBA.Dictionary incidentally, though it is of course possible to create your own class called Dictionary, which is why I used the phrase "in this case". https://www.excelforum.com/excel-pro...ml#post4431231 http://www.eileenslounge.com/viewtop...=24955#p193413 https://www.excelforum.com/excel-pro...d-formats.html http://advisorwellness.com/blue-fortera/
Let dicLookupTableMSRD.CompareMode = vbTextCompare ' Compare mode property vbTextCompare is case unnsensitive. This must be done at the point here that the dictionary is empty
dicLookupTableMSRD.Add Key:=0, Item:="Formula" ' if you make a selection it
dicLookupTableMSRD.Add Key:=1, Item:="Number" ' Like a Double, Long, Single etc.
dicLookupTableMSRD.Add Key:=2, Item:="Text (a String)"
dicLookupTableMSRD.Add Key:=1 + 2, Item:="Number or Text" ' An example of one possible combinination
dicLookupTableMSRD.Add Key:=4, Item:="Logical value (True or False)" ' A logical value (True or False)
dicLookupTableMSRD.Add Key:=8, Item:="Range object" ' Note: usually you would then Set=InputBox for this option only. However, for the case of a returned range object, there will not be an error in assigning the returned thing to a variant ( Let Var = , or Var =) , ( rather than a more conventional in this case of Setting it to a range object) , as this is a typical case where VBA returns the default property of .Value from the range object. However the code has to do a bit of juggling about for this return and in the case of an Array return in order to show those values in a single displayable String
dicLookupTableMSRD.Add Key:=16, Item:="Error value" ' An error value, such as #N/A
dicLookupTableMSRD.Add Key:=64, Item:="Array"
Dim TypeOptions() As Variant: Let TypeOptions() = dicLookupTableMSRD.keys ' This Method returns an Array in Variant types - The variant type is necerssary as those keys could have been almost anything apart from Arrays. So we had to declare the Array to get the stuff back Variant type
Dim Stear As Variant
For Each Stear In TypeOptions()
Dim ThingReturned As Variant
Let ThingReturned = Application.InputBox(Prompt:="Type " & CLng(Stear) & ", " & dicLookupTableMSRD.Item(Stear) & "", Title:="MyBox", Default:="Something", Left:=100, Top:=100, HelpFile:=ThisWorkbook.Path & "\AnyFileName.chm", HelpContextID:=2, Type:=CLng(Stear))
If Not Stear = 4 And ThingReturned = False Then Exit Sub ' We can do a check here for if the user hit Cancel for all but the Type:= logical value as a logical value of false is returned for if the cancel is selected
If IsArray(ThingReturned) Then ' We have a 2 dimensional array even in the case of a single row or single column as that is how VBA holds array returned from a spreadsheet area
Dim strThingsReturned As String: Let strThingsReturned = "" ' If this is not reset to "" then the string build for the second time ( the Array type ) will include the first string built von the Range, that is to say the Range defaulting to Range.Value 'Let strThingsReturned = VBA.Strings.Join(ThingReturned, ", ")This is no good to us as the first argument must be a 1 dimension Array
Dim rIndx As Long, cIndx 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
For rIndx = 1 To UBound(ThingReturned, 1)
For cIndx = 1 To UBound(ThingReturned, 2)
Let strThingsReturned = strThingsReturned & ThingReturned(rIndx, cIndx) & ", "
Next cIndx
Let strThingsReturned = VBA.Strings.Left$(strThingsReturned, (Len(strThingsReturned) - 2)) ' Remove the last ", " in each complete row
Let strThingsReturned = strThingsReturned & ";" & vbCrLf ' go down a line for next row
Next rIndx
Let strThingsReturned = VBA.Strings.Left$(strThingsReturned, (Len(strThingsReturned) - 3)) ' takes off the last vbCr & vbLf & ";"
Debug.Print strThingsReturned: MsgBox Prompt:="Returned using option Type:=" & Stear & " ( " & dicLookupTableMSRD.Item(Stear) & ")" & vbCrLf & "(and held in the assigned Variant variable is """ & TypeName(ThingReturned) & """) is:" & vbCrLf & "values of " & vbCrLf & strThingsReturned
Else ' Single value is returned
Debug.Print ThingReturned; " "; TypeName(ThingReturned): MsgBox Prompt:="Returned using option Type:=" & Stear & " (" & dicLookupTableMSRD.Item(Stear) & ")" & vbCrLf & "(and held in the assigned Variant is Type Name """ & TypeName(ThingReturned) & """) is:" & vbCrLf & CStr(ThingReturned) ' The CStr appears only to be necessary for the case of an error in ThingReturned in the Message box. Debug.print seems to convert it to a string. All other things are converted to a String
End If
Next Stear
End Sub
Bookmarks