My First VBA Project For CATIA V6

Print Friendly, PDF & Email

My First VBA Project For CATIA V6

In this post we will create a new 3DPart, add a new Geometrical set and then create a Point by Coordinates. Finally, we will build a simple user interface that will allow us to add additional geometrical sets and points.

Creating a New Macro Library

To get started launch the Visual Basic Editor from within CATIA, typically the Short cut keys Alt+F11 will do this, not only in CATIA but PowerPoint, Excel, Word etc..

Visual Basic Editor

When the Dialogue window displays select Yes to create or Open and Existing VBA Project.

Create or Open VBA Project

Within the Macro Library’s Dialogue window select Create New Library

Create New Library

Within the 3DExperience Platform the VBA Library’s are stored as objects unlike V5 where the VBA project is just stored on the file system.

3DExperience VBA Library Object

The VBA IDE application will now open allowing you to create and edit your code.

VBA IDE

Creating a New 3DShape

Insert a new Module, within which we will write the code. To insert a new Module Right Mouse Click on the library and select Insert->Module from the secondary contextual menu.

Create New Module

Within the Property’s panel we can rename the new Module to “PointBuider”.

Module Name

To get started we have to create the main Subroutine that CATIA will execute and it must be called CATMain. This is actually enough to execute, not that it will do anything.

Sub CATMain()
  
  
End Sub
Sub CATMain

Let start of by getting the CATIA Application object, from this we can traverse down the class hierarchy, to the class that will allow us to create a new 3DShape.

Sub CATMain()

    Dim ioCATIA As Application
    Set ioCATIA = CATIA

End Sub

PLMNewService

In CATIA V6 there are no longer documents on the file system, everything is stored within the PLM system. As a result we have to use the PLM system to create new objects for us. The way in which Dassault Systems has done this is through Services, there are Session Services and Editor Services we want to access the Session Services.

Application Services

Typically to navigate from one object (Class) to another we need to first declare an object of that type in memory and then navigate from the parental object to the child object. Currently we have the application object called “ioCATIA” so to navigate to the Service object we simply concatenate the two together with a period.

Sub CATMain()

    Dim ioCATIA As Application
    Set ioCATIA = CATIA
    
    Dim ioAppServices As services
    Set ioAppServices = ioCATIA.services

End Sub

This is typically the process but in this case notice the Red color of the Service node, the “GetSessionService” text to the left of the Service node and the arrow below the node along with the list of types. This means we have to use the Method “GetSessionService” that belongs to the Application object to retrieve a Session service of a given Type.

Sub CATMain()

  Dim ioCATIA As Application
  Set ioCATIA = CATIA
    
  Dim ioPLMNewService As PLMNewService ' Declare in Memory a new Variable of type PLMNewService
  Set ioPLMNewService = ioCATIA.GetSessionService("PLMNewService") ' Get the Session Service by its Type Name

End Sub

So why is it we want this object? When we search in the DSYAutomation.CHM file found in the installation path, the PLMNewService object. We find that there are two methods we can use; PLMCreate and SetAttributeValue, that belong to this object. When we read the PLMCreate documentation we find it requires an input String (iUserType notice the “i” for input) and a Editor object as an output (notice the “o” for output i.e. oEditor).

We also find that we can either create a 3DShape or a Drawing. Currently there is no way to create a Physical Product or 3DPart.

PLMCreate

Using the ioPLMNewService object we created previously we can now use the PLMNewService API, by first creating a new variable of type Editor.

Sub CATMain()

    Dim ioCATIA As Application
    Set ioCATIA = CATIA
    
    Dim ioPLMNewService As PLMNewService
    Set ioPLMNewService = ioCATIA.GetSessionService("PLMNewService")
    
    Dim ioEditor As Editor 
    ioPLMNewService.PLMCreate "3DShape", ioEditor

End Sub

If we execute this code now, we will find a new 3DShape is created within our CTAIA V6 session.

Create New 3DShape

Creating a New Geometrical Set

Now we have a new 3DShape we need to traverse the object structure so that we can create a new geometrical set.

Active Object

This is where the Locals window is super useful, when we expand out the ioEditor object we can see below it there is an object called ActiveObject and below it the objects that make up a Part. Also tot he right in the Type column we can see that the type is AnyObject/Part which is super useful since we now know we must cerate a variable of type Part.

ActiveObject – Part

So to traverse down the structure from the ioEditor object, we must create a new object of type Part in this case called ioPart. We can then equate this to the ioEditor.ActiveObject. So to walk down the tree we just concatenate the two objects with a period, remembering to equate this to the correct type.

Sub CATMain()

    Dim ioCATIA As Application
    Set ioCATIA = CATIA
    
    Dim ioPLMNewService As PLMNewService
    Set ioPLMNewService = ioCATIA.GetSessionService("PLMNewService")
    
    Dim ioEditor As Editor
    
    ioPLMNewService.PLMCreate "3DShape", ioEditor
    
    Dim ioPart As Part
    Set ioPart = ioEditor.ActiveObject

End Sub

To create a new Geometrical Set, we actually want to create something called a HybridBody. If we look in the Part Object Model Map, we will find this object below the HybridBodies Collection object. So we must step down from the Part object to the HybridBodies object.

Part Object Model Map

Following the same process, lets create a new variable of type HybridBodies, and then equate it to ioPart.HybridBodies.

Sub CATMain()

    Dim ioCATIA As Application
    Set ioCATIA = CATIA
    
    Dim ioPLMNewService As PLMNewService
    Set ioPLMNewService = ioCATIA.GetSessionService("PLMNewService")
    
    Dim ioEditor As Editor
    
    ioPLMNewService.PLMCreate "3DShape", ioEditor
    
    Dim ioPart As Part
    Set ioPart = ioEditor.ActiveObject
    
    Dim ioHybridBodies As HybridBodies
    Set ioHybridBodies = ioPart.HybridBodies

End Sub

If we now look at the HybridBodies object, we can see that there is an Add method that we can use to create a New HybridBody. Importantly, if we read closely, we can see Func Add() As Hybridbody so it actually tells us that the Add method is a Function that returns a Hybridbody.

HybridBodies Methods

Since its a function it returns something, so we must create a variable of that type before using the function, in this case the type is Hybridbody.

Sub CATMain()

    Dim ioCATIA As Application
    Set ioCATIA = CATIA
    
    Dim ioPLMNewService As PLMNewService
    Set ioPLMNewService = ioCATIA.GetSessionService("PLMNewService")
    
    Dim ioEditor As Editor
    
    ioPLMNewService.PLMCreate "3DShape", ioEditor
    
    Dim ioPart As Part
    Set ioPart = ioEditor.ActiveObject
    
    Dim ioHybridBodies As HybridBodies
    Set ioHybridBodies = ioPart.HybridBodies
    
    Dim ioHybridBody As HybridBody
    Set ioHybridBody = ioHybridBodies.Add()

End Sub

If we run this code now, we will get a new 3DPart with a new Geomatical Set within it.

New 3DPart and Geometrical Set

Finally ,we want to change the name of the Geometrical Set. If we look at the documentation for HybridBody there is no Name property. However HybridBody inherits from System.AnyObject, which inherits from System.CATBaseDispatch etc.

HybridBody Object

If we look at AnyObject we can see there is a property called Name which either Gets or Sets the Name of the HybridBody object.

AnyObject Object

So we can simply use this property and equate it to a string for the name of the Geometrical Set.

Sub CATMain()

    Dim ioCATIA As Application
    Set ioCATIA = CATIA
    
    Dim ioPLMNewService As PLMNewService
    Set ioPLMNewService = ioCATIA.GetSessionService("PLMNewService")
    
    Dim ioEditor As Editor
    
    ioPLMNewService.PLMCreate "3DShape", ioEditor
    
    Dim ioPart As Part
    Set ioPart = ioEditor.ActiveObject
    
    Dim ioHybridBodies As HybridBodies
    Set ioHybridBodies = ioPart.HybridBodies
    
    Dim ioHybridBody As HybridBody
    Set ioHybridBody = ioHybridBodies.Add()
    
    ioHybridBody.Name = "MyNewGeometricalSet"

End Sub

Creating a New Point by Coordinate

So now we have somewhere to create the point within the new geometrical set, but how do we do that? If we go back and look at the Part Object, we can see all the objects that are associated to the part. There are three Factories that are important, HybridShapeFactory (Wireframe and Surface) , InstanceFactory (Instanciation of UDF’s and Powercopies), and ShapeFactory (Part Design). In this case we want to use the HybridShapeFactory. These factory’s are below an abstract Factory object, which all factory’s inherit from. We can navigate from the Part object to the HybridShapeFactory directly i.e. ioPart.HybridShapeFactory.

Factory Object

As before we have to create a space in memory for the HybridShapeFactory and then we can fill this space with that object.

Sub CATMain()

    Dim ioCATIA As Application
    Set ioCATIA = CATIA
    
    Dim ioPLMNewService As PLMNewService
    Set ioPLMNewService = ioCATIA.GetSessionService("PLMNewService")
    
    Dim ioEditor As Editor
    
    ioPLMNewService.PLMCreate "3DShape", ioEditor
    
    Dim ioPart As Part
    Set ioPart = ioEditor.ActiveObject
    
    Dim ioHybridBodies As HybridBodies
    Set ioHybridBodies = ioPart.HybridBodies
    
    Dim ioHybridBody As HybridBody
    Set ioHybridBody = ioHybridBodies.Add()
    
    ioHybridBody.Name = "MyNewGeometricalSet"
    
    Dim ioHybridShapeFactory As HybridShapeFactory
    Set ioHybridShapeFactory = ioPart.HybridShapeFactory

End Sub

Within the HybridShapeFactory documentation, we can find the method documentation for AddNewPointCoord. We can see that this is a Func that returns a HybridShapePointCoord. We have to supply three Double’s for X, Y, and Z.

Add New Point Coord
Sub CATMain()

    Dim ioCATIA As Application
    Set ioCATIA = CATIA
    
    Dim ioPLMNewService As PLMNewService
    Set ioPLMNewService = ioCATIA.GetSessionService("PLMNewService")
    
    Dim ioEditor As Editor
    
    ioPLMNewService.PLMCreate "3DShape", ioEditor
    
    Dim ioPart As Part
    Set ioPart = ioEditor.ActiveObject
    
    Dim ioHybridBodies As HybridBodies
    Set ioHybridBodies = ioPart.HybridBodies
    
    Dim ioHybridBody As HybridBody
    Set ioHybridBody = ioHybridBodies.Add()
    
    ioHybridBody.Name = "MyNewGeometricalSet"
    
    Dim ioHybridShapeFactory As HybridShapeFactory
    Set ioHybridShapeFactory = ioPart.HybridShapeFactory

    Dim ioHybridShapePointCoord As HybridShapePointCoord
    Set ioHybridShapePointCoord = ioHybridShapeFactory.AddNewPointCoord(10, 20, 30)
    
End Sub

If we execute this code we will created the point but it will not be added to the specification tree.

Looking through the inheritance hierarchy for HybridShapePointCoord you will not find any methods allowing you to add the point to the specification tree. However we will find a Compute method that allows to to pre-update the new object, well come back to appending the point to the specification tree.

Compute Method

Its often worth navigating some of the inheritance links to see what methods are hidden away, when writing this I found one AppendHybridShape which i will discuss much later on ion another post.

HybridShape Compute

And if we Navigate to the Compute method, well find its a Subroutine, so all we have to do is call it since it does not return anything like a Function.

Compute

I also renamed the point, this is just the same as renaming the geometrical set.

Sub CATMain()

    Dim ioCATIA As Application
    Set ioCATIA = CATIA
    
    Dim ioPLMNewService As PLMNewService
    Set ioPLMNewService = ioCATIA.GetSessionService("PLMNewService")
    
    Dim ioEditor As Editor
    
    ioPLMNewService.PLMCreate "3DShape", ioEditor
    
    Dim ioPart As Part
    Set ioPart = ioEditor.ActiveObject
    
    Dim ioHybridBodies As HybridBodies
    Set ioHybridBodies = ioPart.HybridBodies
    
    Dim ioHybridBody As HybridBody
    Set ioHybridBody = ioHybridBodies.Add()
    
    ioHybridBody.Name = "MyNewGeometricalSet"
    
    Dim ioHybridShapeFactory As HybridShapeFactory
    Set ioHybridShapeFactory = ioPart.HybridShapeFactory

    Dim ioHybridShapePointCoord As HybridShapePointCoord
    Set ioHybridShapePointCoord = ioHybridShapeFactory.AddNewPointCoord(10, 20, 30)
    
    ioHybridShapePointCoord.Compute
    ioHybridShapePointCoord.Name = "MyNewPoint"
    
End Sub

Back to appending the point to the geometrical set, and when you say it like this we can make a guess that the method we need is on the geometrical set object (HybridBody).

Append HybridShape

If we look at this method, again its a Subroutine so we can simply call the method and pass in the HybridShape to append.

Append HybridShape

In the documentation it shows parenthesis around the HybridShape being passed in, in this case the HybridShapePointCoord. Since its a subroutine and there is no equals symbol then the parenthesis are not required.

Sub CATMain()

    Dim ioCATIA As Application
    Set ioCATIA = CATIA
    
    Dim ioPLMNewService As PLMNewService
    Set ioPLMNewService = ioCATIA.GetSessionService("PLMNewService")
    
    Dim ioEditor As Editor
    
    ioPLMNewService.PLMCreate "3DShape", ioEditor
    
    Dim ioPart As Part
    Set ioPart = ioEditor.ActiveObject
    
    Dim ioHybridBodies As HybridBodies
    Set ioHybridBodies = ioPart.HybridBodies
    
    Dim ioHybridBody As HybridBody
    Set ioHybridBody = ioHybridBodies.Add()
    
    ioHybridBody.Name = "MyNewGeometricalSet"
    
    Dim ioHybridShapeFactory As HybridShapeFactory
    Set ioHybridShapeFactory = ioPart.HybridShapeFactory

    Dim ioHybridShapePointCoord As HybridShapePointCoord
    Set ioHybridShapePointCoord = ioHybridShapeFactory.AddNewPointCoord(10, 20, 30)
    
    ioHybridShapePointCoord.Compute
    ioHybridShapePointCoord.Name = "MyNewPoint"
    
    ioHybridBody.AppendHybridShape ioHybridShapePointCoord
    
End Sub

Now if we run this code we will have a new point.

New Point

Code Clean Up

To make this code a little more friendly we will reorganize it into logical groups so that we can independently create a new 3DShape, New Geometrical Set and new Point.

First lets create a Function that will create a new 3DShape if required. First we will get the PLMNewService and then using the error handler we will test to see if there is an active editor, and then if the active object is a part or not. Based on this testing we can decide if a new 3DShape should be created or if we ask the user if we need to create a new 3DShape.

Function CreateOrGet3DShape(ioCATIA As Application) As Part

    Dim ioPLMNewService As PLMNewService
    Set ioPLMNewService = ioCATIA.GetSessionService("PLMNewService")
    
    Dim ioEditor As Editor
    Dim ioPart As Part
    
    On Error Resume Next
    
        Set ioEditor = ioCATIA.ActiveEditor
        
        If (Err.Number <> 0) Then
            ioPLMNewService.PLMCreate "3DShape", ioEditor
        Else
            Set ioPart = ioEditor.ActiveObject
            If (Err.Number <> 0) Then
                ioPLMNewService.PLMCreate "3DShape", ioEditor
            Else
                If (MsgBox("Do You Want to Create a New 3DShape?", vbYesNo, "Create New 3DShape") = vbYes) Then
                    ioPLMNewService.PLMCreate "3DShape", ioEditor
                End If
            End If
            Set ioPart = ioEditor.ActiveObject
        End If
    
    On Error GoTo 0
    
    Set CreateOrGet3DShape = ioEditor.ActiveObject

End Function

Again using Error Handling we can try to get the Geometrical Set by its name, if an error is thrown then we know that the Geometrical Set does not exist. IN this case we will then create a new one and rename it.

Function CreateOrGetGeometricalSet(ioPart As Part, GeoSetName As String) As HybridBody

    Dim ioHybridBodies As HybridBodies
    Set ioHybridBodies = ioPart.HybridBodies
    
    On Error Resume Next
    
        Set CreateOrGetGeometricalSet = ioHybridBodies.Item(GeoSetName)
        
        If (Err.Number <> 0) Then
            Set CreateOrGetGeometricalSet = ioHybridBodies.Add()
            CreateOrGetGeometricalSet.Name = GeoSetName
        End If
      
    On Error GoTo 0

End Function

We will do something similar for the creation of the point, if the point already exists then well update the X, Y, Z and Name, otherwise well create a new point.

Function CreateOrGetPointCoord(ioPart As Part, ioHybridBody As HybridBody, iX As Double, iY As Double, iZ As Double, PointName As String) As HybridShapePointCoord

    Dim ioHybridShapeFactory As HybridShapeFactory
    Set ioHybridShapeFactory = ioPart.HybridShapeFactory
    
    Dim ioHybridShapes As HybridShapes
    Set ioHybridShapes = ioHybridBody.HybridShapes
    
    Dim PointArray(2)
    PointArray(0) = iX
    PointArray(1) = iY
    PointArray(2) = iZ
    
    On Error Resume Next
    
        Set CreateOrGetPointCoord = ioHybridShapes.Item(PointName)
        
        If (Err.Number <> 0) Then
            Set CreateOrGetPointCoord = ioHybridShapeFactory.AddNewPointCoord(iX, iY, iZ)
            CreateOrGetPointCoord.Compute
            ioHybridBody.AppendHybridShape CreateOrGetPointCoord
        Else
            Dim ExistingPoint As Variant
            Set ExistingPoint = CreateOrGetPointCoord
            ExistingPoint.SetCoordinates PointArray
            ExistingPoint.Compute
        End If
    
    On Error GoTo 0
    
    CreateOrGetPointCoord.Name = PointName
      
End Function

This simplifies our original code, and makes it much more extensible, this way we can use this in conjunction with a Form, which we will do next.

Sub CATMain()

    Dim ioCATIA As Application
    Set ioCATIA = CATIA
    
    Dim ioPart As Part
    Set ioPart = CreateOrGet3DShape(ioCATIA)
    
    Dim ioHybridBody As HybridBody
    Set ioHybridBody = CreateOrGetGeometricalSet(ioPart, "MyNewGeometricalSet")

    Dim ioHybridShapePointCoord As HybridShapePointCoord
    Set ioHybridShapePointCoord = CreateOrGetPointCoord(ioPart, ioHybridBody, 10, 20, 30, "MyNewPoint")
    
End Sub

Completed Code.

Sub CATMain()

    Dim ioCATIA As Application
    Set ioCATIA = CATIA
    
    Dim ioPart As Part
    Set ioPart = CreateOrGet3DShape(ioCATIA)
    
    Dim ioHybridBody As HybridBody
    Set ioHybridBody = CreateOrGetGeometricalSet(ioPart, "MyNewGeometricalSet")

    Dim ioHybridShapePointCoord As HybridShapePointCoord
    Set ioHybridShapePointCoord = CreateOrGetPointCoord(ioPart, ioHybridBody, 10, 20, 30, "MyNewPoint1")
    Set ioHybridShapePointCoord = CreateOrGetPointCoord(ioPart, ioHybridBody, 30, 40, 50, "MyNewPoint2")
  	Set ioHybridShapePointCoord = CreateOrGetPointCoord(ioPart, ioHybridBody, 50, 60, 70, "MyNewPoint3")
  
End Sub

Function CreateOrGetPointCoord(ioPart As Part, ioHybridBody As HybridBody, iX As Double, iY As Double, iZ As Double, PointName As String) As HybridShapePointCoord

    Dim ioHybridShapeFactory As HybridShapeFactory
    Set ioHybridShapeFactory = ioPart.HybridShapeFactory
    
    Dim ioHybridShapes As HybridShapes
    Set ioHybridShapes = ioHybridBody.HybridShapes
    
 	Dim PointArray(2) ' Using a Variant Array for to Update the Points Coordinates
    PointArray(0) = iX
    PointArray(1) = iY
    PointArray(2) = iZ
    
    On Error Resume Next
    
        Set CreateOrGetPointCoord = ioHybridShapes.Item(PointName)
        
        If (Err.Number <> 0) Then
            Set CreateOrGetPointCoord = ioHybridShapeFactory.AddNewPointCoord(iX, iY, iZ)
            CreateOrGetPointCoord.Compute
            ioHybridBody.AppendHybridShape CreateOrGetPointCoord
        Else
    		Dim ExistingPoint As Variant ' OOTB Bug This is How to Get Around it.
            Set ExistingPoint = CreateOrGetPointCoord
            ExistingPoint.SetCoordinates PointArray
            ExistingPoint.Compute
        End If
    
    On Error GoTo 0
    
    CreateOrGetPointCoord.Name = PointName
      
End Function

Function CreateOrGetGeometricalSet(ioPart As Part, GeoSetName As String) As HybridBody

    Dim ioHybridBodies As HybridBodies
    Set ioHybridBodies = ioPart.HybridBodies
    
    On Error Resume Next
    
        Set CreateOrGetGeometricalSet = ioHybridBodies.Item(GeoSetName)
        
        If (Err.Number <> 0) Then
            Set CreateOrGetGeometricalSet = ioHybridBodies.Add()
            CreateOrGetGeometricalSet.Name = GeoSetName
        End If
      
    On Error GoTo 0

End Function

Function CreateOrGet3DShape(ioCATIA As Application) As Part

    Dim ioPLMNewService As PLMNewService
    Set ioPLMNewService = ioCATIA.GetSessionService("PLMNewService")
    
    Dim ioEditor As Editor
    Dim ioPart As Part
    
    On Error Resume Next
    
        Set ioEditor = ioCATIA.ActiveEditor
        
        If (Err.Number <> 0) Then
            ioPLMNewService.PLMCreate "3DShape", ioEditor
        Else
            Set ioPart = ioEditor.ActiveObject
            If (Err.Number <> 0) Then
                ioPLMNewService.PLMCreate "3DShape", ioEditor
            Else
                If (MsgBox("Do You Want to Create a New 3DShape?", vbYesNo, "Create New 3DShape") = vbYes) Then
                    ioPLMNewService.PLMCreate "3DShape", ioEditor
                End If
            End If
            Set ioPart = ioEditor.ActiveObject
        End If
    
    On Error GoTo 0
    
    Set CreateOrGet3DShape = ioEditor.ActiveObject

End Function

Creating a User Interface

There are two steps when building a User Form; The User Form Layout and then the code behind, fortunately we’ve already built the code behind we just have t link it to the form values.

So lets build the form first start by inserting a new User Form object. This is done by right mouse clicking on the library and selecting Insert->User Form from the secondary contextual menu.

New User Form

Next we need some content, for this project we need 5 labels, 5 input boxes and a button. These can be added by selecting the control required form the Toolbox and then selecting approximately where you want it on the form. Once an object is on the form you can copy and paste them to make more if you need.

I did find a bug, I was missing the button command, i had to right mouse click in the Toolbox and select Additional Controls… in the Additional Controls window, I enabled Microsoft Outlook Command Button Control. This also turned on the Default Button Control was looking for, make sure you use CommandButton and Not OkCommandButton.

Building Out The Form

Next we need to make these look a little nicer by editing the Caption and Name fields in the property’s for each object, The Name Field will be used on the code side, so for a Label I use LBL_<Name>, for Buttons I use BTN_<Name> and so on, this will help while coding. For the Caption property its what you want to display on the form for example we need labels for Geometrical Set Name, Point Name and X, Y , Z values.

So we should end up with something that looks like this.

Finished Form

If you double click on the button, the code behind will be displayed.

Private Sub CMB_CreatePoint_Click()

End Sub

We can now copy and paste the code from the CATMain into this Subroutine for the button execution. This wont work yet we have to make some changes.

Private Sub CMB_CreatePoint_Click()

    Dim ioCATIA As Application
    Set ioCATIA = CATIA
    
    Dim ioPart As Part
    Set ioPart = CreateOrGet3DShape(ioCATIA)
    
    Dim ioHybridBody As HybridBody
    Set ioHybridBody = CreateOrGetGeometricalSet(ioPart, "MyNewGeometricalSet")

    Dim ioHybridShapePointCoord As HybridShapePointCoord
    Set ioHybridShapePointCoord = CreateOrGetPointCoord(ioPart, ioHybridBody, 10, 20, 30, "MyNewPoint1")
    Set ioHybridShapePointCoord = CreateOrGetPointCoord(ioPart, ioHybridBody, 30, 40, 50, "MyNewPoint2")
    Set ioHybridShapePointCoord = CreateOrGetPointCoord(ioPart, ioHybridBody, 50, 60, 70, "MyNewPoint3")
  
End Sub

This is where ensuring that the Name property for the controls was changed. For the Geometrical Set Name we need to link it to the Value of Text Box, where the user will key in the geometrical set name. In my case i renamed the control to TBX_GeoSetName and we can retreive the value in the text box by refering to the Value property.

    Dim ioHybridBody As HybridBody
    Set ioHybridBody = CreateOrGetGeometricalSet(ioPart, TBX_GeoSetName.Value)

We can repeat this for the other values required. Since the form data is all String data we have to convert it type Double for the X, Y, and Z that where the method CDBL() is used to Convert to Double (CDBL).

    Dim ioHybridShapePointCoord As HybridShapePointCoord
    Set ioHybridShapePointCoord = CreateOrGetPointCoord(ioPart, ioHybridBody, _
    CDbl(TBX_X.Value), CDbl(TBX_Y.Value), CDbl(TBX_Z.Value), TBX_PointName.Value)

If we Run the Form, we can create a New Point or Update an Existing One, however there are some issues with this Form, for example what happens if the user does not key in a value for the Point Name or X value. So we will have to do some code changes to improve robustness. In addition to this, while the form is active we can not do anything else in CATI, so we have to change the modal property’s of the Form..

Point Creation Form

Form Modal Property

When the Form is selected its Property’s are shown change the ShowModal property from True to False. This will allow the user to interact with CATIA and the Form not just the Form.

Modal Property

Value Validation

To ensure that all data is supplied we can validate that the Text Box fields are not empty strings, if any of them are well send a message to the user telling them that one or more fields are not populated.

Private Sub CMB_CreatePoint_Click()

    If (TBX_GeoSetName.Value <> "" And TBX_PointName.Value <> "" And _
    TBX_X.Value <> "" And TBX_Y.Value <> "" And TBX_Z.Value <> "") Then

        Dim ioCATIA As Application
        Set ioCATIA = CATIA
        
        Dim ioPart As Part
        Set ioPart = CreateOrGet3DShape(ioCATIA)
        
        Dim ioHybridBody As HybridBody
        Set ioHybridBody = CreateOrGetGeometricalSet(ioPart, TBX_GeoSetName.Value)
    
        Dim ioHybridShapePointCoord As HybridShapePointCoord
        Set ioHybridShapePointCoord = CreateOrGetPointCoord(ioPart, ioHybridBody, _
        CDbl(TBX_X.Value), CDbl(TBX_Y.Value), CDbl(TBX_Z.Value), TBX_PointName.Value)
    Else
        MsgBox ("Please Ensure That All Fields Are Filled In.")
    End If
    
End Sub

Default Values

For each of the Input Boxes, there is a Property called Text, we can populate this property with a Default Value to make the from a little more user friendly.

Default Values

Now when the Form is Run, we have default values for the fields.

Default Values

Only Allow Numeric Values

BY Double Clicking on an Input box in the Form we can access the code behind for the Text Box Change Event. If we do this for the X, Y , Z values we can add the following code to restrict value input to only numbers.

Private Sub TBX_X_Change()
    With Me.TBX_X
        If .Text Like "[!0-9]" Or Val(.Text) < -1 Or .Text Like "?*[!0-9]*" Then
            Beep
            .Text = Left(.Text, Len(.Text) - 1)
        End If
    End With
End Sub

Private Sub TBX_Y_Change()
    With Me.TBX_Y
        If .Text Like "[!0-9]" Or Val(.Text) < -1 Or .Text Like "?*[!0-9]*" Then
            Beep
            .Text = Left(.Text, Len(.Text) - 1)
        End If
    End With
End Sub

Private Sub TBX_Z_Change()
    With Me.TBX_Z
        If .Text Like "[!0-9]" Or Val(.Text) < -1 Or .Text Like "?*[!0-9]*" Then
            Beep
            .Text = Left(.Text, Len(.Text) - 1)
        End If
    End With
End Sub

Now we have Form that’s a little more robust, there always more things we can do such as inactive buttons or fields based on user input and interactivity but for now this is a good start.

Final Form Code

Private Sub CMB_CreatePoint_Click()

    If (TBX_GeoSetName.Value <> "" And TBX_PointName.Value <> "" And _
    TBX_X.Value <> "" And TBX_Y.Value <> "" And TBX_Z.Value <> "") Then

        Dim ioCATIA As Application
        Set ioCATIA = CATIA
        
        Dim ioPart As Part
        Set ioPart = CreateOrGet3DShape(ioCATIA)
        
        Dim ioHybridBody As HybridBody
        Set ioHybridBody = CreateOrGetGeometricalSet(ioPart, TBX_GeoSetName.Value)
    
        Dim ioHybridShapePointCoord As HybridShapePointCoord
        Set ioHybridShapePointCoord = CreateOrGetPointCoord(ioPart, ioHybridBody, _
        CDbl(TBX_X.Value), CDbl(TBX_Y.Value), CDbl(TBX_Z.Value), TBX_PointName.Value)
    Else
        MsgBox ("Please Ensure That All Fields Are Filled In.")
    End If
    
End Sub

Private Sub TBX_X_Change()
    With Me.TBX_X
        If .Text Like "[!0-9]" Or Val(.Text) < -1 Or .Text Like "?*[!0-9]*" Then
            Beep
            .Text = Left(.Text, Len(.Text) - 1)
        End If
    End With
End Sub

Private Sub TBX_Y_Change()
    With Me.TBX_Y
        If .Text Like "[!0-9]" Or Val(.Text) < -1 Or .Text Like "?*[!0-9]*" Then
            Beep
            .Text = Left(.Text, Len(.Text) - 1)
        End If
    End With
End Sub

Private Sub TBX_Z_Change()
    With Me.TBX_Z
        If .Text Like "[!0-9]" Or Val(.Text) < -1 Or .Text Like "?*[!0-9]*" Then
            Beep
            .Text = Left(.Text, Len(.Text) - 1)
        End If
    End With
End Sub