Location via proxy:   [ UP ]  
[Report a bug]   [Manage cookies]                
0% found this document useful (0 votes)
67 views

VBA: Visual Basic For Applications - Introduction

This document provides an introduction to Visual Basic for Applications (VBA) within Microsoft Excel. It discusses what VBA is, how it can be used to develop macros within Excel to automate tasks and procedures. An example is provided of using VBA macros in Excel to numerically solve equations by implementing the Newton-Raphson method on a sample function. The document walks through recording a macro, programming the Newton-Raphson method in VBA code within Excel cells, and generating a graph to visualize the roots.

Uploaded by

jamil
Copyright
© © All Rights Reserved
Available Formats
Download as PDF, TXT or read online on Scribd
0% found this document useful (0 votes)
67 views

VBA: Visual Basic For Applications - Introduction

This document provides an introduction to Visual Basic for Applications (VBA) within Microsoft Excel. It discusses what VBA is, how it can be used to develop macros within Excel to automate tasks and procedures. An example is provided of using VBA macros in Excel to numerically solve equations by implementing the Newton-Raphson method on a sample function. The document walks through recording a macro, programming the Newton-Raphson method in VBA code within Excel cells, and generating a graph to visualize the roots.

Uploaded by

jamil
Copyright
© © All Rights Reserved
Available Formats
Download as PDF, TXT or read online on Scribd
You are on page 1/ 16

VBA: Visual Basic for Applications - Introduction

What is VBA?

VBA is a version of Visual Basic (VB) available in most Microsoft (MS) Office applications such as MS
Excel, MS Word, and MS PowerPoint. A more limited version of VB, known as VBScript, is available in
MS Access (the MS Office database application), as well as in MS Internet Explorer (the MS web
browser). In MS Office applications VBA is used mainly to develop procedures, known as Macros, that
can be run within the application itself.

By using VBA within a given application you can use the application's own interface to run a program (a
macro) rather than creating your own interface as you do when developing a VB program from scratch.
For example, when using VBA within MS Excel we can use the Excel spreadsheet cells as input or output
locations for a given numerical procedure. Other than that, programming a macro within MS Excel, or any
MS Office application, for that matter, is not different than programming a sub procedure in VB. All the
VB commands, such as Open, Close, Input, Print, If blocks, Do While, Do Until, For…Next, etc., are also
available within VBA.

Numerical solutions in MS Excel

MS Excel is an excellent application for developing numerical solutions. Even without programming
macros in the spreadsheet, you can solve many numerical problems by using the operations and functions
already available in MS Excel itself. For instance, the examples on numerical solution of non-linear
equations, numerical integration, and calculations of statistics of a sample, provided in earlier handouts,
were developed using MS Excel.

Considering that spreadsheet programs are commonly available, I expect that you have had a minimum
amount of experience in using MS Excel (or other spreadsheet applications, e.g., Quattro Pro) including the
production of tables, use of pre-defined functions, and creation of graphics. If you have not used MS Excel
before, I would recommend that you learn its basic operation by following one of the many books on the
subject available in any local bookstore. Some of those books may be available at the USU library for
check out. My understanding is that those students that took Freshman Engineering seminar at USU have
had experience with MS Excel or Quattro Pro spreadsheets. Therefore, I will be covering mainly the use of
VBA within an MS Excel spreadsheet, rather than the operation of the spreadsheet per se.

Combining MS Excel and VBA - An Example

As indicated above, MS Excel worksheet cells can be used as input locations for a VBA program. Those
input cells in the worksheet can be referenced within a VBA program (macro) by using the VBA functions
Range and Cells. As an example of a simple VBA application within Excel, open an Excel worksheet and
fill out the cells as shown in the figure below. The contents of cells A1 and A3 are simply strings that
cover additional cells to the right. These strings are entered by clicking on the corresponding cell and
typing the string directly. The contents of cells A5 and B5 are the strings "x" and "y", respectively. Again,
entered by typing directly on those cells.

Creating a Table of values


The problem we are trying to solve is to find the solution to the equation f(x) = 0 (see figure below) in the
interval (2,5). Therefore, it will be convenient to have a graph of the function available to estimate the
location of the root or roots. This, as you know, is easily achieved in Excel by typing values of x in the
cells immediately below cell A5, and, then entering the formu la corresponding to f(x) in the cells
immediately to the right, i.e., below cell B5. To fill out the first entry in the table, type the value 2 in cell
A6, and then, in cell B6, type the formula:

= Exp(A6)*Sin(2.*A6)-3.5

1 VBAIntro
Next, in cell A7 enter the formula

= A6 + 0.1

Then, click on cell B6 to select the cell, place the cursor on the lower right corner of that cell, then, holding
the left button on the mouse, drag the mouse until the cell B7 is selected. Release the mouse button. What
you have just done is to copy the formula in cell B6 onto cell B7. Because the formula in B6 refers to the
relative position A6, when copying the same formula to cell B7, Excel modifies to formula to refer to the
corresponding adjacent cell in the x column, namely A7, thus completing the second entry into the table.

To complete the table up to x = 5, select cells A7 and B7 simultaneously by holding down the left mouse
button, placing the cursor on the lower right corner of cell B7, and dragging the mouse down several rows.
Stop dragging the mouse when the value 5.0 shows up somewhere in the A column. For this case, that
happens when we reach row number 36. As shown in the figure below, we now have a complete table of y
= f(x), in the domain (2,5).

Figure 1. Spreadsheet for calculating roots of a function using the Newton-Raphson method.

2 VBAIntro
Creating a graph

To produce the graph, perform the following steps:

1. Select the entire table, including the headings (x and f(x)), then select the Chart option in the Insert
menu. You will get a window entitled "Chart Wizard - Step 1 of 4 - Chart Type."

2. Select the chart type XY Scatter, then select as chart sub-type the rightmost one in the second column
(i.e., curved lines, no markers for individual data points).

3. Press the Next button. You will now get the window entitled "Chart Wizard - Step 2 of 4 - Chart Data
Source."

4. Press the Next button again. That will take you to the window entitled "Chart Wizard - Step 3 of 4 -
Chart Type."

5. Enter titles for the x- and y-axes labels in the fields entitled "Value (X) Axis" and "Value (Y) Axis,"
respectively. For example, x for Value (X) Axis, and y for Value (X) Axis.

6. Click on the Gridlines tab and clear off all the selected options so that no gridlines will be shown in the
graph.

7. Press the Next button once more. You will now be in a window entitled "Chart Wizard - Step 3 of 4 -
Chart Location." Select the option "as a new sheet" and press the Finish button.

Excel has, at this point, created a separate worksheet with the graph of the function as shown in Figure 2.
This worksheet is labeled Chart 1, as indicated in the tab at the bottom left corner of the sheet. We can see
from the graph that there are two roots of the function in the interval (2,5), one near 3.0, and one closer to
5.0. This information will be useful when using the Newton-Raphson (or any other method) to find those
roots, because it help us select a proper initial value for the solution. You could select for example, values
of 3.0 and 5.0 to get the process started.

Programming the Newton-Raphson method

To get back to the original spreadsheet click on the tab labeled "Sheet 1." We will now proceed to enter in
that spreadsheet the data necessary to get the Newton-Raphson method started. Recall that such a method
requires the following parameters:

• A tolerance value for convergence, or error, of the solution for which we use the variable name
epsilon.
• A maximum allowable number of iterations after which we will stop the process if the solution has not
yet been found. We will use the name Nmax for such a variable.
• An initial value, or seed, for the process, which we call x0.

The variable names and their corresponding values are typed into cells E5 to F8 as shown in Figure 1. In
order to program the Newton-Raphson method in the present worksheet we need to have access to the
Visual Basic toolbar.

3 VBAIntro
Figure 2. Graph of f(x)= ex·sin(2x) - 3.25.

The Visual Basic Toolbox

To get the Visual Basic toolbar, do a left mouse click somewhere in the toolbar area of your worksheet and
select the Visual Basic option of the drop down menu shown. A toolbar will appear somewhere in the
middle of your worksheet showing the following:

Figure 3. Visual Basic (VBA) toolbox for Microsoft Excel.

4 VBAIntro
This toolbox can be dragged and dropped in the main toolbar, typically located on the top of the worksheet,
so that it will be available while we finish preparing this particular worksheet. Proceed, therefore, to move
the Visual Basic toolbox on to the main toolbar. Your toolbar may look as that shown in Figure 1.

Figure 3 shows the names of the six controls in the Visual Basic toolbox. The Run Macro, Record Macro,
and Resume Macro buttons are used when running, recording, or resuming a Macro within the worksheet.
As indicated above, a Macro is a sequence of operations to be performed by the Excel worksheet at the
user's request. By pressing the Record Macro button, all actions that the user performs in the worksheet
after pressing that button will be recorded as a Vis ual Basic sub procedure. The recording of the Macro
will continue until the user decides to stop it. The Macro, being just another VB sub procedure, can be
given a name by the user, or simply take the default name given by Excel.

Recording a Macro in an Excel worksheet is convenient when there is a number of operations in your
spreadsheet that you that you perform routinely, and that could be conveniently programmed as a separate
procedure. Examples of such operations are: typing the same title for spreadsheets, generating the same
type of chart for similar spreadsheets, etc. The Help feature in Visual Basic provides a good amount of
information on the manipulation of recorded macros. In this handout I will concentrate on creating macros
using the Visual Basic Editor rather than recording them.

The Visual Basic Editor button will open the VBA editor for you to type any sub procedure or sub function.
The Control Toolbox button will generate a toolbox with all VB controls as shown in Figure 4. The Design
Mode button toggles the control between the design mode, in which you can alter the properties of any VB
control that you define in your worksheet, and the operating mode, in which the worksheet is available to
run any pre-recorded or pre-defined Macros.

The Control Toolbox

Figure 4. The Control Toolbox.

The Control Toolbox include all the Visual Basic controls available in the original Visual Basic
programming environment, as well as a large number of other controls found when pressing the More
Control button in the Control Toolbox. Some of the controls with which you should be already familiar

5 VBAIntro
are Text Boxes, Images (or Pictures), Command Buttons, and Labels. They are used in VBA in basically
the same way that you use them when building your interface form in Visual Basic.

As the Visual Basic toolbox did earlier, the Control Toolbox first appears as a free-floating toolbar in the
middle of the worksheet. It is a good idea to move it to the main toolbar as we did with the Visual Basic
toolbox. The main tool bar will now appear as shown in Figure 1.

Creating a Command Button to Launch the Program

Click on the Design Mode button of the Visual Basic toolbox, and then on the Command Button button of
the Command toolbox to select the command button object. Place a command button as indicated in Figure
1. Then press the Properties button of the Control toolbar while the button that you just created is still
selected. You will get a properties window for this button as shown in Figure 5. Change the following
properties in the window: (Name): cmdNewton, and Caption: Solve for x. Then click off the properties
window.

Figure 5. Properties window for command button cmdNewton.

Programming the Command Button cmdNewton

Double click on the command button cmdNewton while the Design Mode button is still active. This
operation will open the Visual Basic editor and place the cursor in the code window within the appropriate
sub procedure corresponding to cmdNewton, i.e., Private Sub cmdNewton_Click( ) .

6 VBAIntro
Type the following code within that sub procedure:

Private Sub cmdNewton_Click()

Dim x As Double
Dim epsilon As Double
Dim Nmax As Integer
Dim i As Integer

epsilon = Range("F5")
Nmax = Range("F6")
x = Range("F7")

i = 0

Do While Abs(f(x)) > epsilon And i < Nmax


x = x - f(x) / fp(x)
i = i + 1
Range("F10").Value = f(x)
Loop

If Abs(f(x)) < epsilon Then


Range("F9").Value = x
Else
MsgBox ("No convergence after " & Str(i) & " iterations - try new initial value.")
End If

End Sub

The following functions need to be typed also. They define the function f(x) and its derivative, fp(x), used
in the Newton-Raphson iterative formula:

Private Function f(x As Double) As Double


f = Exp(x) * Sin(2# * x) - 3.5
End Function
Private Function fp(x As Double) As Double
fp = Exp(x) * (Sin(2# * x) + 2# * Cos(2# * x))
End Function

Simple Input and Output from the Worksheet

Notice how the input data is extracted from the spreadsheet by using the lines:
epsilon = Range("F5")
Nmax = Range("F6")
x = Range("F7")

While output is produced either by assigning a value to a cell by using:


Range("F10").Value = f(x)

or,
Range("F9").Value = x

Also, message boxes can be used for output as in the line:

MsgBox ("No convergence after " & Str(i) & " iterations - try new initial value.")

7 VBAIntro
Running the Macro

Once the code has been entered, select the option Close and return to Microsoft Excel in the File menu.

At this point you will be back in the worksheet and ready to run the macro through the command button
cmdNewton. It is advisable first, however, to save the worksheet. Next, click off the Design Mode button
in the Visual Basic toolbox. Also, make sure that values for epsilon, Nmax, and x0 are given in the
appropriate cells. Finally, press the button labeled "solve for x."

The solution found for x0 = 3, is 3.21229 with and error of f(x)= 2.31E-09. (See Figure 1). Also, check
that if you use x0 = 5, your solution will be 4.696412, with an error of -5.2E-09.

Improving the Spreadsheet's Appearance

The spreadsheet used for the solution and presented in Figure 1 is a bare-bone version of it. You can use
many of the features of Excel to produce a more appealing spreadsheet as the one shown below in Figure 6,
which includes the graph in the worksheet "Newton-Raphson." Consult a book on Excel or use the Help
feature in the program itself to learn more about Excel features.

Figure 6. An improved version of the spreadsheet presented in Figure 1.

8 VBAIntro
Opening a Spreadsheet that Includes Macros

Whenever you try to open an Excel spreadsheet that contains Macros, you will be asked to decide whether
to disable or enable those macros. If you want to run the programs you have coded in that particular
spreadsheet, you must select the Enable Macros options. The main reason that this question is presented to
the user when opening a Macro is to avoid getting any computer virus inserted in the Macro particularly
when you receive anonymous or unsolicited Microsoft Office documents. By disabling the Macros you can
prevent those viruses from disturbing your work. Most of the viruses programmed in Microsoft Office
documents are relatively harmless, however, annoying, and can be easily detected with computer virus
detection software.

An Excel-based Newton-Raphson Program for Different Functions

The program whose interface is shown in Figure 7 was developed starting from the simpler Newton-
Raphson solution presented earlier. This new program allows the user to define the values of f(x) and f'(x),
therefore, providing with a very powerful application that solves more than one problem. The user has to
make sure that he or she enters the proper expressions for f(x) and f'(x). The user can also provide the lower
and upper limits for a range of values of x to produce the attached table and its related graph. The table and
graph are produced by pressing the button labeled "ß create table". The operation of the Newton-Raphson
solution is started by pressing the button labeled "solve for x." The code for the different buttons is
presented in the next few pages. Notice in particular the use of the functions Cells(I,J) in the code. The
naming of the sub procedures is straightforward (i.e., according to the prescribed operations).

Figure 7. Fancy interface for solving non-linear equations using the Newton-Raphson method in Excel.

9 VBAIntro
'----------------------------------------------------------------------------------------
Private Sub cmdInfo_Click()

Dim myMessage As String


myMessage = "Enter expressions for f(x) and f'(x) in cells K1 and K2, respectively."
myMessage = myMessage & " Enter starting and ending values of x, as well as an
increment, to generate the table of (x,y)."
myMessage = myMessage & " Press the button to create the table first. It will also
modify the graph."
myMessage = myMessage & " Then, select the parameters for the Newton-Raphson
algorithm, and press the solve button."

MsgBox (myMessage)

End Sub
'----------------------------------------------------------------------------------------
Private Sub cmdTable_Click()

Dim xT As Double
Dim xStart As Double
Dim xEnd As Double
Dim Dx As Double
Dim n As Integer, j As Integer
Dim ExpressionX As String
Dim FormulaX As String

For j = 1 To 500
Cells(5 + j, 2).Value = ""
Cells(5 + j, 3).Value = ""
Next j

ExpressionX = Range("K1")
xStart = Range("K3")
xEnd = Range("K4")
Dx = Range("K5")

n = (xEnd - xStart) / Dx + 1

For j = 1 To n
xT = xStart + (j - 1) * Dx
Cells(5 + j, 2).Value = xT
Cells(5 + j, 3).Value = ExpressionOut(ExpressionX, 5 + j)
Next j

End Sub
'----------------------------------------------------------------------------------------
Private Sub cmdNewton_Click()

Dim x As Double
Dim epsilon As Double
Dim f As Double, fp As Double
Dim Nmax As Integer
Dim i As Integer
Dim Expressionf As String
Dim Expressionfp As String

Expressionf = Range("K1")
Expressionfp = Range("K2")

epsilon = Range("F5")
Nmax = Range("F6")
x = Range("F7")

i = 0

Range("H25").Value = x
Range("H26") = ExpressionOut(Expressionf, -1)
Range("H27") = ExpressionOut(Expressionfp, -1)

f = Range("H26")
fp = Range("H27")

10 VBAIntro
Do While Abs(f) > epsilon And i < Nmax
x = x - f / fp
Range("H25").Value = x
f = Range("H26")
fp = Range("H27")
i = i + 1
Range("F10").Value = f
Loop

If Abs(f) < epsilon Then


Range("F9").Value = x
Else
MsgBox ("No convergence after " & Str(i) & " iterations - try new initial
value.")
End If

End Sub
'----------------------------------------------------------------------------------------
Private Function ExpressionOut(ExpressionIn As String, index As Integer) As String

Dim xVariable As String


Dim increase As Integer

If index < 0 Then


xVariable = "H25"
increase = 2
Else
Select Case index
Case Is < 10
increase = 1
Case Is < 100
increase = 2
Case Is < 1000
increase = 3
End Select
xVariable = "B" & Trim(Str(index))
End If

ExpLengthIn = Len(ExpressionIn)

countx = 0

For i = 1 To ExpLengthIn
If (Mid(ExpressionIn, i, 1) = "x" And Mid(ExpressionIn, i + 1, 1) <> "p") Then
countx = countx + 1
End If
Next i

ExpLengthOut = ExpLengthIn + increase * countx

ExpressionOut = ""

i = 0: j = 0
Do While j <= ExpLengthOut
i = i + 1
j = j + 1
If (Mid(ExpressionIn, i, 1) = "x" And Mid(ExpressionIn, i + 1, 1) <> "p") Then
j = j + increase
ExpressionOut = ExpressionOut & xVariable
Else
ExpressionOut = ExpressionOut & Mid(ExpressionIn, i, 1)
End If
Loop
ExpressionOut = "=" & ExpressionOut

End Function
'----------------------------------------------------------------------------------------

11 VBAIntro
Analysis of the code

Some details of the operation of the procedures and functions listed in the code above are presented
following:

Procedure cmdInfor_Click

The sub procedure cmdInfor_Click() produces an info box giving an outline of the worksheet operations.

Procedure cmdTable_Click

The sub procedure cmdTable_Click() generates the table of values of x and y = f(x). The sub
procedure first empties up to 500 cells down from the top of the table using the statements:
For j = 1 To 500
Cells(5 + j, 2).Value = ""
Cells(5 + j, 3).Value = ""
Next j

Then, it loads the values of the expression corresponding to the function f(x) in cell K1, the starting and
ending values of x (cells K3 and K4), and the increment of x (cell K5), using the statements:

ExpressionX = Range("K1")
xStart = Range("K3")
xEnd = Range("K4")
Dx = Range("K5")

Notice the use of the Range procedure in loading the values of the variables.

The number of entries in the table is calculated as:


n = (xEnd - xStart) / Dx + 1

The table, proper, is filled by using these statements:

For j = 1 To n
xT = xStart + (j - 1) * Dx
Cells(5 + j, 2).Value = xT
Cells(5 + j, 3).Value = ExpressionOut(ExpressionX, 5 + j)
Next j

To fill out the cells corresponding to the table we use the property Value in the Cells procedure. Unlike the
Range procedure, which uses references such as "K1" or "K5" to locate a cell, the Cells procedure uses the
location of the cell as the ordered pair (k,j), where k is the cell's row index and j is the cell's column index
in the spreadsheet. For example, in the For-Next loop shown immediately above, we let the index j vary
from 1 to n, and fill the values of Cells(5+j,2), i.e., row 5+j and second column, with the values of xT
corresponding to consecutive values of x in the table. On the other hand, cells in row 5+j and third column,
i.e., Cells(5+j,3), get filled with the Excel formula corresponding to the result of the function:

ExpressionOut(ExpressionX, 5 + j).

Function ExpressionOut

The user-defined function

ExpressionOut(ExpressionIn As String, index As Integer) As String

takes as arguments a string, ExpressionIn (= ExpressionX = expression for f(x), above), and an integer
value, index (= 5+j = row index, above), and returns a string. The function ExpressionOut uses the string
functions Trim, Len, and Mid, as well as of the concatenation operator '&', to translate expressions given as
functions of x into Excel formulas that can be placed in the spreadsheet cells. The function basically scans
12 VBAIntro
the input string for any appearance of the character "x" and converts it to the string "Bnnn", where nnn is
the numeric value of the function's argument index. For example, for the call shown above, i.e.,

Cells(5 + j, 3).Value = ExpressionOut(ExpressionX, 5 + j)

the value placed in Cells(5+j,3) is the Excel formula for f(x), with x replaced by the reference to the cell
immediately to the left. As an illustration, for the case of Figure 7, and for j = 3, i.e., in Cells(8,3) =
Range("C8"), the value placed in the cell is

= Exp(B8)*Sin(2.*B8)-3.25 .

Thus, cell "B8" holds a value of x, and cell "C8" holds the value of f(x) = Exp(x)*Sin(2.*x)-3.25.

The function ExpressionOut is also used in procedure cmdNewton_Click to translate the expressions for
f(x), in cell K1, and for f'(x), in cell K2, in terms of the reference cell H25. (For these cases the value of the
function's argument index is set to -1.) The resulting formulas are then placed in cells I25 and J25,
respectively, by the cmdNewton_Click procedure. The results placed in cells H25-J25 are used in that
procedure to solve for the root of f(x) = 0.

Detailed explanation of the operation of user-defined function ExpressionOut


========================================================

In function ExpressionOut, the variable increase helps determines how many characters must be reserved
in the resulting string to replace every occurrence of the "x" character (not followed by p, as in "Exp") with
an appropriate cell reference. For example, if the "x" characters are to be replaced by the cell reference
"B6", increase = 1 (only one number follows the "B" in the cell reference). If "x" is to be replaced by
"B16", then increase = 2, and so on. The following piece of code, from the function, determines the value
of increase, and creates a string variable, called xVariable, that will hold the cell reference to replace "x" in
the string returned by the function:

If index < 0 Then


xVariable = "H25"
increase = 2
Else
Select Case index
Case Is < 10
increase = 1
Case Is < 100
increase = 2
Case Is < 1000
increase = 3
End Select
xVariable = "B" & Trim(Str(index))
End If

The value of xVariable will be either "H25", if index<0, or, for any other value of index, B followed by that
value. In the latter case, the following statement assigns the value of xVariable:

xVariable = "B" & Trim(Str(index))

In the previous statement, the Str function converts the value of index into a string, and the function Trim
then removes any leading or trailing spaces from that string. The use of Trim is necessary because the
function Str inserts a leading space whenever the value of index is a positive number. For example, if index
has the value 16, Str(index) = " 16" , and Trim(Str(index)) = "16" .

In function ExpressionOut, the variable countx keeps track of the number of occurrences of the character
"x" in the input argument ExpressionIn, as shown in the code segment below (Notice, however, that the
occurrence of "x" in "Exp" is not counted as an occurrence of "x"):

13 VBAIntro
ExpLengthIn = Len(ExpressionIn)
countx = 0
For i = 1 To ExpLengthIn
If (Mid(ExpressionIn, i, 1) = "x" And Mid(ExpressionIn, i + 1, 1) <> "p") Then
countx = countx + 1
End If
Next i

In the previous piece of code, the string function Mid is used to make sure that if an "x" exists in location i,
but it is not followed by a "p," then the value of countx is increased by one. (Because this function uses
many string-related functions to operate, I have included a section, below, briefly describing the operation
of some of those functions.)

The length of the string argument, ExpressionIn, used as input to the function is determined by using:

ExpLengthIn = Len(ExpressionIn)

After increase and countx have been determined, the length of the output function is determined to be:

ExpLengthOut = ExpLengthIn + increase * countx

The value returned by the function is the string created through the following code segment:

i = 0: j = 0
Do While j <= ExpLengthOut
i = i + 1
j = j + 1
If (Mid(ExpressionIn, i, 1) = "x" And Mid(ExpressionIn, i + 1, 1) <> "p") Then
j = j + increase
ExpressionOut = ExpressionOut & xVariable
Else
ExpressionOut = ExpressionOut & Mid(ExpressionIn, i, 1)
End If
Loop
ExpressionOut = "=" & ExpressionOut

In the code segment above, the counter i keeps track of the location of each character in the input argument
ExpressionIn. The counter j keeps track of the current location of the next character of the output argument
ExpressionOut (which is being built by copying ExpressionIn into ExpressionOut, but replacing the
character "x" with an appropriate cell reference). Every time that such replacement occurs the value of j is
increased by the value of increase. The Do-While loop shown above is executed as long as j is not larger
than the length of the output string. The final statement of the code segment shown above adds an equal
sign in front of the formula built in the Do-While loop. With this equal sign the output string
ExpressionOut takes the shape of an Excel formula that can be placed in the right location in a spreadsheet
to calculate a value.

Procedure cmdNewton_Click

This procedure takes the expressions for f(x) and f'(x) from the spreadsheet by using the statements:

Expressionf = Range("K1")
Expressionfp = Range("K2")

It also reads the values of the tolerance for convergence (epsilon), maximum number of iterations (Nmax),
and initial value of x (x), from the spreadsheet by using:

epsilon = Range("F5")
Nmax = Range("F6")
x = Range("F7")

14 VBAIntro
The current values of x is placed in cell H25 through the statement:

Range("H25").Value = x

While, the formulas that calculate f(x) and f'(x), with the value of x in H25, are placed in cells H26 and
"H27", respectively, with the statements:
Range("H26") = ExpressionOut(Expressionf, -1)
Range("H27") = ExpressionOut(Expressionfp, -1)

Excel calculates the values of f(x) and f'(x) in H26 and H27, respectively, and those values get passed back
into the procedure cmdNewton_Click through the statements:

f = Range("H26")
fp = Range("H27")

With the first value of x, f(x), and f'(x) available, the procedure now iterates calculating improved values of
the root using the following Do While loop:

Do While Abs(f) > epsilon And i < Nmax


x = x - f / fp
Range("H25").Value = x
f = Range("H26")
fp = Range("H27")
i = i + 1
Range("F10").Value = f
Loop

When the control gets out of that loop, either because a solution is found or because the maximum number
of iterations is reached, the procedure produces a result that can be either the solution:

Range("F9").Value = x

or, a message warning of no convergence:

MsgBox ("No convergence after " & Str(i) & " iterations - try new initial value.")

Built-in string and string-related functions

String Functions: Left, Mid, Right, Trim

The functions Left, Mid, Right are used to extract characters (substrings) from the left end, middle,
and right end of a string. Suppose str is a string and m and n are positive integers. Then,
v Left(str, n) is the string consisting of the first n characters of str.
v Mid(str,m, n) is the string consisting of the n characters of str, beginning with the mth character.
v Right(str, n) is the string consisting of the last n characters of str

Trim (str) is the string str with all leading and trailing spaces removed.

String-related Numeric Functions: Len, InStr

Suppose str is strings. The value of Len(str) is the number of characters in str.

Suppose str1 and str2 are strings. The value of InStr(str1, str2) is zero if str2 is not a substring of str1.
Otherwise, its value is the first position of str2 in str1.

15 VBAIntro
References

This handout barely touches the surface of the variety of engineering applications of MS Excel alone, or
combined with VBA programming. If Visual Basic programming within Excel is of interest to you, you
will need to find some good references on the subject to learn on your own. References for the operation of
Excel spreadsheets are readily available in bookstores or libraries. References on VBA, however, are not
as readily available. I have only had access to two references for VBA, but mainly because I have not had
a whole lot of experience with it:

(1) Cummings, Steve, 1998, "VBA for Dummies," IDG Books Worldwide, Inc., Foster City, CA.,

and,

(2) "Visual Basic Complete," 1999, SYBEX, San Francisco.

Of these two, the first one contains a good amount of technical information, but the examples barely touch
Excel applications, rather concentrating on a graphics software called VISIO. (The VISIO software,
although not a Microsoft product, is authorized to include VBA in its interface.) The second reference
contains a few chapters dealing with VBA but mostly within the MS Word and MS Access applications.

Logan, Utah, October 28, 1999.

Update on References

A couple of references of more recent acquisition, and which I am still reviewing, are:

(3) Lomax, Paul, 1998, "VB & VBA in a nutshell - The Language," O'Reilly & Associates, Inc.,
Sebastopol, CA 95472,

and

(4) Walkenbach, John, 1999, "Excel 2000 Programming for Dummies," IDG Books Worldwide, Inc.,
Foster City, CA.

Of the latter two titles, the last one is an excellent introductory text for learning Visual Basic for
Applications (VBA) in the Excel environment. It is easy to understand, very well documented, and
presents a very organized approach to the language and its use within Excel. It assumes, however,
familiarity with Excel operation. Reference number (3) is an excellent reference for Visual Basic (VB) and
Visual Basic for Applications (VBA) for the experienced programmer.

Logan, Utah, Monday, November 22, 1999 - Reviewed in October, 2000.

16 VBAIntro

You might also like