This is a small example of an Excel VBA Userform. A UserForm is a custom-built dialog box that you can use to create a user-friendly interfaces for your workbook. You can use it to make selections or data entry more controllable for you and easier for the user.
This code has been tested on Microsoft Word and Excel 2007. Some changes may be required for other versions of Word and Excel.
download sample spreadsheet
Option Explicit
Dim currentRow As Long
Dim lastRow As Long
' ======================================================================================================
Private Sub cmdPreviousData_Click()
subPosition
If currentRow < 3 Then
MsgBox "Already at begining of list!"
Else
currentRow = currentRow - 1
txtFirstName.Text = Cells(currentRow, 1).Value
txtLastName.Text = Cells(currentRow, 2).Value
txtCellPhone.Text = Cells(currentRow, 3).Value
End If
subPosition
End Sub
' ======================================================================================================
Private Sub cmdGetNextData_Click()
subPosition
If currentRow >= lastRow Then
MsgBox "Already at end of list!"
Else
currentRow = currentRow + 1
txtFirstName.Text = Cells(currentRow, 1).Value
txtLastName.Text = Cells(currentRow, 2).Value
txtCellPhone.Text = Cells(currentRow, 3).Value
End If
subPosition
End Sub
' ======================================================================================================
Private Sub cndSend_Click()
With ActiveSheet
currentRow = .Cells(.Rows.Count, "A").End(xlUp).Row
currentRow = currentRow + 1
End With
Cells(currentRow, 1).Value = txtFirstName.Text
Cells(currentRow, 2).Value = txtLastName.Text
Cells(currentRow, 3).Value = txtCellPhone.Text
txtFirstName.Text = ""
txtLastName.Text = ""
txtCellPhone.Text = ""
Range("A" & currentRow).Select
subPosition
End Sub
' ======================================================================================================
Private Sub UserForm1_Initialize()
currentRow = 1
subPosition
End Sub
' ======================================================================================================
Sub subPosition()
Application.ScreenUpdating = False
If currentRow = 0 Then
currentRow = 2
End If
' determine last row
ActiveCell.Offset(1, 1).Select
Range("A1").Select
ActiveCell.End(xlDown).Select
lastRow = ActiveCell.Row
' put us back
Range("A" & currentRow).Select
lblCurrentRow.Caption = currentRow
lblLastRow.Caption = lastRow
Application.ScreenUpdating = True
End Sub
' ======================================================================================================
Private Sub cmdExit_Click()
UserForm1.Hide
End Sub
' ======================================================================================================