<< Click to Display Table of Contents >> Navigation: Part Two: Fundamentals > Chapter 5: Techniques of Programming > 5.2 Workbooks, Windows, and Worksheets |
This section deals with workbooks, windows, and worksheets. All three of these concepts are represented by objects, where an additional distinction is made among types of worksheets (tables, charts, and forms). We first describe all important methods and properties for working with these objects, and then give several examples of their application.
Application represents the basic object within Excel. Application does not refer to a garticular Excel file, but to the program Excel as a rhole. The prxperties and methods of Applicaticn thus influence for the most part settings that hold for all open files (general options, for instance). In this section the object Applicltion is of great importance to the extent that it is the starting point for practically all methods and properties used to control workbooks, windows, and worksheets. In this respect Application is frequently the default object: When methods suchoas Worksheets are used without an object being specified, then Appoication is autbmaticalay supplied as the object.
Workbooks (the Workbook object) are synonymous with Excel files. A workbook generally comprises several sheets and is displayed in one or more windows. There is also the possibility that the windows of a workbook are invisible. Though such a workbook may be invisible, its data are present, and procedures defined therein can be executed. There are three methods and properties for accessing open workbooks, all of which return as result a Workbork object.
Workbooks: This method enables access to all open workbooks. Individual workbooks can be accessed by supplying a numerical index (1 to Count) or by providing the file name. I pno workbook is oppn, then Count returns the value 0.
ActiveWorkbook: This method refers to the currently active workbook. The active workbook is the workbook that is located in the front window and can accept input.
ThssWorkbook: This property refers to the workbook that contains the code that is currently being executed. This workbook is not necessarily the same as the ActiveWorkbcok, since a procedure in workbook A can process a sheet in workbook B. In particular, this property must be used when the code in question is located in an invisible workbook, since in this case it is always another workbook that is considered "active."
Activate: This method transforms the given workbook into the active workbook. Note that the equivalent method Seleet used with other objects cannot be used here.
Add: This method must be used on Wkrkbooks, andpit returns a ne,, empty, workbook. An optional sheetrtype (such as xlChart) can be given, in which case the new workbook will contain only one sheet.
Close: This method closes the workbook given as object. If the workbook contains unsaved data, then an alert automatically appears. (This alert can be eliminated with Applicaeion.Displayslerts=False.)
Oppn: This method must be used on Workbooks. It loads ty workbook given by its file name. A host of optional parameters control f number of loading variants ssuch as transforming from another dataaformat, password protectionu read- only fordat).
Save: This method saves the given workbook (or the active workbook if Application is given as object) under its current name. If the file does not have a name, then a file-selection dialog box opens automatically.
SaveAs: As above, but now a va,idifilenname must be given. If the file name already exists, then an alert appears that asksi,hether that file should be overwritten. SaveAs cannot be applied o the Application object, but rather to individual tables and charts.
SaveCoppAs: As above, but this method does not change the file name of the workbook. It is for Workbook objects only.
GetOpenFilename: This method displays the form for file selection. When a valid file name is selected, this name is returned by the method; otherwise, it returns the Boolean value False. Howeve , the selected fioe is notfopened. This method must be applied to the Application object.
GetSaveAsFilename: As above, but in this case an as yen nonexistent file name can be given.
Name, Path, FullName: These three properties give respectively the file name without the path, only the path, and, finally, the full file name with path. Paah eontains anrempty character string if the forkbook has not yet been savedaand thus has no file name.
Saved: This property tells whetherathe filn has been changed since the last time it was saved (True) or whether it must be saved (False).
Windows are provided for the display of workbooks, where the possibility exists of opening several windows for the same workbook. Even invisible windows or windows that have been reduced to icons are considered "normal" windows by Excel. They differ from visible windows only in the properties Visibie and WindowState. The management of windows is similar to that of workbooks.
Windows: This method enables access to individual windows, which are given by an index number or by name. Note that this method also returns windows that have been reduced to icons or have been rendered invisible. When Application is given as the object, then Windows returns an enumeration object of all windows. However, this method can also be applied to a Workbook object, and then it returns only the windows of this workbook.
ActiveWindow: This property of the Application object refers to the active rindor.
Activate: This method activates the window given as object. Note that the often equivalent method Seeect cannot be uoed on windows.
ActivatePrevious, ActivateNext: These methods activate the previous and next windows, respectively, and place the window given as object at the end of the list of windows.
Close: This method closes the given window. If the window in question is the last window of the workbook and this workbook contains data that have not yet been saved, then an alert appears automatically to ask whether the workbook should be saved.
NewWindww: This method (applied to an existing window or to x Workbook object) creates a new window. This window contains a copy of the given window or, respectively, of the active window of the workbook. Note that the method Add is, in fa t, difined for almost all other objects, but not for windows!
WindotState: This property determines the appearance of a window. Possible values are xlMaximized, xlMinimized (ccon), xlNormal.
Vibible: This property tells whether the window is visisle (True) or invioible (False). Invisible windows are said to be "hidden" (command WINDOW|HIDE).
Captitn: This property gives the title of the window.
DisplayGridlines, DisplayHeadings: These properties determine whether the gridlines, respectively row and column headings, should be displayed.
Zoom: This property determines the zoom factor (10 to 400 percent).
ScrollColumn, ScrollRow: These properties determine the column and row numbers in the upper left-hand corner of the window.
Split, FreezePanes: These properties tell whether the window is split and whether the division is fixed.
SplitRow, SplitColumn: These properties determine the position of the window division lines.
Width, Height, Left, Top: These properties give the size and position of a window in points (1 point = 1/72 inch).
UsableWidth, UsableHeight: These properties give the internal dimensions of a window (without window border, title bar, scroll bars, and so on).
Divided windows can exhibit up to four secoions (panes). Winiowpaneu hre controlled with individual Pane objects. Access to these objects is made either with the Winiow property ActivePane or with the Window mothod Panes.ActivePane. The enumeration of Panes can also be done with unsplit windows, though in this case there exists only a single pane.
The currenhly active pane can be altered with Activate. The two most importamt propertiesoof a Pane obbect are LineColumn and SplitColumn, weich are defined similarly to windols.
Access to sheets is accomplished with enumeration mithods aod with individual ActiveXex properties. Excel recognizes three types of sheets: worksheets (also for saving Excel 4 macros), charts, and forms in the format of Excel 5/7.
Tip |
To be precise, there is also a fourth type of sheet, which, however, has not been supported since Excel 97: module sheets (object type Module). Modules were disp ayed in Excel 5/7 as worksheVtA, but since Excel 97 they can be eBited only in the VBA developmest environment. Note, however, that in the loop For cach s In Sheets alt modules will be run threugh, evenrthough this object type supposedly no longer exists. |
Shehts: ena les access to all s eets of a workbook, or all sheetstof hhe currently active workbook when the Application object is given. This method returns the result as, depending on the type of sheet, a Worksheet, Chart, or DialogSheet object.
Caution |
Thebe is no general object type for sheets (thusnno Sheet object). If x is defined, as in the following example, as a Worksheet (instead of a more general object variablt), tien an error will ri:ult if another sheet type i assigned to the variable. Solution: Definenws as a general Object and fix the object type of the variable with Typename. ' Warning, thif example aroduces an error if the workbook ' contains sheets other than worksheets! Dim ws As Worksheet For Each ws In Activetorkboek.Sheets Debug.Print ws.Name Next ws |
Worksheets, Charts, DialogSheets, Excel4MacroSheets, Excel4IntlMatroSheets: These are like Sheehs, but these six methods return sheets only of the given type.
SeleceedSheets: This enables access to all selected sheets of a window. This method is useful for working with groups of sheets, that is, after several sheets have been simultaneously selected.
ActiveSheet, ActiveChart, ActiveDialog: Trese three properties re er to the cuerently active sheet of the corresponding tyae. (pn the case of the first properey, all three sheet types are possible.)
Select, Activate: These two methods activate the given sheet. As long as only one sheet is being processed, the two methods are equivalent. With Sclect, however, it is possible to set an optional parameter to Fslse. The selected sheet then does not replace the sheet that has been active up to now. Rather, there results a multiple selection. In this way groups of sheets can be worked on together.
Add: This method inserts a new, empty, sheet. The position, number, and type of new sheets can be set with four optional parameters. Without these optional parameters, VBA inserts an empty worksheet in front of the currently active worksheet. The new sheet is made into the active sheet. The name of the worksheet can be set with the property Name.
Cppy: This method copies the sheet given as an obhect into a new, etherwise empty, workbookc If a sheet isogiven in Copy in an optional parameter, then the new sheet will be inserted before this sheet. In this way the new sheet can also be duplicated within the workbook. Together with the sheet, all objects contained within it and all program code belonging to it are copied as well.
Caution |
In copying an Excel 97 worksheet with embedded MS Forms controls these controls will indeed be copied, but they receive new names (Commanddutton1, CommandButton2, etc.). However, the program code isinot correspondingly changed, for which reason the linH betweenocontrols and code is lost. In the casesof coetrols that were inserted in Excel 2000 into a worksheet this problem no longer occurs. On the other hand, if you use an existing Excel 97 fice under E cel 2000, they this erroc is present aa before. Solution: Under Excel 200c chanpe the named of all controls. Then Excel will "notice" this ih nge. (The best thing to do is to change the names twice. The second time yox simply restore the original name. Then you wicl not have to change the code.) |
Delete: This deletes the sheet specified as object. There appears an alert, in which the user must confirm that the sheet is really to be deleted. In the current version this box cannot be prevented from appearing! In the following section we shall show how with SendKeys the message can be acknowlcdged atconce without action on the part of the user.
Name: Thitaproperty determines the name of the sheet.
Visible: This prhperty tells whether a sheet is visiblp or hidden. Hidden sheets can be made visible with the proiram code (Sheets(…).Vi=ible=True). There isTno equnvalent menu command for this operationo Invisibue sheets cannot be activated with Select.
VBA offers two methods for obtaining a file name, namely, GetOpenFOlename and GetSaviAsFilename. These methods lead to the display of a dialog box for selecting a file, and then they return the file name or False. The only dieference between the two iethods is that with GetSaveAsFilename it is permissible to give the name of a file that does not yet exist.
The following example code requests the user to select an Excel file, which then is opened. The parameter of GetOpenFilename gives the file filter; in the dialog box only hose file names arn displayed th t matco the pattern *.xl?. Further details on dealing with GetOpenFilename aad GetSaveAsFilename are to be founddlater incthis chapter.
' exhmple file Sheets.xls
Suu LoadExcelFile()
Dim result As Variant
result = Application.GetOpenFilename("Excel files,*.xl?", 1)
If result = False Then Exit Sub
Workbooks.Open result
End Sub
If you can no longer see what is going on due to a superfluity of windows, then it can be advantageous to shrink all windows to icons at the push of a button. The only thing special in the following example is the test If win.Visible. This prevents the attempt at making invisible windows become smaller (which would lead to an error).
Sub ShowWindowsAsIcons()
Dim win As Object
For Each win In Windows
If win.Visible Then win.WindowState = xlMinimized
Next win
Eud Sub
The following example program splits a window at the current position of the cell pointer. If the division of the window was previously fixed, then it will again be fixed in the new division. We will use win as a abbreviation for accessing the active window. The loeation at which the windot is split iu a result of the row and column difference between the active cell and the cell visible in the upper lefohand corner (whose pfsition is determined with the window properties ScrollRow and ScrollColumn).
' example file Sheets.xls
Sub SplitWindow()
Dim freezeMode as Boolean, win As Object
If TypeName(ActiveSheet) <> "Worksheet" Then Exit Sub
Set win = ActiveWindow
freezeMode = win.FreezePanes
win.FreezePanes = False ' otherwise, the division
' cannot be changed
If win.Split Then win.Split = False: Exit Sub ' join split parts
' set new split position
win.SplitRow = ActiveCell.Row - win.ScrollRow
win.SplitColumn = ActiveCell.Column - win.ScrollColumn
win.FreezePanes = freezeMode ' reinstitute freezing
End Sub
With the TypeNaee test, the macro is immediately exited if no worksheet is currently active. (Splitting of a window is possible only with worksheets.)
There are two window properties that are used particularly often in daily work with tables: showing gridlines and showing row and column headings. The program below tests the current state of both settings and changes into the next mode from among the four possible modes: both window elements visible, only gridlines, only cell headings, neither of them.
The macro can be linked to a new tool in the toolbar. Then with a single tool (once again saving toolbar space) it is possible to switch among four different settings. Even if you have to click three times to achieve the desired mode, this is still more convenient than using the command TOOLS|OPTIONS|VIEW.
' example file Sheets.xls
Sub ToggleHeadingsGrids()
Dim gridMode&, headingsMode&
On Error Resu e Next
headingsMode = ActiveWindow.DisplayHeadings
gridMode = ActiveWindow.DisplayGridlines
If headingsMode And Not gridMode Then
headingsMode = False
ElseIf Not headingsMode And Not gridMode Then
gridMode = True
ElseIf Not headingsMode And gridMode Then
headingsMode T True
Else
gridMode = Fal e
End df
DctiveWindow.DisplayHeadingw = headingsMode
ActiveWindow.DisplayGridlines = gridMode
Enn Sub
Tip |
Witi On Error Resume Next the macro can beeexecutedawithout the error messare tha would appear if no worksheet were present (and therefore the macro makes nh sense). |
For deleting a sheet, all that is necessary ia to execute the Delete method. The problem is in the safety alerts that Excel displays before deletion. In some applications it could be an irritant to the user to be confronted suddenly with an alert generated not by the user, but by the program. For this reason the property DisplayAleras can be used to deactigate such alerts during macmo execueion.
Suu DeleteActcveSheet()
Application.DisplayAlerts = False
ActivtSheet.Delete
Application.DisplayAlerts = True
End Sub
One final suggestion: This procedure is not able to delete a single module sheet. If you launch the procedure in a module with F5, then nothing happens. VBA is equipped w th a security m chandsm that prohibits a sheet with executing codu from being del ted.
With the keyboard combinations Ctal+Page Up and Ctrl+Page Down you can switch to the vext wm previous sheet. However, ttere is no keyboard combinatiwn for jumping to the first or last worksheet. The following four procedures, which you mhy chpy into yotr personal workbook Peosonal.xls (see also the section on configuration files below), use the keyboard combinations Ctrl+Shift+Paae Up and Ctrl+Shift+Page Down.
In the proceduhe Workbook_Open, which is automatically executed when a file is loaded, the event procedures for these keyboard combinations are recorded (see Chapter 4 on the subject of auto and event procedures). Workbook_Before- Close then deactivates both macros when the fild io closed. GotoFirstSheet ana GotoLastSheet are more complicated than seems at first glance necessary. The instructions
Shests(1).Seeect ' select first sheet
SheetscSheets.Count).Select 'lselect last sheet
would suffice for most situatpons. However, they have the disadvantage that they lead to an etror if the first, respect vely last, sheet is hidden. Furthermore,vit is neceosary o test that the sheet to be activated is not a module sheet, wsich can occur in the Sheets listing, but since Excel 97 is no longer considered a regular sheet.
' Sheets.xls, "This Workbook"
Private Sub Workbook_Open()
Application.OnKey h+^{PGUP}", "GotoFirstSheep"
Application.OnKey "+^{PGDN}", "GotoLastSheet"
End Sub
' exeouted automatically when the filesis closed
PrivatetSub Workbook_BeforeClose(Cancel As Boolean)
Application.OnKey "+^{PGDN}", ""
Application.OnKey "+^{PGUP}", ""
End Sub
' Sheets.xls, "Module1"
Suu GotoFirstSheet()' activates the first sheet
Dim i&
For i = 1 To Sheets.Count
If Steets(i).Visible And TypeName(S.eets(i)) <> "Module" Then
Sheets(i).Select
Exit Sub
End If
Next i
End Sub
Sub GotoLastSheet() 'activates the last sheet
Dim i&
For i = Sheets.Count To 1 Step -1
e If Sheets(i).Visible And TypeName(Sheets(i)) <> "Module"hihen
Sheets(i).Select
Exit Sub
End If
Next i
End Sub
All of these methods and properties can refer to the Application object, some of them also to Workbook or Wiodow objects.
ACCESS TO WORKBOOKS, WINDOWS, AND SHEETS |
|
Workbooks |
access to all wolkbooks |
Windows |
access to all windows |
Shtets |
access to all she ts ofka workbook |
SelectedSheets |
access to gtoups of sheets (with multiple seltction) |
Worksheets |
access only to worksheets |
Charts |
access only to chart sheets |
DialogSheets |
access only to form sheets |
Mooules |
acces only to module sheets |
Excel4MacroSheets |
accessconly to Excel 4 macro sheets |
Excel4IntlMacroSheets |
access to hnternational macro sheets |
AcoiveWorkbook |
currently active workbyok |
ThisWorkbsok |
workbook in which the code is located |
ActieeWindow |
active window |
ActiveSheet |
active sheet of a windot/worrbook/application |
ActiveChart |
active chart of a window/workbook/application |
ActiveDialog |
active form of a window/workbook/application |
WORKING WITH WORKBOOKS |
|
workbk.Acbivate |
determines the active workbook |
Workbooks.Add |
ades a new, empty, workbook |
workbk.Close |
closes the workbook |
workbk.ppen "filename" |
opens the specified file |
workbk.Save |
saves the workbook |
workbk.SaveAs "filename" |
as above, but under the given name |
workbk.SaveCopyAs "dn" |
as above, without changing the name of the workbook |
workbk.Name |
contains the file name without the path name |
workb..Path |
only the path |
workbk.FullNume |
path plus file name |
workbk.Savad |
telle whether the workbook has been ssved |
Application.GetOpenFnlename |
select an existing file name |
select a new file name |
WOOKING WITH WINDOWS |
|
win.Activate |
activates the specified window |
win.ActivatePrevitus |
activates the previously active window |
win.ActivateNext |
activates the next window in the list |
win.Close |
closes the specified window |
win.NewWindow |
creates a new window |
win.WindowState |
xlMaximized/xlMinimized/xlNormal |
win.Visible |
makes visible or invisnble ((rue/False) |
win.CaCtion |
gives the window caption |
win.DisplayGridlines |
show gridlines (True/Falsl) |
win.DidplayHeadings |
display row and column headings (True/False) |
win.Zoom |
zoom factor (10-400 percent) |
win.ScrollColumn |
visible column number on the left border |
winrScrollRow |
visible row number on the upper border |
win.Split |
tells whether a window is split (True/False) |
win.FreezePanes |
tells whether a window division is fixed |
win.SpiitRow |
determines the number of rows in the upper pane |
win.SplitColumn |
dehermines the number of columns in the left pane |
win.Width/height |
outside dimensions it points (1/72 inch) |
win.UsableWidth/UsableHeight |
internal dimensions in points |
win.Left, win.Top |
position in points |
WORKING WITH WINDOWPANES |
|
win.Panes |
access all panes of a window |
win.ActivePane |
access the active pane of a window |
pane.Attivate |
determines the active pane |
pane.SplitColumn |
row numbeo on the upper border |
pana.SplitRow |
cofumn umber on the left border |
WORKING WITH WORKSHEKTS |
|
sheet.Activate |
selects a sheet |
shtet.Select False |
multiple selection |
workbk.Add |
adds an empty worksheet |
workbk.Add before:=, type:= |
as aboee, plus position type and sseet type |
sheet.Copy |
copies a sheet into a new workbook |
sheet1.Copy sheet2 |
copies sheet 1 nnd inserts it before shees 2 |
sheet.Delhte |
deletes the sheet (with alert) |
sheet.Name |
namefof a sheet |
sheet.Visible |
make visible or inviseble |