InputBox and MsgBox

Maintained on

When creating macros in VBA, the ability to receive user input and display processing results is essential. VBA provides two functions—InputBox and MsgBox—that make these tasks easy.

This article covers everything from basic usage to advanced techniques for InputBox and MsgBox, with practical code examples.

When You Need InputBox and MsgBox

In practice, you’ll use InputBox and MsgBox in these situations:

InputBox Use Cases

  • User name input: Capture names for login or record keeping
  • Search keyword entry: Search for specific values in data
  • Numeric input: Obtain parameters needed for calculations
  • File name specification: Let users specify save file names
  • Date input: Set date ranges or filter conditions

MsgBox Use Cases

  • Completion notifications: “Processing complete” messages
  • Error message display: Warnings when problems occur
  • Confirmation dialogs: “Are you sure you want to delete?” prompts
  • Choice presentation: “Yes/No” selection requests
  • Information display: Show calculation results or statistics

MsgBox: Displaying Messages

Basic Syntax

MsgBox(message, [buttons], [title], [helpfile], [context])

Simplest form:

MsgBox "Message"

Basic Usage

msgbox_basic.bas
Sub MsgBoxBasic()
    ' Simple message display
    MsgBox "Hello, World!"

    ' With title
    MsgBox "Processing complete.", , "Notification"

    ' Multi-line message
    MsgBox "Line 1" & vbCrLf & "Line 2" & vbCrLf & "Line 3"
End Sub
チェック

vbCrLf is a line break constant. You can also use vbLf (line feed) or vbCr (carriage return).

Button Types

MsgBox supports various button combinations:

ConstantValueDescription
vbOKOnly0OK button only (default)
vbOKCancel1OK and Cancel buttons
vbAbortRetryIgnore2Abort, Retry, Ignore buttons
vbYesNoCancel3Yes, No, Cancel buttons
vbYesNo4Yes and No buttons
vbRetryCancel5Retry and Cancel buttons
msgbox_buttons.bas
Sub MsgBoxButtons()
    ' OK and Cancel buttons
    MsgBox "Continue?", vbOKCancel, "Confirm"

    ' Yes/No buttons
    MsgBox "Delete this item?", vbYesNo, "Delete Confirmation"

    ' Yes/No/Cancel buttons
    MsgBox "Save changes?", vbYesNoCancel, "Save Confirmation"
End Sub

Icon Types

Display icons based on message importance:

ConstantValueDescriptionIcon
vbCritical16Critical error
vbQuestion32Question
vbExclamation48Warning⚠️
vbInformation64Informationℹ️
msgbox_icons.bas
Sub MsgBoxIcons()
    ' Error message
    MsgBox "An error occurred!", vbCritical, "Error"

    ' Warning message
    MsgBox "Please check your input.", vbExclamation, "Warning"

    ' Information message
    MsgBox "Process completed.", vbInformation, "Complete"

    ' Question message
    MsgBox "Delete this?", vbQuestion + vbYesNo, "Confirm"
End Sub
チェック

Buttons and icons can be combined by adding them together. Example: vbYesNo + vbQuestion

Handling Return Values

MsgBox returns a value based on which button the user clicks:

ConstantValueButton Clicked
vbOK1OK
vbCancel2Cancel
vbAbort3Abort
vbRetry4Retry
vbIgnore5Ignore
vbYes6Yes
vbNo7No
msgbox_return_value.bas
Sub MsgBoxReturnValue()
    Dim result As VbMsgBoxResult

    ' Get user's selection
    result = MsgBox("Delete this file?", vbYesNo + vbQuestion, "Delete Confirmation")

    ' Branch based on return value
    If result = vbYes Then
        MsgBox "File deleted.", vbInformation
        ' Actual delete code here
    Else
        MsgBox "Deletion cancelled.", vbInformation
    End If
End Sub

Using Select Case for Multiple Options

When there are multiple choices, Select Case is convenient:

msgbox_select_case.bas
Sub MsgBoxSelectCase()
    Dim result As VbMsgBoxResult

    result = MsgBox("Save changes?", vbYesNoCancel + vbQuestion, "Exit Confirmation")

    Select Case result
        Case vbYes
            MsgBox "Saving and exiting.", vbInformation
            ' Save code here

        Case vbNo
            MsgBox "Exiting without saving.", vbInformation
            ' Exit code here

        Case vbCancel
            MsgBox "Cancelled.", vbInformation
            ' Do nothing

    End Select
End Sub

Setting the Default Button

Specify which button is selected by default (responds to Enter key):

ConstantValueDescription
vbDefaultButton10First button (default)
vbDefaultButton2256Second button
vbDefaultButton3512Third button
vbDefaultButton4768Fourth button
msgbox_default_button.bas
Sub MsgBoxDefaultButton()
    Dim result As VbMsgBoxResult

    ' Dangerous operation: set default to "No"
    result = MsgBox("Delete ALL data?", _
                    vbYesNo + vbCritical + vbDefaultButton2, _
                    "Dangerous Operation")

    If result = vbYes Then
        MsgBox "Data deleted.", vbInformation
    End If
End Sub
チェック

For destructive operations like deletion, set the safe option as the default button to prevent accidental execution.

InputBox: Getting User Input

Basic Syntax

InputBox(prompt, [title], [default], [xpos], [ypos], [helpfile], [context])

Basic Usage

inputbox_basic.bas
Sub InputBoxBasic()
    Dim userName As String

    ' Simple input
    userName = InputBox("Enter your name:")

    If userName <> "" Then
        MsgBox "Hello, " & userName & "!", vbInformation
    Else
        MsgBox "No name entered.", vbExclamation
    End If
End Sub

With Title and Default Value

inputbox_with_defaults.bas
Sub InputBoxWithDefaults()
    Dim filePath As String

    ' With title and default value
    filePath = InputBox("Enter save location:", _
                        "File Path", _
                        "C:\Documents\output.xlsx")

    If filePath <> "" Then
        Debug.Print "Path: " & filePath
    End If
End Sub

Handling Cancel

inputbox_cancel.bas
Sub InputBoxHandleCancel()
    Dim input As String

    input = InputBox("Enter a value:")

    ' InputBox returns empty string on Cancel or empty input
    If StrPtr(input) = 0 Then
        ' Cancel was clicked
        MsgBox "Cancelled.", vbInformation
    ElseIf input = "" Then
        ' OK was clicked but input was empty
        MsgBox "No input provided.", vbExclamation
    Else
        ' Valid input
        MsgBox "You entered: " & input, vbInformation
    End If
End Sub
チェック

Use StrPtr(input) = 0 to distinguish between Cancel and empty input. If StrPtr returns 0, the user clicked Cancel.

Input Validation

inputbox_validation.bas
Sub InputBoxWithValidation()
    Dim input As String
    Dim number As Double
    Dim isValid As Boolean

    Do
        input = InputBox("Enter a number (1-100):", "Number Input")

        If StrPtr(input) = 0 Then
            ' Cancel clicked
            Exit Sub
        End If

        ' Check if it's a valid number
        If IsNumeric(input) Then
            number = CDbl(input)
            If number >= 1 And number <= 100 Then
                isValid = True
            Else
                MsgBox "Enter a number between 1 and 100.", vbExclamation
            End If
        Else
            MsgBox "Please enter a valid number.", vbExclamation
        End If
    Loop Until isValid

    MsgBox "You entered: " & number, vbInformation
End Sub

Application.InputBox: Enhanced Input

Excel provides Application.InputBox with additional features not available in the standard VBA InputBox.

Key Difference: Type Parameter

application_inputbox.bas
Sub ApplicationInputBox()
    Dim rng As Range

    ' Type 8: Range selection
    On Error Resume Next
    Set rng = Application.InputBox("Select a range:", "Range Selection", Type:=8)
    On Error GoTo 0

    If Not rng Is Nothing Then
        MsgBox "Selected: " & rng.Address, vbInformation
    Else
        MsgBox "Selection cancelled.", vbInformation
    End If
End Sub

Type Parameter Values

ValueDescription
0Formula
1Number
2Text (String)
4Logical (True/False)
8Range reference
16Error value
64Array of values

Getting Different Input Types

application_inputbox_types.bas
Sub GetDifferentTypes()
    Dim numValue As Variant
    Dim textValue As Variant

    ' Get number (Type 1)
    numValue = Application.InputBox("Enter a number:", "Number Input", Type:=1)
    If numValue <> False Then
        Debug.Print "Number: " & numValue
    End If

    ' Get text (Type 2)
    textValue = Application.InputBox("Enter text:", "Text Input", Type:=2)
    If textValue <> False Then
        Debug.Print "Text: " & textValue
    End If
End Sub

Practical Examples

Data Entry Form

data_entry_form.bas
Sub DataEntryForm()
    Dim name As String
    Dim age As String
    Dim department As String
    Dim confirm As VbMsgBoxResult

    ' Get name
    name = InputBox("Enter employee name:", "Data Entry")
    If StrPtr(name) = 0 Or name = "" Then Exit Sub

    ' Get age
    age = InputBox("Enter age:", "Data Entry")
    If StrPtr(age) = 0 Or Not IsNumeric(age) Then Exit Sub

    ' Get department
    department = InputBox("Enter department:", "Data Entry")
    If StrPtr(department) = 0 Or department = "" Then Exit Sub

    ' Confirm entry
    confirm = MsgBox("Register the following?" & vbCrLf & vbCrLf & _
                     "Name: " & name & vbCrLf & _
                     "Age: " & age & vbCrLf & _
                     "Department: " & department, _
                     vbYesNo + vbQuestion, "Confirm")

    If confirm = vbYes Then
        ' Write to sheet
        Dim nextRow As Long
        nextRow = Cells(Rows.Count, 1).End(xlUp).Row + 1

        Cells(nextRow, 1).Value = name
        Cells(nextRow, 2).Value = age
        Cells(nextRow, 3).Value = department

        MsgBox "Data registered.", vbInformation
    Else
        MsgBox "Registration cancelled.", vbInformation
    End If
End Sub

Progress Messages

progress_messages.bas
Sub ProcessWithProgress()
    Dim i As Long
    Dim total As Long
    Dim result As VbMsgBoxResult

    total = 100

    ' Confirm start
    result = MsgBox("Process " & total & " items?", vbYesNo + vbQuestion, "Confirm")
    If result = vbNo Then Exit Sub

    ' Process with status updates
    Application.StatusBar = "Processing..."

    For i = 1 To total
        ' Your processing code here

        ' Update status bar every 10 items
        If i Mod 10 = 0 Then
            Application.StatusBar = "Processing: " & i & "/" & total & " (" & Format(i / total, "0%") & ")"
            DoEvents
        End If
    Next i

    Application.StatusBar = False
    MsgBox "Processing complete! " & total & " items processed.", vbInformation
End Sub

Summary

InputBox and MsgBox are essential tools for user interaction in VBA:

MsgBox:

  • Use appropriate button combinations for the situation
  • Add icons to convey message importance
  • Set safe defaults for destructive operations
  • Handle return values to control program flow

InputBox:

  • Use StrPtr() to distinguish Cancel from empty input
  • Validate input before processing
  • Use Application.InputBox for range selection and type validation

Master these functions to create user-friendly VBA applications.

#VBA #InputBox #MsgBox #User Interface #Dialog