Home > Excel > VBA > VBA and Multiple Sheets
Google
Web This Site

Using VBA to Work with Multiple Sheets Simultaneously

There are several instances where one may want to carry out some action on multiple sheets at the same time.  This might include printing them or copying them to another location or even editing data in multiple sheets in one step.  In some instances operating on on one sheet at a time will yield a different result than working on multiple sheets at the same time.  In other cases, it might just be a convenience.

Two examples where the results are different are:

When one copies a chart sheet and its associated datasheets in one operation to another workbook the chart references are updated to refer to the datasheets in the new workbook.  However, if these sheets are copied individually, the chart would still refer to the sheets in the old workbook.

Another example is how one prints multiple sheets.  Print them in one step and the pages are numbered sequentially.  Do it one sheet at a time and the pages are numbered separately.  Additionally, each sheet will also be a separate print job.  While some may not consider than as a big issue, for others it can be.

In this tip we look at how to work with multiple sheets through VBA code.  The rest of the section is organized as follows:

Using the macro recorder
Selecting multiple sheets
Working without selecting the sheets
Working with sheets identified only at runtime
When selecting and activating objects is unavoidable
An important warning
 

Recent Comments

Excel User on May 25, 2011:

Very useful info.

   Sub crashExcel()
     Dim x()
     Sheets(x).Copy
     End Sub

   In Excel 2007 this no longer crashes the program, error 13 pops up instead.

Using the macro recorder

Starting with our trusted friend, the macro recorder, the code we get for printing two sheets is

    Sheets(Array("Sheet2", "Chart1")).Select
    Sheets("Sheet2").Activate
    Application.ActivePrinter = "Acrobat Distiller on Ne06:"
    ActiveWindow.SelectedSheets.PrintOut Copies:=1, ActivePrinter:= _
        "Acrobat Distiller on Ne06:", Collate:=True

Note that the code essentially uses an array as an index for the Sheets collection instead of the more typical Sheets(1) or Sheets("Sheet1") syntax.  That essentially is the key to operating on multiple sheets at the same time.

Selecting multiple sheets

We will see an example of how to construct an array with elements identified only at run time.  But, first we look at code that uses the Select statement in a way that is rarely seen.  Did you know that the Select method has an optional parameter?  Check Excel VBA help and you will find the syntax is

Select method as it applies to the Chart, Charts, Shape, ShapeRange,
    Sheets, Worksheet, and Worksheets objects.

Selects the object.

expression.Select(Replace)

expression    Required. An expression that returns one of the above objects.

Replace   Optional Variant. The object to replace.

By setting the Replace argument to False one can add to the existing selection!  The code sample below selects both the datasheet Sheet2 and the chart sheet Chart1 and copies them to a new workbook.

Sheets("Sheet2").Select
Sheets("Chart1").Select False
ActiveWindow.SelectedSheets.Copy
 

As has been noted elsewhere, selecting and activating objects is a step of last resort.  Whenever possible, it is preferred that one work without selecting and activating sheets.  We will see how to do that next.

Working without selecting the sheets

Next, we convert our above code sample to use an array.  Since this will be a building block for the next case where the names are not known in advance, we will use an array data structure.

Option Explicit
Option Base 0
Sub testDynamicSheetArray()
    Dim x(1)
    x(0) = "Sheet2": x(1) = "Chart1"
    Sheets(x).Copy
    End Sub

Finally, we need to figure out a way to work with sheets whose names we don't know up front.  In fact, we might not even know how many sheets we want to work with.

Working with sheets identified only at runtime

Next, we look at how we can operate on sheets without knowing their names up front.  Suppose we want to copy to a new workbook all the sheets in the active workbook that have a left parenthesis in their respective names.  The code below uses an array to store the names of interest and then it carries out the copy in one step.

The handling of the array SheetsFound probably deserves some clarification.  Except at the very end, it is always one larger than the amount of valid data in it.  Before the first iteration of the For Each aSheet loop it has one element (index zero) that contains nothing.  Whenever a sheet of interest is found, its name is entered in the empty element and the array is resized to be one larger.  That means that once again the array has one element that is empty.  Hence, when all iterations of the loop are complete, the array will still have one element too many.  Consequently, the final ReDim trims the array by one.

Option Explicit
Option Base 0
Sub testDynamicSheetCopy()
    Dim aSheet As Object, SheetsFound()
    ReDim SheetsFound(0)
    For Each aSheet In ActiveWorkbook.Sheets
        If InStr(1, aSheet.Name, "(") > 0 Then
            SheetsFound(UBound(SheetsFound)) = aSheet.Name
            ReDim Preserve SheetsFound(UBound(SheetsFound) + 1)
            End If
        Next aSheet
    ReDim Preserve SheetsFound(UBound(SheetsFound) - 1)
    Sheets(SheetsFound).Copy
    End Sub

When selecting and activating objects is unavoidable

One of the features that Microsoft added to Excel is this ability to edit multiple worksheets simultaneously.  Using the categories mentioned in the introduction, this capability falls under the "convenience" category rather than one where behavior is altered.

Together with what Microsoft calls 3D formulas, this capability is something that doesn't naturally fit in with the Excel object model.  Consequently, Microsoft made some compromises within the model.  The standard object model gets sidestepped in these cases and we are forced to use the selection and the activecell objects.

The code that the macro recorder generates to work on Sheet1 and Sheet2 simultaneously is shown below.  The first sample creates the sheet group and changes just one cell (A1).  The second code sample changes a group of cells (A2:B3).

    Sheets(Array("Sheet2", "Sheet1")).Select
    Sheets("Sheet2").Activate
    Range("A1").Select
    ActiveCell.FormulaR1C1 = "14"
    Range("A2:B3").Select
    Selection.FormulaR1C1 = "16"

Essentially, if we were to try and do this through code, we would have to select the specific cell in one of the selected sheets and then work with the Selection object.

Sub testDynamicSheetEdit()
    Dim aSheet As Object, SheetsFound()
    ReDim SheetsFound(0)
    For Each aSheet In ActiveWorkbook.Sheets
        If InStr(1, aSheet.Name, "(") > 0 Then
            SheetsFound(UBound(SheetsFound)) = aSheet.Name
            ReDim Preserve SheetsFound(UBound(SheetsFound) + 1)
            End If
        Next aSheet
    ReDim Preserve SheetsFound(UBound(SheetsFound) - 1)
    Sheets(SheetsFound).Select
    Sheets(SheetsFound(0)).Activate
    Range("A2:B3").Select
    Selection.FormulaR1C1 = "22"
    End Sub

There doesn't appear to be anyway to avoid the activation and selection.  For example, the following code segment generates the runtime error "Object does not support this property or method."

    Sheets(SheetsFound).Range("a2:b3").Value = "24"

The following, on the other hand, only changes the sheet identified in SheetsFound(0)

    Sheets(SheetsFound).Select
    Sheets(SheetsFound(0)).Range("a2:b3").Value = "24"

An important warning

In several of the above examples, we used the construct Sheets( {some array} ).  It is important to note that if the array were never initialized, Excel/VBA will not gracefully handle what is clearly an error.  Instead Excel will crash!  The trivial example below is one such instance.

Sub crashExcel()
    Dim x()
    Sheets(x).Copy
    End Sub