WORKBOOKS AND SHEETS IN VBA

Table of Contents

INTRODUCTION

In this article, we’ll see some additional functions available for WORKBOOKS AND SHEETS in VBA.

Let us understand the terms first.

WORKBOOK:

An Excel’s complete independent file is known as a workbook. The file which is saved in the computer is workbook.
A workbook can have at least one sheet and maximum a big number of sheets in a single workbook.( Subject to the availability of memory)

SHEET:Sheet is a standalone working documents having cells in it, where we work. There can be many sheets in a workbook.

The sheets can have connected. Every Sheet can have a different kinds of data within itself.


Let us see some of the basic functions which we can exploit using VBA to make our work easier.


ACTIVATING A WORKBOOK IN VBA

Activating a workbook means making it active and making it ready to work. It is possible that many workbooks are opened at the same time and we need the VBA to work on the different workbooks.

Now if, a situation occurs, when we need to change the focus on the other workbook, we can use this  

WORKBOOKS(INDEX).ACTIVATE

OR

WORKBOOKS(“WORKBOOK NAME”).ACTIVATE

*INDEX IS GIVEN AS PER THE OPENING EVENT OF THE WORKBOOK. I.E. THE FIRST OPENED WORKBOOK WILL HAVE INDEX 1 AFTER THAT 2,3,…. AND SO ON.

IT’S ALWAYS BETTER TO GO WITH THE NAME.

SAVING THE WORKBOOK

After the job is completed, we can automate it to save itself.

The workbooks can be saved through a routine in VBA.

First of all, let us save all the workbooks, which are already saved and are not new. It’ll simply save the workbooks.

'gyankosh.net
'saving a workbook

Public Sub SaveWorkbooks()

Dim ABC As Workbook

For Each ABC In Workbooks

If ABC.Path <> "" Then ABC.Save

MsgBox(ABC.path)

Next ABC

End Sub

PATH PROPERTY– The path property of the workbook contains its saved path.

The above code declares a workbook as ABC.

Workbooks object contains all the opened workbooks.

So we start a loop and check the workbooks one by one, if the path of any workbook is not empty, then just save it using the method, ABC.SAVE

Just for information, we put another line in the message box.

SAVING THE NEW WORKBOOK USING VBA IN EXCEL

In the previous workbooks, we saved the workbooks which were not new, or the workbooks which were already saved with a name and the current saving process was for the updates we made in the workbooks.

Now let us see how to save a new workbook in Excel using VBA.

'gyankosh.net
'saving a workbook


Public Sub SaveWorkbooks()

Dim ABC As Workbook

For Each ABC In Workbooks

If ABC.Path <> "" Then

ABC.Save

Else

Do

fName = Application.GetSaveAsFilename

Loop Until fName <> False

ActiveWorkbook.SaveAs Filename:=fName

End If

Next ABC

End Sub

The above-mentioned program is the advanced version of the previous one.

In this program, we start by declaring a WORKBOOK variable.

The loop is started for the ABC variable till all the workbooks are visited. The loop starts and checks all the opened workbooks one by one.

First of all the loop checks if the FILE IS ALREADY SAVED by checking its PATH property, if it is not going to be saved for the first time, it’ll be saved.

If the file is to be saved for the first time, it’ll go to a DO LOOP and get the file name by opening a SAVE AS dialog box.

After putting the name in the save as dialog box, the name is passed and the workbook is saved as the given filename.

The DO loop is closed and FOR loop is also closed.

SAVING AND CLOSING ALL THE WORKBOOKS USING VBA IN EXCEL

After the job is done, we have to close the workbooks.

So, we can use VBA to make a routine that will save all the opened workbooks and close them after saving.

It is a very safe practice to save your work before closing the workbook. Let us try to build one.


'gyankosh.net
'closing all workbooks after saving them

Sub closeallworkbooks()

    Dim ABC As Workbook

       For Each ABC In Workbooks

         If ABC.Name <> ThisWorkbook.Name Then

         ABC.Close savechanges:=True

         End If

        Next ABC

     ThisWorkbook.Close savechanges:=True

End Sub


We declare a variable ABC as a workbook.

The For loop starts to check every workbook.

If the Workbook is not the same as the one which contains the code , then the workbook is closed with save changes as true which means, that the workbook will save all data before the closing.

After closing all the workbooks,

We’ll close the workbook containing the code by

THISWORKBOOK.Close

method.

We close the code containing the workbook in the last because otherwise, all the workbooks may or may not be closed.



ACTIVATING A WORKSHEET USING VBA IN EXCEL

While working in a workbook, we use many different sheets, but whenever using VBA, we always need to activate the sheet and get the worksheet in focus. So there is a need to have a function with the use of which , we can use another sheet whenever we need. Here is the format of activating a Sheet.

SHEETS(INDEX).ACTIVATE

OR

SHEETS(“SHEET NAME”).ACTIVATE

*INDEX IS GIVEN AS PER THE OPENING EVENT OF THE SHEET. I.E. THE FIRST OPENED SHEET WILL HAVE INDEX 1 AFTER THAT 2,3,…. AND SO ON.

IT’S ALWAYS BETTER TO GO WITH THE NAME.

INSERTING THE SHEETS USING VBA IN EXCEL

We use many sheets to segregate the data of different types in the Workbook. We can use many sheets in the workbook as per the availability of the memory.

Let us try a routine to insert the sheets at a specific position in the Workbook.

ADDING A SHEET USING VBA IN EXCEL

'gyankosh.net
'Adding a new sheet

Sub addnewSheet()

Dim newsheet As Worksheet 'Declaring a worksheet variable

Set newsheet = Sheets.Add(Type:=xlWorksheet) 'Adding a new worksheet

Sheets(Sheets.Count).Name = "gyankosh" 'Naming the worksheet

Sheets("gyankosh").Activate 'Bringing the focus to the Sheet

End Sub

We start by declaring a variable of WORKSHEET.


The new worksheet is set by adding a worksheet to the SHEET object with the method SHEETS.

ADDThe type has been specified as xlWorkSheet.

After successfully adding a sheet,  we try to name the sheet.

So we use the method in the SHEETS object.Sheets(index of the Sheets given by Sheets.count which will give a total number of sheets).

Name =”gyankosh or any name you like”.

This is the way to name a sheet in VBA. After naming, remember that the sheet will be added but it won’t be focused, i.e. it won’t be open for work.

SO if we want to activate it too, use the method sheets(“name of the sheet”.Activate

ADDING A SHEET AT A SPECIFIC LOCATION USING VBA IN EXCEL

This section deals with the procedure of adding a new Sheet after a specific Sheet in a workbook.

In the last section, we just added a worksheet to the current Workbook without specifying its location.

So it’ll be added in a sequence whatever index is to be assigned.

Now let us try to learn how we can add a sheet to a specified number. Suppose there are three sheets in the workbook.

We’ll add a sheet at number 2.

'gyankosh.net
'Adding a new sheet at position 2.

Sub addnewSheetataposition()

Dim newsheet As Worksheet 'Declaring a worksheet variable

Set newsheet = Sheets.Add(Type:=xlWorksheet, after:=Sheets(1)) 'Adding a new worksheet after (Sheet(1))

Sheets(2).Name = "kyc" 'Naming the worksheet Sheets(2) is the new added Sheet

Sheets("kyc").Activate 'Bringing the focus to the Sheet

End Sub

We start by declaring a variable of WORKSHEET.

The new worksheet is set by adding a worksheet to the SHEET object with the method SHEETS.ADD.

Here we add one more property after:=position to specify at which position the Sheet should be inserted.

The type has been specified as xlWorkSheet.

After successfully adding a sheet,  we try to name the sheet. So we use the method in the SHEETS object.

Sheets(index of the Sheets given by Sheets.count which will give a total number of sheets).

Name =”kyc” or any name you like.

This is the way to name a sheet in VBA.

After naming, remember that the sheet will be added but it won’t be focused, i.e. it won’t be open for work.

So if we want to activate it too, use the method Sheets(“kyc”).Activate

MOVING THE SHEETS USING VBA IN EXCEL

After inserting the Sheets, it’s now the turn to learn how to move the sheet at a specific position. Like inserting the sheets, it is easy too.  

MOVING A SHEET -AFTER A SPECIFIC SHEET USING VBA IN EXCEL

'gyankosh.net
'Move a sheet at a specific position.
Sub movesheets()

Worksheets("kyc").Move after:=Worksheets(1) 'Moving a sheet at position 2.

End Sub

We start the code by declaring the subprocedure.

There is already a sheet named KYC.

We use the method Worksheets(“kyc”) which refers to kyc sheet  and use the MOVE method to move this sheet.

Using a space and now telling the location by using after:=Worksheets(1) which means that worksheet is to be moved after the Worksheets with the index 1.

Kindly try the same with the property BEFORE.

MOVING A SHEET-BEFORE A SPECIFIC SHEET USING VBA IN EXCEL

We just learned about shifting the sheet after any specific sheet. Now let us try the opposite. Shifting the sheet before a specified sheet.

'gyankosh.net
'Move a sheet at a specific position.

 Sub movesheetsbefore()

    Worksheets("kyc").Move before:=Worksheets(1) 'Moving a sheet at position 2.

 End Sub

The only difference between moving a sheet before and after is in the property used.

For, before, we use the word before. The notation goes like this

Worksheets(“Name of the sheet to be moved”).move before:=Worksheets(index)

ADDING A SHEET BEFORE A SPECIFIC SHEET

This section deals with the procedure of adding a new Sheet BEFORE a specific Sheet in a workbook.

In the last section, we added a sheet after a specified sheet. Now let us try to add a sheet before a specified sheet. Here is the code for doing the action.

'gyankosh.net
'Adding a new sheet at position before kyc.

Sub addnewSheetataposition1()

Dim newsheet As Worksheet 'Declaring a worksheet variable

Set newsheet = Sheets.Add(Type:=xlWorksheet, before:=Sheets("kyc"))
'Adding a new worksheet before "kyc"

newsheet.Name = "bhalu"

'Naming the worksheet Sheets(2) is the new added Sheet

Sheets("bhalu").Activate 'Bringing the focus to the Sheet

End Sub


We start by declaring a variable of WORKSHEET.

The new worksheet is set by adding a worksheet to the SHEET object with the method SHEETS.ADD.

Here we add one more property before:=position (which is given by Sheets(“name of sheet”)) to specify at which position the Sheet should be inserted.

The type has been specified as xlWorkSheet.

After successfully adding a sheet,  we try to name the sheet.

So we use the method in SHEETS object.

We used directly the Worksheet to name it by the use of property NAME. After naming, remember that the sheet will be added but it won’t be focused, i.e. it won’t be open for work.

So if we want to activate it too, use the method Sheets(“bhalu”).Activate