Download as pdf or txt
Download as pdf or txt
You are on page 1of 22

A Few PI ProcessBook VBA

Tips

OSIsoft vCampus White Paper


How to Contact Us
Worldwide Offices
Email: vCampus@osisoft.com
Web: http://vCampus.osisoft.com > Contact Us
OSIsoft Australia Pty Ltd.
Perth, Australia
Auckland, New Zealand

OSIsoft, LLC OSIsoft Europe GmbH


777 Davis St., Suite 250 Frankfurt am Main, Germany
San Leandro, CA 94577 USA OSI Software Asia Pte Ltd.
Singapore
Houston, TX
OSIsoft Canada ULC
Johnson City, TN
Montreal, Quebec
Mayfield Heights, OH
Calgary, Alberta
Phoenix, AZ
Savannah, GA OSIsoft, LLC. Shanghai
Seattle, WA Shanghai, People’s Republic of China
Yardley, PA OSIsoft Japan KK
Tokyo, Japan
OSIsoft Mexico S. De R.L. de C.V.
Mexico City, Mexico

Sales Outlets and Distributors


Brazil South America/Caribbean
Middle East/North Africa Southeast Asia
Republic of South Africa South Korea
Russia/Central Asia Taiwan

WWW.OSISOFT.COM

OSIsoft, LLC is the owner of the following trademarks and registered trademarks: PI System, PI
ProcessBook, Sequencia, Sigmafine, gRecipe, sRecipe, and RLINK. All terms mentioned in this book
that are known to be trademarks or service marks have been appropriately capitalized. Any trademark
that appears in this book that is not owned by OSIsoft, LLC is the property of its owner and use herein
in no way indicates an endorsement, recommendation, or warranty of such party’s products or any
affiliation with such party of any kind.

RESTRICTED RIGHTS LEGEND


Use, duplication, or disclosure by the Government is subject to restrictions as set forth in subparagraph
(c)(1)(ii) of the Rights in Technical Data and Computer Software clause at DFARS 252.227-7013

Unpublished – rights reserved under the copyright laws of the United States.

© 1998-2010 OSIsoft, LLC


a_few_processbook_vba_tips_v2.docx
TABLE OF CONTENTS
Table of Contents ............................................................................................................................... ii
Overview ........................................................................................................................................... 1
About this Document ............................................................................................................................. 1

What You Need to Start ......................................................................................................................... 1

"One-Click Value Trend" VBA Script .................................................................................................... 2


Introduction ............................................................................................................................................ 2

The General Settings .............................................................................................................................. 2

The Display_Open Event........................................................................................................................ 2

The Display_Click Event .......................................................................................................................... 3

"One-Click Value Ad Hoc Trend" VBA Script ........................................................................................ 5


Introduction ............................................................................................................................................ 5

The General Settings .............................................................................................................................. 5

The Display_Open Event........................................................................................................................ 5

The Display_Click Event .......................................................................................................................... 5

Creating XYPlots Programmatically ..................................................................................................... 7


Introduction ............................................................................................................................................ 7

The General Settings .............................................................................................................................. 7

The Command Button ............................................................................................................................ 8

The CreateButton_Click Event................................................................................................................ 8

The Display_DataUpdate Event ............................................................................................................ 10

“SetViewPort” VBA code snippet ...................................................................................................... 12


Introduction .......................................................................................................................................... 12

The General Settings ............................................................................................................................ 12

The Display_Open Event...................................................................................................................... 12

The Value1_DataUpdate Event ............................................................................................................ 12

“Modified” property ........................................................................................................................ 13


Introduction .......................................................................................................................................... 13

The General Settings ............................................................................................................................ 13

ii
The Display_BeforeClose Event ........................................................................................................... 13

Pass the Context from Parent to Child (Module Relative Display) ...................................................... 14
Introduction .......................................................................................................................................... 14

The General Settings ............................................................................................................................ 14

The cmdOpenChildDisplay_Click Event ............................................................................................... 14

Pass the Context from Parent to Child (Element Relative Display)...................................................... 16


Introduction .......................................................................................................................................... 16

The General Settings ............................................................................................................................ 16

The cmdOpenChildDisplay_Click Event ............................................................................................... 16

Revision History ............................................................................................................................... 18

iii
OVERVIEW
ABOUT THIS DOCUMENT
This document is exclusive to the OSIsoft Virtual Campus (vCampus) and is available on its
online Library, located at http://vCampus.osisoft.com/Library/library.aspx. As such, it is
provided 'as is' and is not supported by OSIsoft's regular Technical Support.

Any question or comment related to this document should be posted in the appropriate
vCampus discussion forum (http://vCampus.osisoft.com/forums) or sent to the vCampus
Team at vCampus@osisoft.com.

ABOUT THIS WHITE PAPER


This document contains a loose collection of various examples that can prove useful to
manipulate PI ProcessBook displays and objects. Some of these examples were previously
provided as standalone elements and were re-written and grouped for clarity purposes.

VBA allows a user to build displays that modify themselves based on an event. This event
can be a mouse click as well as the receiving of a new value in a PI Point.

WHAT YOU NEED TO START


The VBA scripts have been developed with the following product:

PI ProcessBook 3.2

1
"ONE-CLICK VALUE TREND" VBA SCRIPT
INTRODUCTION

The "One-Click Value Trend" VBA script places a displayed value into a PI ProcessBook trend
when it is selected. You can access a trend of any value in your display.This VBA script
references a Trend object named PointTrend on the display. In your own displays, you could either
modify the VBA script to reference a trend with a different name or rename your Trend object to
PointTrend:

THE GENERAL SETTINGS


The Option Explicit statement forces the declaration of all variables.

' Make sure we define all our variables


Option Explicit

THE DISPLAY_OPEN EVENT


In the Display_Open event we set the time range of the trend when the file gets opened.

Private Sub Display_Open()


' Reset the trend time range to be one day each time display is opened.
Call ThisDisplay.PointTrend.SetStartAndEndTime("*-1d", "*")
End Sub

2
THE DISPLAY_CLICK EVENT
1. We select the Display_Click event:

2. And declare some variables:


' The PI Server name
Dim strPIServername As String
' The PI Point name in the selected Value
Dim strPITagname As String
' The Start Time of the Trend
Dim strTrendStartTime As String
' The End Time of the Trend
Dim strTrendEndTime As String
' Status
Dim Success As Boolean
' The Symbols collection
Dim MySymbols As SelectedSymbols
' One Symbol
Dim MySymbol As Symbol

3. Now we get a reference of the selected symbols collection and check if there any are
selected :
' Set selected symbols object to the selected symbols collection.
Set MySymbols = ThisDisplay.SelectedSymbols

' Check to see how many are selected.


If MySymbols.Count = 0 Then
' If the count is zero, user clicked display background, do nothing.
Exit Sub
End If

4. As we have the collection of symbols, we loop through it and search for a value
symbol and modify the trend object accordingly:
For Each MySymbol In MySymbols
' If symbol object is type pbSymbolValue, it is a value object.
If MySymbol.Type = pbSymbolValue Then
' Get the tagname and trend it.
strPITagname = MySymbol.GetTagName(1)
' Pick up the current trend time range.
strTrendStartTime = ThisDisplay.PointTrend.StartTime
strTrendEndTime = ThisDisplay.PointTrend.EndTime
' If selected tag is not the current one in trend, put it there.
If Not (PointTrend.GetTagName(1) = strPITagname) Then
' Remove old point trace from trend.
PointTrend.RemoveTrace(1)
' Add trace for this tag to trend ( using format \\severname\tagname )
PointTrend.AddTrace(strPITagname)
' Refresh time range, setting
Call PointTrend.SetStartAndEndTime(strTrendStartTime, strTrendEndTime)
End If

5. In addition, we can use the PI SDK to add some PI Point information to the trend
title. In order to do this, we have to reference the PI SDK:

3
6. Then we can use PI SDK objects:
' If you plan to use this script to enhance displaysviewed
' in PI ProcessBook, you can use the PI SDK.
'
' NOTE: You will need to add a reference to the PI SDK libraries
' to your PI ProcessBook VBA
' project.

' Strip out PI Server name ( used in Option 2 only).


strPIServername = Mid(strPITagname, 3, InStr(3, strPITagname, "\") - 3)

' Strip out PI Tag name.


strPITagname = Right(strPITagname, _
Len(strPITagname) - _
InStr(3, strPITagname, "\"))

' Set the Trend title to the Descriptor.


PointTrend.TrendTitle = PISDK.Servers(strPIServername). _
PIPoints(strPITagname). _
PointAttributes. _
Item("Descriptor")

7. And finally we set the trace scale to "Autorange" and finish the loop:
' Refresh trend Y-axis scale.
Success = PointTrend.SetTraceScale("Autorange", "Autorange")
Exit Sub
End If
Next MySymbol

4
"ONE-CLICK VALUE AD HOC TREND" VBA SCRIPT
INTRODUCTION

This VBA script automates the "ad hoc trending" functionality of PI ProcessBook. When you
click any value in the display, an ad hoc trend appears.

THE GENERAL SETTINGS


The Option Explicit statement forces the declaration of all variables.

' Make sure we define all our variables


Option Explicit

THE DISPLAY_OPEN EVENT


In the Display_Open routine we set the time range of the Display to 1 day when the file gets opened.

Private Sub Display_Open()


' Reset the trend time range to be one day each time display is opened.
Call ThisDisplay.PointTrend.SetStartAndEndTime("*-1d", "*")
End Sub

THE DISPLAY_CLICK EVENT


1. We select the Display_Click procedure:

2. And declare some variables:


Dim pbSymbols As SelectedSymbols
Dim pbSymbol As Symbol
Dim pbBar As PBCommandBar
Dim pbButton As PBCommandBarButton

3. Now we get the selected symbols object and check if there are selected symbols at
all:
5
' Set selected symbols collection object to the
' selected symbols currently on ThisDisplay.
Set pbSymbols = ThisDisplay.SelectedSymbols

' Check to see how many are selected.


If pbSymbols.Count = 0 Then
' If the count is zero, user clicked display background, do nothing.
Exit Sub
End If

4. As we have the collection of symbols, we search for all value symbols:


' Look through selected symbols for a value object, trend first one found.
For Each pbSymbol In pbSymbols
' If symbol object is type 7, by definition its a value object.
If pbSymbol.Type = pbSymbolValue Then

5. Get the Standard Toolbar object:


' Grab PI ProcessBook's "Standard Toolbar"
Set pbBar = Application.CommandBars.Item("Standard Toolbar")

6. Get the Trend Display button


' Set the button object to the "Trend Display" button within that toolbar.
Set pbButton = pbBar.Controls.Item("Trend Display")

7. And “push” it from code:


' Programatically "push" the button.
Call pbButton.Execute()

8. Time to finish the loop:


Exit Sub
End If
Next pbSymbol

6
CREATING XYPLOTS PROGRAMMATICALLY
INTRODUCTION

The following VBA script creates several PI ProcessBook objects and populates them with tags
retrieved by a simple PI SDK call. The purpose of this example is to show you how to create display
objects programmatically instead of drawing them manually. The advantage of the programmatic
approach gets obvious if the number of objects increases.

This VBA script was inspired by a customer in training who asked for an option to create XYPlots
where ten tags compare to each other. If the number of tags to trend is n, you can simply calculate
that the number of XYPlot is n(n-1)/2 so for 10 tags this will be 45 XYPlots to draw.

THE GENERAL SETTINGS


1. The script uses the PI SDK to retrieve the PointList. In order to do this, we have to
reference the PI SDK:

2. The Option Explicit statement forces the declaration of all variables.


' Make sure we define all our variables
Option Explicit

7
3. We define some constants. These constants define the size of the XYPlot symbol, the
time range of the trend, the tag mask and the PI Server.
' Heigth of symbol
Const cHeigth = 600
' Width of symbol
Const cWidth = 600
' The timerangefor our symbols
Const strStartTime = "Y"
Const strEndTime = "T"
' The taglist we use to build our symbols
Const strWhereClause = "Tag='sin*'"
' The PI Server. make sureit is already in the known server list!
Const strServer = "ANDREASPC"

THE COMMAND BUTTON


1. To run our VBA script we will use a Command Button:

2. And we give it a friendly name of CreateButton (right-click on it when it Build mode,


click Properties and change its name):

THE CREATEBUTTON_CLICK EVENT


1. In the VBA environment, select the CreateButton_Click procedure:

8
2. First we disable the redrawing to reduce the load:
' Improve the performance by turning off
' redrawing until we have drawn all our symbols
Application.Redraw = False

3. And declare some variables:


' We are going to create XYplots!
Dim MyXYPlot As XYPlot

' Some loop variables


Dim a, b, i As Long

' We want to arrange the plots nicely in a square


Dim iConnections As Long

' The number of tags weare going to use


Dim TagMaxNumber1, TagMaxNumber2 As Long

' The PI Server


Dim MyPIServer As PISDK.Server

4. Initialize the PI Server object and connect to it:


' Initialize the PI Server object
Set MyPIServer = pisdk.Servers.Item(strServer)

' Open the connection


Call MyPIServer.Open()

5. Create the PointList and initialize it with the tags based on the tag mask:
' The point list
Dim MyPointList As pisdk.PointList

' Initialize the point list with all our tags


' that correspond to the mask defined above
Set MyPointList = MyPIServer.GetPoints(strWhereClause)

6. Get the count, limit it to 15 (to reduce the number of symbols) and calculate how to
get them best arranged as a square of symbols:
' Get the count
TagMaxNumber1 = MyPointList.Count

' With 15 tags we already get > 100 XY plots,


' if we don't limit the amount, we will have performance issues
If TagMaxNumber1 > 15 Then
MsgBox("Too many tags! Using only first 15 tags.")
TagMaxNumber1 = 15
End If

' Calculate the connections: n x (n-1)/2


iConnections = TagMaxNumber1 * (TagMaxNumber1 - 1) / 2

' As mentioned, we want to have a nice square of trends,


' so we calculate the square root

9
TagMaxNumber2 = Sqr(iConnections)

' Initialize our counter


i = 0

7. Now we iterate through all the tags and create an XYPlot symbol:
' Get an XY plot for each tag with each tag;-)
' from the first to the last tag
For a = 1 To TagMaxNumber1
' With each other tag
For b = (a + 1) To TagMaxNumber1
' Add an XY plot
Set MyXYPlot = ThisDisplay.Symbols.Add(pbSymbolXYPlot)

8. We cannot simply add a trace to a XYPlot object directly. You have to add tags to the
collection that is part of the XYDefinition object:
' The XY definition
Dim MyDefinition As XYDefinition
' Initialize the XY definition
Set MyDefinition = MyXYPlot.GetDefinition

' Add the two tags


MyDefinition.Tags.Add("\\" & MyPIServer.Name & "\" & yPointList.Item(a))
MyDefinition.Tags.Add("\\" & MyPIServer.Name & "\" & MyPointList.Item(b))

' Apply to our XY plot


Call MyXYPlot.SetDefinition(MyDefinition)

9. So let us move the XYPlot to the appropriate position and adjust its size:
' Move it to the right place and the right size
MyXYPlot.Left = -14950 + (((i Mod TagMaxNumber2) + 1) * (cWidth + 5))
MyXYPlot.Top = 14950 - (((i \ TagMaxNumber2)) * (cHeigth + 5))
MyXYPlot.Height = cHeigth
MyXYPlot.Width = cWidth

10. Adjust the time range and don’t forget to count the XYPlot (in favor of some complex
mathematics I simply count the XYPlot to arrange them in a square ;-)):
' Set the time
Call MyXYPlot.SetTimeRange(strStartTime, strEndTime)

' Count!
i = i + 1

11. Close the loop and switch on drawing:


Next b
Next a
' Now we turn drawing back on
Application.Redraw = True

ThisDisplay.Zoom = “FitAll”

THE DISPLAY_DATAUPDATE EVENT


100 XYPlots might be not too easy to check – how about some logic to simplify the task?

10
1. Let's use the Display_DataUpdate event to analyze all of our XYPlots when they
update (You may wonder why we don’t do that when we create them – well, the
statistics are not updated after you set the definition, so you have to wait for the
data update) and declare some variables:
' We want to access the XY statistic
' this should be done after the DataUpdate

' The symbols


Dim MySymbol As Symbol
Dim MyXYPlot As XYPlot

2. Again we iterate through all the symbols on the display:


' Search for all symbols on the display
For Each MySymbol In ThisDisplay.Symbols
' Is it an XY plot?
If MySymbol.Type = pbSymbolXYPlot Then

' Initialize our XY plot


Set MyXYPlot = MySymbol

3. And access the XY statistics:


' The statistics
Dim MyXYStat As XYStat

' Initialize the statistics


' we have only one so don't be too smart ;-)
Set MyXYStat = MyXYPlot.Stats.Item(1)

4. As a simple example we modify the BackgroundColor of the XYPlots to identify the


ones that have a CorrelationCoefficient > 0.5:
' Set each XY Plot with CorrelationCoefficient > 0.5 to white
' Others go green
If Abs(MyXYStat.CorrelationCoefficient) > 0.5 Then
MyXYPlot.BackgroundColor = vbWhite
Else
MyXYPlot.BackgroundColor = vbGreen
End If
End If
Next MySymbol

11
“SETVIEWPORT” VBA CODE SNIPPET
INTRODUCTION
PI ProcessBook displays can be huge and the amount of information overwhelming. With the help of
VBA we can zoom the view to a certain area to catch the eye of the observer. In this example we will
use a digital tag (CDM158) to drive the visible area.

THE GENERAL SETTINGS


The Option Explicit statement forces the declaration of all variables.

' Make sure we define all our variables


Option Explicit

THE DISPLAY_OPEN EVENT


In the Display_Open routine we set the size of the Display and the ViewPort.

Private Sub Display_Open()


' Preset
ThisDisplay.Width = 600
ThisDisplay.Height = 450
ThisDisplay.Zoom = 50
' Reset the trend time range to be one day each time display is opened.
Call ThisDisplay.SetViewPort(15000, -15000, 2000, 3000)
End Sub

THE VALUE1_DATAUPDATE EVENT


After we add a Value object to a display we can use the Value1_DataUpdate event for our
example:

Private Sub Value1_DataUpdate()


' If you have a big screen, and you want
' to Zoom in based on an event.
Select Case ThisDisplay.Value1.GetValue(vrDate, vrStatus)
Case "Cascade"
Call ThisDisplay.SetViewPort(14000, -15000, 1000, 1500)
Case "Program"
Call ThisDisplay.SetViewPort(14000, -13500, 1000, 1500)
Case "Prog-Auto"
Call ThisDisplay.SetViewPort(15000, -13500, 1000, 1500)
Case "Manual"
Call ThisDisplay.SetViewPort(15000, -15000, 1000, 1500)
Case "Prog-Auto"
Call ThisDisplay.SetViewPort(15000, -15000, 1000, 1500)
Case Else
Call ThisDisplay.SetViewPort(15000, -15000, 2000, 3000)
End Select
End Sub

12
“MODIFIED” PROPERTY
INTRODUCTION
The PI ProcessBook Display class exposes a property called Modified. Simply catch the
BeforeClose event of the Display and set the Modified property to False. PI ProcessBook
will not ask you to save the changes.

This can be handy if your users are allowed to change the display but you neither want them to safe
the changes nor bother them with the question.

THE GENERAL SETTINGS


The Option Explicit statement forces the declaration of all variables.

' Make sure we define all our variables


Option Explicit

THE DISPLAY_BEFORECLOSE EVENT


In the Display_BeforeClose routine we set the modified property of the Display to false:

Private Sub Display_BeforeClose(bCancelDefault As Boolean)


' Do not save changes
ThisDisplay.Modified = False
End Sub

13
PASS THE CONTEXT FROM PARENT TO CHILD
(MODULE RELATIVE DISPLAY)
INTRODUCTION

In this example we will play with the concept of a Module-Relative Display (MRD), which consists of
a unique display that can represent data from a list of similar Modules (as opposed to creating one
display per Module). Looking at assets in a "top-down" approach is not uncommon and therefore
one might be interested in opening a child display from another display (i.e. the parent). In this
scenario, passing the "module context" (i.e. the Module you were looking at) from the parent display
to the child display might prove useful, such that the user does not have to re-select the desired
Module from the list.

To illustrate the functionality we have built two displays: ParentDisplay.PDI with a Microsoft Forms
2.0 CommandButton and a Module Relative Trend showing an Alias and ChildDisplay.PDI with a
Module Relative Trend showing an Alias. Both displays use the same modules and we will use the
Microsoft Forms 2.0 CommandButton named cmdOpenChildDisplay to open the child display.

THE GENERAL SETTINGS


The Option Explicit statement forces the declaration of all variables.

' Make sure we define all our variables


Option Explicit

THE CMDOPENCHILDDISPLAY_CLICK EVENT


The cmdOpenChildDisplay_Click gets fired when the user hits the Command button In the Display.

Private Sub cmdOpenChildDisplay_Click()

End Sub

1. First we get the path to the current display and remove the filename:
' This will hold the absolute path to the display,
' exluding fileame
Dim myPath As String

14
' Get the path from this display, excluding filename
myPath = ThisDisplay.Path
myPath = Left(myPath, InStrRev(myPath, "\", -1, vbTextCompare))

2. Next we get our own object for ThisDisplay:


' Get the current display
Dim myParentDisplay As Display
Set myParentDisplay = ThisDisplay

3. And the context handlers:


' The context handlers
Dim MrdContextHandler As ContextHandler
Set MrdContextHandler = Application.ContextHandlers("ModuleContext")
Dim AliasContextHandler As ContextHandler
Set AliasContextHandler = Application.ContextHandlers("Alias")
Dim PropContextHandler As ContextHandler
Set PropContextHandler = Application.ContextHandlers("Property")

4. And open the child display:


' This will be the Child Display
Dim myChildDisplay As Display
' Open the child display
Set myChildDisplay = Application.Displays.Open(myPath & "ChildDisplay.PDI", True)

5. Now we get the context handlers in sync:


' Set all three context handlers to have thesame context in Child and Parent
MrdContextHandler.CurrentContext(myChildDisplay) = _
MrdContextHandler.CurrentContext(myParentDisplay)

AliasContextHandler.CurrentContext(myChildDisplay) = _
AliasContextHandler.CurrentContext(myParentDisplay)

PropContextHandler.CurrentContext(myChildDisplay) = _
PropContextHandler.CurrentContext(myParentDisplay)

15
PASS THE CONTEXT FROM PARENT TO CHILD
(ELEMENT RELATIVE DISPLAY)
INTRODUCTION

In this example we will play with the concept of an Element-Relative Display (ERD), which consists of
a unique display that can represent data from a list of similar AF Elements (as opposed to creating
one display per AF Element). Looking at assets in a "top-down" approach is not uncommon and
therefore one might be interested in opening a child display from another display (i.e. the parent). In
this scenario, passing the "element context" (i.e. the AF Element you were looking at) from the
parent display to the child display might prove useful, such that the user does not have to re-select
the desired element from the list.

To illustrate the functionality we have built two displays: ParentDisplayERD.PDI with a Microsoft
Forms 2.0 CommandButton and an Element Relative Trend showing an Attribut and
ChildDisplayERD.PDI with an Element Relative Trend showing an Attribute. Both displays use the
same AF Elements and we will use the Microsoft Forms 2.0 CommandButton named
cmdOpenChildDisplay to open the child display.

THE GENERAL SETTINGS


The Option Explicit statement forces the declaration of all variables.

' Make sure we define all our variables


Option Explicit

THE CMDOPENCHILDDISPLAY_CLICK EVENT


The cmdOpenChildDisplay_Click gets fired when the user hits the Command button In the Display.

Private Sub cmdOpenChildDisplay_Click()

End Sub

6. First we get the path to the current display and remove the filename:

16
' This will hold the absolute path to the display,
' exluding fileame
Dim myPath As String

' Get the path from this display, excluding filename


myPath = ThisDisplay.Path
myPath = Left(myPath, InStrRev(myPath, "\", -1, vbTextCompare))

7. Next we get our own object for ThisDisplay:


' Get the current display
Dim myParentDisplay As Display
Set myParentDisplay = ThisDisplay

8. And the context handler:


' The context handlers
Dim ErdContextHandler As ContextHandler
Set ErdContextHandler = Application.ContextHandlers("E")

9. And open the child display:


' This will be the Child Display
Dim myChildDisplay As Display
' Open the Childdisplay
Set myChildDisplay = Application.Displays.Open(myPath & "ChildDisplayERD.PDI", True)

10. Now we get the context handler in sync:


' Set all three context handlers to have thesame context in Child and Parent
ErdContextHandler.CurrentContext(myChildDisplay) = _
ErdContextHandler.CurrentContext(myParentDisplay)

Note: The code is almost identical to the module context, except that you have only one context
(not the one for alias and property), and its name is “E”.

17
REVISION HISTORY

2006 Initial DevNet version by Curt Hertler (Click Value AdHocTrend) and Tom Hosea
(Click Value Trend)

09-Mar-09 AS> Conversion to vCampus format

09-Mar-09 AS> Minor changes

10-Mar-09 AS> added XYPlot

10-Aug-09 SP> Minor changes

05-May-10 AS> Minor fixes in the code examples, some updates:


- SetViewPort
- Modified property
- Module Context
- Element Context

12-May-10 AS> Minor changes

18

You might also like