Worksheet object (Excel)

Represents a worksheet.

Remarks

The Worksheet object is a member of the Worksheets collection. The Worksheets collection contains all the Worksheet objects in a workbook.

The Worksheet object is also a member of the Sheets collection. The Sheets collection contains all the sheets in the workbook (both chart sheets and worksheets).

Example

Use Worksheets (index), where index is the worksheet index number or name, to return a single Worksheet object. The following example hides worksheet one in the active workbook.

Worksheets(1).Visible = False

The worksheet index number denotes the position of the worksheet on the workbook's tab bar. Worksheets(1) is the first (leftmost) worksheet in the workbook, and Worksheets(Worksheets.Count) is the last one. All worksheets are included in the index count, even if they are hidden.

The worksheet name is shown on the tab for the worksheet. Use the Name property to set or return the worksheet name. The following example protects the scenarios on Sheet1.

 
Dim strPassword As String 
strPassword = InputBox ("Enter the password for the worksheet") 
Worksheets("Sheet1").Protect password:=strPassword, scenarios:=True

When a worksheet is the active sheet, you can use the ActiveSheet property to refer to it. The following example uses the Activate method to activate Sheet1, sets the page orientation to landscape mode, and then prints the worksheet.

Worksheets("Sheet1").Activate 
ActiveSheet.PageSetup.Orientation = xlLandscape 
ActiveSheet.PrintOut

This example uses the BeforeDoubleClick event to open a specified set of files in Notepad. To use this example, your worksheet must contain the following data:

  • Cell A1 must contain the names of the files to open, each separated by a comma and a space.
  • Cell D1 must contain the path to where the Notepad files are located.
  • Cell D2 must contain the path to where the Notepad program is located.
  • Cell D3 must contain the file extension, without the period, for the Notepad files (txt).

When you double-click cell A1, the files specified in cell A1 are opened in Notepad.

Private Sub Worksheet_BeforeDoubleClick(ByVal Target As Range, Cancel As Boolean)
   'Define your variables.
   Dim sFile As String, sPath As String, sTxt As String, sExe As String, sSfx As String
   
   'If you did not double-click on A1, then exit the function.
   If Target.Address <> "$A$1" Then Exit Sub
   
   'If you did double-click on A1, then override the default double-click behavior with this function.
   Cancel = True
   
   'Set the path to the files, the path to Notepad, the file extension of the files, and the names of the files,
   'based on the information on the worksheet.
   sPath = Range("D1").Value
   sExe = Range("D2").Value
   sSfx = Range("D3").Value
   sFile = Range("A1").Value
   
   'Remove the spaces between the file names.
   sFile = WorksheetFunction.Substitute(sFile, " ", "")
   
   'Go through each file in the list (separated by commas) and
   'create the path, call the executable, and move on to the next comma.
   Do While InStr(sFile, ",")
      sTxt = sPath & "\" & Left(sFile, InStr(sFile, ",") - 1) & "." & sSfx
      If Dir(sTxt) <> "" Then Shell sExe & " " & sTxt, vbNormalFocus
      sFile = Right(sFile, Len(sFile) - InStr(sFile, ","))
   Loop
   
   'Finish off the last file name in the list
   sTxt = sPath & "\" & sFile & "." & sSfx
   If Dir(sTxt) <> "" Then Shell sExe & " " & sTxt, vbNormalNoFocus
End Sub

Events

Methods

Properties

See also

Support and feedback

Have questions or feedback about Office VBA or this documentation? Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.