You are on the Home/Excel/VBA/OOPS Example 1 page
Google
Web This Site

Object Oriented Programming – An example

 

The solution to the problem described below was provided by Jay Petrulis in a posting at http://www.mrexcel.com/board2/viewtopic.php?p=355022#355022.  In this write up, the procedural programming solution is redone from an object oriented perspective.  The reader should not interpret this to mean that OOP solutions are written in the conventional manner and subsequently translated into OOP.  Quite the contrary.  The OOP paradigm is so different from that of procedural programming that translation from one to the other is definitely not recommended!  The solution below was designed from scratch while, of course, sharing the underlying mathematics and trigonometry analysis with Jay’s solution.

 

The problem at hand is to find the coordinates of the center of the circle given two points on the circumference and the radius.  Basically, in Figure 1, given the location of points P0 and P1 and the radius R, what is the location of point C?  Of course, this chapter is not about geometry and trigonometry.  The focus is on developing an object oriented solution; the underlying mathematics will be taken as given.

 

Figure 1

 

A point is a type of object, and hence should be a class of its own.  However, Excel already has an object named point – it is part of a series in a chart.  Rather than use a name that will conflict with Excel’s Point, we will call this object a GeoPoint (for Geometric Point).

 

What are the key properties of a point?  Absolutely critical would be the coordinates – given by a point’s x and its y values.  In addition, other properties that will be of use are distance of another point from this point, the coordinate of the midpoint between this point and another point, and the slope of the line connecting this point with another point.

 

Create a class module, name it GeoPoint, and add the code in Figure 2.

Text Box: Option Explicit
 
Private dblX As Double, dblY As Double
 
Property Let x(uX As Double): dblX = uX: End Property
Property Get x() As Double: x = dblX: End Property
 
Property Let y(uY As Double): dblY = uY: End Property
Property Get y() As Double: y = dblY: End Property
 
Function Distance(P0 As GeoPoint) As Double
    Distance = Sqr((Me.x - P0.x) ^ 2 + (Me.y - P0.y) ^ 2)
    End Function
 
Function Slope(P0 As GeoPoint) As Double
    If Me.x = P0.x Then
        Slope = 3E+100
    Else
        Slope = (Me.y - P0.y) / (Me.x - P0.x)
        End If
    End Function
 
Function Midpoint(P0 As GeoPoint) As GeoPoint
    Set Midpoint = New GeoPoint
    With Midpoint
    .x = (P0.x + Me.x) / 2
    .y = (P0.y + Me.y) / 2
        End With
    End Function
 

Figure2

 

The next object to create is a circle.  The two critical definitional elements of a circle are its center and its radius.  Of course, the center, itself, is a point.  Create a Class module, name it GeoCircle, and add the code in Figure 3.  While the area and the circumference of a circle are not needed for this example, they are very common properties, and are included in the code.

Text Box: Option Explicit
 
Private pt_Center_Coord As GeoPoint
Private dblRadius As Double
 
Property Get Center_Coord() As GeoPoint
    Set Center_Coord = pt_Center_Coord
    End Property
Property Set Center_Coord(uCenter_Coord As GeoPoint)
    Set pt_Center_Coord = uCenter_Coord
    End Property
 
Property Get Radius() As Double: Radius = dblRadius: End Property
Property Let Radius(uRadius As Double): dblRadius = uRadius: End Property
Property Get Area() As Double
    Area = Application.WorksheetFunction.Pi() * Radius ^ 2
    End Property
Property Get Circumference() As Double
    Circumference = 2 * Application.WorksheetFunction.Pi() * Radius
    End Property

Figure 3

The only other property that needs to be added is setting the coordinates of the center given two points, P0 and P1.  Figure 4 contains that code and it too goes into the GeoCircle class module.  Don’t worry about the mathematics in it.  The key element to note is that the function has two arguments, each of which is a GeoPoint.  In addition, it uses the properties of the GeoPoint object to calculate midpoints, distances, and slopes of lines as needed.  Finally, if there is an error it returns the error as a string message.

Text Box: Function CenterCoordfrom2Pts(P0 As GeoPoint, P1 As GeoPoint) As String
    Dim MidptDist As Double, MidPt As GeoPoint, _
        Triangle_Height As Double, _
        Slope_Test As Double, Orthogonal_Slope As Double, _
        Theta As Double
    
    MidptDist = P0.Distance(P1) / 2
    Set MidPt = P0.Midpoint(P1)
    
    If MidptDist > Radius Then
        CenterCoordfrom2Pts = "no solution"
        Exit Function       '<<<<<
    ElseIf MidptDist = Radius Then
        Set Center_Coord = MidPt
        Exit Function       '<<<<<
    ElseIf MidptDist = 0 Then
        CenterCoordfrom2Pts = "infinite solutions"
        Exit Function       '<<<<<
        End If
 
    Triangle_Height = Sqr(Radius ^ 2 - MidptDist ^ 2)
    Set Center_Coord = New GeoPoint
    If P0.x = P1.x Then
        With Center_Coord
        .x = P0.x + Triangle_Height
        .y = MidPt.y
            End With
        Exit Function       '<<<<<
        End If
    Slope_Test = P0.Slope(P1)
    If Slope_Test = 0 Then
        With Center_Coord
        .x = MidPt.x
        .y = MidPt.y + Triangle_Height
            End With
    Else
        Orthogonal_Slope = -1 / Slope_Test
        Theta = Atn(Orthogonal_Slope)
        With Center_Coord
        .x = MidPt.x + Triangle_Height * Cos(Theta)
        .y = MidPt.y + Triangle_Height * Sin(Theta)
            End With
        End If
    End Function
 

Figure 4

The above code yields some very easy to use capability that is available both from VBA and from Excel.  In VBA, one can establish the center of a circle from its radius and two points with the code in Figure 5.

 

Text Box: Sub VBACenterFrom2Points()
    
    Dim P0 As New GeoPoint, P1 As New GeoPoint
    
    P0.x = 1 / Sqr(2): P0.y = 1 / Sqr(2)
    P1.x = -1 / Sqr(2): P1.y = 1 / Sqr(2)
    
    Dim aCircle As New GeoCircle, Rslt As String
    
    aCircle.Radius = 1
    Rslt = aCircle.CenterCoordfrom2Pts(P0, P1)
    If Rslt <> "" Then
        MsgBox "CenterCoordfrom2Pts returned error: " & Rslt
    Else
        With aCircle.Center_Coord
        MsgBox .x & ", " & .y
            End With
        End If
    End Sub

Figure 5

To use this new capability from an Excel worksheet, one needs a user-defined function.  This will also serve as an interface between the Excel worksheet, which deals with cells laid out in a tabular fashion, and the custom classes used to solve the problem.  In a standard module, enter the code in Figure 6.

 

Text Box: Function CenterFrom2Points(Radius As Double, _
        x0 As Double, y0 As Double, x1 As Double, y1 As Double)
    Dim P0 As GeoPoint, P1 As GeoPoint, _
        aCircle As GeoCircle, _
        ErrMsg As String, Rslt(1) As Double
    Set P0 = New GeoPoint: Set P1 = New GeoPoint
    Set aCircle = New GeoCircle
    P0.x = x0: P0.y = y0: P1.x = x1: P1.y = y1
    aCircle.Radius = Radius
    ErrMsg = aCircle.CenterCoordfrom2Pts(P0, P1)
    If ErrMsg <> "" Then
        CenterFrom2Points = ErrMsg
        Exit Function
        End If
    Rslt(0) = aCircle.Center_Coord.x
    Rslt(1) = aCircle.Center_Coord.y
    If Not TypeOf Application.Caller Is Range Then
        CenterFrom2Points = Rslt
    ElseIf Application.Caller.Columns.Count > 1 Then
        CenterFrom2Points = Rslt
    Else
        CenterFrom2Points = Application.WorksheetFunction.Transpose(Rslt)
        End If
    End Function
 

Figure 6

This function, CenterFrom2Points is array-entered in two cells in a worksheet.  These can be in the same row or in the same column as in Figure 7.

 

Figure 7