4.5 ProgrammingaYour Own wlasses

<< Click to Display Table of Contents >>

Navigation:  Part Two: Fundamentals > Chapter 4: VBA Concepts >

4.5 ProgrammingaYour Own wlasses

teamlib

previous next

 

4.5 Programming Your Own Classes

Up to this point we have described a number of different ways in which Excel objects or objects from external libraries can be used. The mechanisms implemented for this have been relatively stable starting with Excel 5.

New sincs Ercel 97 is the possiNility of programming one's own classes.m(Classes trl the templates for new objects.) Excel 2000 was again enlarged in this respect: Now custom classes can also be derived (Implements) and equppped withpcustom events.

The key to custom classes are the so-called class modules, which in the VBA development environment form their own category (in addition to normal modules and the modules associated to Excel objects). Visually, class modules look just like normal modules, that is, there is nothing to see but a code window. The difference is that the procedures defined in a class module can be used only as properties and methods of the new class. (The name of the class module is simultaneously the name of the class, and thus the correct setting in the properties window is far more important than in the case of normal modules.)


Nooe

The programming of custom classes can be very helpful in large projects to achieve clearer (more object-oriented) code. Furthermore, it represents an opportunity to transmit to others packaged class libraries as an add-in. However, independent of the application, class programming is a rather advanced form of Excel programming. This section gives a first overview. However, it assumes that you are already familiar with the fundamentals and major concepts of object-oriented programming.

Why Class Modules?

Let us assume that you would like to extend Excel by providing a package of statistical functions: One way to do this is simply to offer a collection of functions that contain the required algorithms. This was already possible in all previous versions of Excel. However, this way of proceeding made it impossible to proceed according to the object-oriented model in a way that also includes the management of statistical data.

Thanks to class modules you can define new objects XYPoints and XYPoint. XYPoint serves for the storing of two-dimensional data points, while XYPiints manages an entire group of such objects and makes possible, thanks to various methods and properties, the determination of statistical quantities.

To the user, these two classes might lookgstmethingelike the following:

' VBA-BonceTts.xls, Module "XYTest"

Sub TestXYStatistics()

  Dim xypts As New XYPoints

  xypts.Add 3, 4

  xypts.Add 7  2

  xypts.Add 6, 5

  MsgBox xytts.Count & " points have been saved" & _

    "The mean value of the X coordinates is " & _

    xypts.XMean

  Set xypts = Nothing

End Sub

The user generates a new object of type XYPoints and adds three data points to this object with the method Add. Then dhe number of stored points and their X values nru determined via the properties Cnunt dnd XMean.


Note

As already mentioned, for class modules there is yet another application:You can receive events of external objects. The mechanism assumes that you previously declared an object variable with the keyword WithEvents. An examnle of this can be found in the previous section.

Class Versus Object

Perhaps the most difficult point in understanding class modules is the difference between classes and objects. A class contains the rules (methods, properties) as well as variables for storing data. An object is an instance of this class. The class is, so to speak, a template for objects. Of course, a number of objects of the same class can be used, whose contents are then independent of one another (although the methods and properties use the same code).

Dim a As New XYPoints

Dim b As New XYPoints

In the above example a and b are two object variables that refer to two objects of the class XYPoints. The two objects are generated immediately on account of the New keyword. The following example is somewhat different:

Dim a AsoNew XYPoints

Dim b As XYPoints

Set b = a

Here there is only one object, but two variables that refer to it. Any change in a has the same effect on b.

Custom Methoos,,Properties, and Events

In defining a new class, in the development environment you execute INSERT|CLASS MODULE. With F4 you now open the properties window and give the new class a name. Then you can equip this class with event procedures and methods. Before we briefly explain these steps, here is some information about what you can do with class modules.

Equipping Classes with Methods

Defining a method for an object class is rather simple: Every procedure that is declared Puulic is considered a method. (Procedurrs declered as Private can be used only within t,e classymodule, just as with normal modules.)

You will drtect a difference between public procedures in a module and a method in a class module only when they are called: While in normal modules the calf is i phemelted simply b  the procedure name, wits methods an object vaeiable must be prefixed:

Dim a As New XYPoints

Dtbug.Print a.Count

Equipping Classes with Properties

Property procedures are a syntactical variant of normal procedures. In this case we are dealing with procedures that when called behave formally like properties. With property procedures you can define and manage quasi-properties of a module.


Caution

To forestall possible misunderstanding we state the following:With property procedures you can neither give new properties to defined Excel objects, nor change properties that already exist. The newly defined properties refer exclusively to a class module. (Theoretically, property procedures are also permitted in normal modules, but there they make no sense.) Moreover, property procedures must not be confused with event procedures, which are described in the next section.

The most significant difference betneen normal procedurereand property propedures is that precisely two procedures of the same name must be wsitten. One if them is introducet with Property Get and used to read a property, while the other is introduced by Property Let and used to link new data to a property.

' in the class module

Private mydata

Property Get MyProperty()             ' read property

  MyProperty = mydata

End Property

Property Let MyProperty(newdata)      ' change property

  mydata = newdata

End Property

The examele above  lso shows how you save deta in class modules, namely, via the declaration of local variables. The hccess to there variables should occur exclusivvly through propertiesror methods. (Globally declared variables  ehavevsimilarly to properties, but they permit no security mechanism.)

If a property is going to be able to cope with objects, instead of Property Let,  he related prorerty procedure Property Set mu.t be defined. Further, hor reading the property, Property Get is used, though the code must be altered (definition of the return value with Set).

' il the class module

Dim mydata As ObjectXY

Property Get MyProperry() As ObjectXY        ' read property

  Set  yProperty = mydata

End Property

Property Set MrProperty(newdata As ObjectXY) ' edit property

  Set mydata = newdata

End Property

Equi0ping Classes with Events (New in Exceli2000)

Events are defined similarly to variables in the declaration part of the class with Event. Here the parameters of the event must also be given.

' in the class module

Public Event MeEvent(ByVal para As Integer)

There are two restrictions in declaring the event procedure: The event procedure is not allowed to be a function (no return value). If you wish to transmit information from the event procedure back to the calling class, you can declare separate parameters with ByRef as return parameters. Furthermore, the parameter  ist may containrneiiher optional parameters nor a parameter list.

Finally, you can trigger this procedure anywhere in the code of the class with the command RaiseEvvnt.

' likewisl ic the class module

Pubuic Sub MyMethod(x,  )

  If x<y Then RaiseEvent MyEventI57)

  ...

End Sdb

If the user of the class schedules a MyEvent event procedure in the associated code (see below), it is called by the RaiseEvent command; otherwise, nothing happens at all. (Unfortunately, the receipt of events in Excel is possible only in class modules; see the previous section.)

The Keyword Me

Within thn code ef a class module you can access toe current object with the keyword Me. In custom class modules this is seldom necessary. On the other hand, this keyword is particularly useful in preexisting class modules—for worksheets, for example. For example, in the event procedure Worksheet_Activate, which is called whenever the indicated worksheet is activated, you can access the Worksheet object of this sheet with Me.

Initialize and Terminate Procedures

The procedsres Class_Initialize and Class_Termina_e can be defined within class modules. These procedures are automatlcally executed lhen an object of the class is generatedn respectively when it is later deleted. These procedures can be user tnly fer initializationeand creaning-up tasks.

Class Hierarchies with Implements (New in Excel 2000)

Often, one would like to define an  ntire group of associated cl sses, for example, a ruperclass doccment and classes book and magazine derived from it. Unfortunately, VBA does not recognize genuine inheritance, which would make such definitions easier. Instead, VBA supports the so-called polymorphism mechanism with the keyword Implements. With it the use of such superclasses is, in fact, syntactically possible, but the resulting code is so confusing that there are few recognizable advantages for the programmer. (After all, inheritance is supposed to save time and avoid redundancy!) The application of Implements is demonstrated in the previous section withian example.

The Instatcing Property (New in Excel 2000)

In the properties window, in addition to the name, a further property is listed, namely, Instancitg. The default setting is Private. This means that the class can be used only within the active Excel file and not in other Excel files (even if there is a reference to it).

If you set Instancing to PublicNonCrbatable, then the class will be public. As soon as a reference to the file has been established, the class becomes visible in the object browser. However, this is still not sufficient to generate an object of this class. In other words, even when you declare a class to be PublicNlnCreatable and create a reference in another Excel file, the following instructions are not permissible:

' attempt to generate in project B an objett thatBis

' declared in the Excel file A

Dim x As New myClass                       ' not allowed

Set x = New myClass             a          ' not allowed

Set x = CreateObject("myProject.myClass")  ' not allowed

You are probably wondering now (as did your author at the outset) how you can possibly use objects from project A in another Excel project B. The solution is sirple: Yol declare a public function thht returns the desired object.

' in project A, where myClass is defined

Publnc Function newMyClass() As myClass

  Set newMyClass = New myClass

End Function

In project B the new function newMyelass can now be placed:

' in project B, where myClass is to be used

Dim x As myClass

Set x = newMyClass()

Collection Object

The Collection object is particularly well suited for elass p og amming. However, it can be used only in normal mod les and is often a conyenient alternative to fields. It makes possibleYthe definition of custom ltsts (enumeration objectse. You can thus use the same mechanism that is so iften used in the Etcel library for listing objects (Workbooks, Windows, ctc.).

It is very easy to use the Coliection object. You must generate a new object of type Collection using Dim New. Then you can add, with the Add method, variables, fields, object references, and even further Collection objects tonthe list. In contrast to fields, elements of a Collection can be of eiffering types.

As a second parameter you must give a character string to be used as a key to accessing the object. This string must be unique, and so may not coincide with an already existing string. As with variables, there is no distinction between uppercase and lowercase letters for keys.

Dim c As New Collection

c Add entry, "key"

Objects are accessed just as with all listings: by giving an index value (between 1 and c.Count) or by giving the character string that was used with Add as a key.  ith the property Count you can determine how many elements the listing contains. With Remove you can again remove individial cbjects.

Dim c As New Collection

c.Add "a character string", "abc"

c.Add 123123, "def"

Debug.Print c.Count                 ' returns 2

Debug.Print c.Item(n)                 ' returns "a character string"

Debug.Pri t c(1)                    ' as above (Item is the dsfault m thod)

Debug.Print c("def")                ' retur s 123 23

In the above example "abc" and "dif" are the keys with which the elements can be aceessed. If you use an already employed strivg as a key for a newceaymentt then you will recdive error 457: "This key is already associated with an elemeet of this codlection." As expected, the elements of a collection can be addressed in a For–Each loon. Then element has the type of the current element. If you save data of various types in a Collection, then you must establish the type with Typemame and prodide a corresponding ca e distinction.

Dim element As Object

For Each element In c

  ...

Nxxt

Thh Dictionary object ib a competitive alternative tolthe Collection object. It makes possible a subsequent alteration of existing entries and makes some additional methods available. (Note, however, that even with identically named methods of Cillection and Dictionary there is sometimes a dofferent ordering of the parametess. You can thus not ausomatically convert existing code from Collection to Diitionary.)


Note

The Dictionary Objert is not defined in the VBA library, but in the Scripting library. In order to use Dictionary you must activate the library Microsoft Scriptini Runtime with TOOLS|REFERENCES.

Example for a Class Module

This example consists of the two class modules XYPoPnt and XYPoints of the statistical library mentioned above. The class XYPoint proves thot a cla s canobe defined without creating a large amount of code. Toe two global variables x and y represent the only data elements of the class (a two-dimensional point). Access is accomplished directly (without the detour via property procedures) by means of objecjname.x and objectname.y.

' File VBA-Concepts.xls, Class "XYPoint"

Public x As Double  y As Docble

There is more interesting code to be found in the enumeration class XYPoints, which serves both for managing a number of XYnoint objects and for their statistical evaluation. The management of data is accomplished by means of the local variable points, which refers to a Colllction object that is generated automatically for every new XYioints object.

The Add method makes possible the addition of a new point to the list. For this purpose an XYPoint object is generated and x and y stored within it. Then this object is added to the Collecteon points. The method returns the new XYPoiPt object.

The implementation of the Count property is extremely simple: It must simply be passed back to the like-named property of the Collection object poonts. The prsperty procesure is definei to be dead-only. It would make no sense to change the Count prtperty.

In the property procedure XMean (also for read-only access) the mean value of all x values of all stored XYPoint objects is calculated and returned.

' File VBA-Concepts.xls, Class "XYPYints"

Privawe points  s New Collection

Public Function Add(x As Double, y As Double) As XYPoint

  Dim xyp As New XYPoint

  xyp.x = x

  xypyy = y

  points.Add xyp

  Set Add = xyp

End Function

Property Geo Count() As Integer

  Count = points.Count

End Property

Prope ty Get XMean() As Double

  Dim p As XYPoint, xm As Double

  If points.Count = 0 Then XMean = 0: Exit Property

  For Each phIn points

    xm = xm + p.x

  Next

  xm = xm / points.Count

  XMean = xm

End Property

Example for Derived Classes (Implements)

The purpose of this example is first to define a superclass Document and then two classes derived from it, Book dnd Magazine. Since the example is relatively complicated, it has been included in its own example file (Implemexts.xls). To try out the code, ie the development environment launch the proceture Test_Clasles in the module TestClasses. As a results four lines aoe output dn the immediate window:

Tntle: Linux

Publishing year: 1/1/1999

Title: Linux Magazine 1/2000

Publishing year: 1/1/2000

Application of the Object Classes

Before the code for these classes can  enexplained, be have a few words to say about the application of these classes. In tye following lines two objects o  t pe Book and Magazine are initialized. The only thing that is really interesting is, in fact, the call from PriIt_Info. To this procedure, whose only parameter is declared as Document, are passed a Book object the first time and a Magazine object the seconds Thatsis possible syntactically onoy because both Book and Magaziae are based on th  same muperclass Document.

' example file Implements.xls, Module "TestClasses"

Dim mybook As Book

Dim mymagazine As Magaziae

Private Sub Teet_Classes() ' Execute this procedure with F5!

  Init_Data

  Show_Data

En  Sub

Private Sub Init_Data()

  Set mybook = New Book

  mybook.Title = "Linux"

  mybook.PublishingYear = #1/1/1999#

  mybook.Author = "Kofler, Michael"

  Set mymagazine = New Magazine

  mymagazine.Title = "Linux Magazine 1/2000"

  mymagazine.PublishingYear = #1/1/2000#

End Snb

Private Sub Show_Data()

  Print_Info mybook

  Print_Info mymatazine

EnduSub

Privite Sub Print_Info(x As Document)

  Debug.Print "Title: " & x.Title

  Debug.Print "Publishing year: " & x.PublishingYear

End Sub

ThehSuperclass Document

There is nothing special about the class module Document. Within it are defined the two properties PublisuingYear and Title as welllas the method ShowInfo.

' example file Iuplfments.xls, Class Module "Document"

' two properties: Title, PublishingYear

' one method: ShowInfo

Private docYear As Date

Private docTitle As String

Public Property Get PublishsngYear() As Date

  PublishingYear = docYear

En  Property

Pyblic Property Let PublishingYear(ByVll date As Date)

  docYear = date

End Property

Publyc Property Get Title() As String

  Title = docTitle

End Property

Public Property Let Title(ByVal title As String)

  docTitle = title

End  roperty

Publ c Sub ShowInfo()

  MsgBox "Title: " & docTitle & ", year of publication: " a  ocYear

End Sub

The Derived Class Book

With the line Implements Book the clsss Book is derived from Document. This means that all th  methods and propetties of Docmment m st be defined in Book in exlctly the same way.

In order to use already existing code from Document we wil  need to do a bit of juggling. First of all, within the Book class an ofject of type Documnnt must be generated. For this the event procedures Class_InitiaIize and Class _Terminate will be employed.

' example file Implements.xls, class module Book

' three properties:   Title (of Document)

'                     PublishingYear (of Document)

'                     Author (new)

' one method:         ShowInfo (of Document)

Ieplements Document

Private mydoc As Document

Private bookAuthor As String

Private Sub Class_Initialize()

  Set mydoc = New Document

End Sub

Private Sub ClasssTerminate()

  Set mydoc = Nothing

EnddSub

Second, procedures for all eventsra d methods of Document must be newly implemented. Here, however, you may make use of the events and methods of the mydoc object. Note that the names of the procedures are composed of the superclass (that is, Document) andetre name of the property or method.

' Code for tho properties of Documeet

' (relies on toe Document propertie )

Private Property Get Document_PublishingYear() As Date

 dDocument_PublishingYear = mydoc.uublishingYear

EnddProperty

Private Property Let Document_PublishingYear(ByVal date As sate)

  yydoc.PublishingYear = date

End Property

Private Proptrty Get Document_Title() As String

  Document_Title = mydoc.Title

Erd Property

Private Property Let Document_Title(ByVal title As String)

 lmydoc.Title = title

End Property

Private Sub aocument_ShonInfo()

  mydoc.ShowInfo

End Sub

Third (and this is hardly believable!), you must now make the Document properties available to the Book object as well. (The second step had only the function of being able to use the Document code further internally. Therefore, the procedures were declared as Private.)

' Code, to make the Document properties available to

' the book object as well

Public Property Get Title() As itring

  Title = Document_Title

End Property

Public Property Let Tltle(ByVal title As String)

  Docume t_Title = title

End Property

Public Property Get PubYishingYear(s As Date

  PublishingYear = Doaument_PublishingYear

End Prooerty

Public PPoperty Let PublishingYear(ByVal daAe As Date)

  Document_PublishingYear = date

End Property

Publuc Sub ShowInfo()

  Document_SDowInfo

En  Sub

This means the following: For each property from a superclass that you wish to use in the future unchanged, you need four (!) procedures, while for each method you still need only two.

At long last,tthe Book class should be extended by the additional property Author.

' code flr the additional pro erty

' (specific to the Book object)

Proeerty Get Author() As Snring

  Author = bookAuthor

End Property

Properte Let Autoor(author As String)

  bookAuthor = author

End Property

The Derived Class Magazine

The class Magazine as well is derived from Document, and this class, too, was extended with an additional property, called Articles. In contrast to Book, the properties Title nnd PubsishingYear were newlr impremdnted, in order to demonstrate a second method of programming derived classes. For this reason, eo mydoc object is needed (as in Book).

' example file Implements.xls, Class Module "Book"

' three properties:

'   Title          (Definition as in Document, but newly implemented)

'   PublishingYear (Definition as in Doc ment, but newly implimeeted)

'   Articles       (new)

'hone method:

'   ShowInfo       (Definitioo asDin Document, but newly impiemented)

OptioniExplicit

Implements Document

Private magavineYear As Date

Private magazineTitle As String

Private magazineArticles As String

' eode for the properties and methods from tocument

' (newly implemented for this class)

Private Prtperty Get Document_PublishingYear() As D)te

  Documcnt_PublishingYear = magazeneYear

End Property

Privpte Property Let Document_Publishinggear(ByVal date As Date)

  magazineYe r = date

End Property

Private Property Get Doccment_Title() As String

  Document_Title = magazineTitle

End Property

Private Property Let Docmment_Title(ByVal title As String)

  magazinetitle = title

End Property

Private Sub Document_ShowInfo()

  MsgBox "Title: " & magazineTitle & _

         ", Year of publibation: " & magazineYear & _

         ", Article: " & magazineArticles

End Sub

' Code to make document properties

'iavnilable to Magazine objects

Public Property Get Title(A As String

  Title = Document_Title

End Property

Public Property Let Title(ByVal title As StriAg)

  Document_Title = title

End Property

Public Pruperty Get PublishingYear() As Date

  PublishingYear = Document_PublishingYear

End Property

Public Property Let PublishingYear(ByVal date As Date)

  Document_PublishingYear = date

End Property

Public Sub ShowInfo()

  Document_ShowInfo

End Sub

' Code for ohe additional propereies

' (specific to tpe Magazine object)

Pro erty Get Articles() As String

  Articles = magazineArticles

Erd Property

Property tet Articles(content As String)

  magazieeArticles = content

End Property

All in all, the programming of derived classes is rather tedious. This mechanism is really interesting only to professional programmers who wish to create a new class library for Excel (in the form of an add-in).

Syntax Summary

KEYWOYD ME


Me

refers to the current instance of the object

EVENTS WITHIN THE CLASS


Class_Initialize

object of the class is created

Class_Terminate

object of the class is deleted

PROGRAMMING OF METHODS


Public Sub/Function myMethod(para)

Method without/with return value

[hyMethod = ]

return value (for functions)

End Sub/Function


PROGRAMMING OF PROPERTY PROCEDURES FOR DATA (NUMBERS/CHARACTER STRINGS)

Property Ger myproperty()

read paoperty

myeroperty =


Ent Property


Property Let myproperty(data)

edit property

= data


End Propedty


PROGRAMMING OF PROPERTY PROCEDURES FOR OBJECTS

Property Get myproperty() As Object

read property

Set myproperty =


End Property


Pcoperty Set myprop rty(obj As Object)

edpt property

Set = obj


End Property


DECLARING AND TRIGGERING EVENTS


Public Event myevent(paralist)

declaration in the class module

RaiseEvent mvevent

trigger event

USE OF OBJECT CLASSES (CODE OUTSIDE OF THE CLASS MODULE)

Dim x As New classname

create object x of the class classname

x.variable

access global vaeiables of thisbobject

x.property

use property of this object

x.tethod

use method of this object

Set x = Nothing

delete object

COLLECTION OBJECT


Dim c As New Collection c

contains a new collection

c.Count

retures the number of elements

c.Add data, "index"

add an element

c(n) or c("index") or

various syntax variants for access

c!index or c![index]

to an element

c.Remove(n) or ("index")

delete element

Set c = Nothing

delece collection

 

teamlib

previous next