Community
Inventor Programming - iLogic, Macros, AddIns & Apprentice
Inventor iLogic, Macros, AddIns & Apprentice Forum. Share your knowledge, ask questions, and explore popular Inventor topics related to programming, creating add-ins, macros, working with the API or creating iLogic tools.
cancel
Showing results for 
Show  only  | Search instead for 
Did you mean: 

VBA: Distinguis​h hole features from other circles in drawing, add centermark​s.

4 REPLIES 4
SOLVED
Reply
Message 1 of 5
CragMonkey
2426 Views, 4 Replies

VBA: Distinguis​h hole features from other circles in drawing, add centermark​s.

I'm attempting to use VBA to put center marks on each hole in my drawing.

So far I have the following code:

    Dim oIntent As GeometryIntent
    Dim oCenterOfPart As Centermark
    
    'Add center marks to base view
    For Each oCurve In oBaseView.DrawingCurves ' <- need to identify Hole Features
        If Not oCurve.CenterPoint Is Nothing Then
            If oCurve.CurveType = kCircleCurve Then 'CurveTypeEnum
                Set oIntent = oSheet.CreateGeometryIntent(oCurve)
                Set oCenterOfPart = oSheet.Centermarks.Add(oIntent, True, True)
            End If
        End If
    Next oCurve
    
    'Add center marks to top view
    For Each oCurve In oTopView.DrawingCurves ' <- need to identify Hole Features
        If Not oCurve.CenterPoint Is Nothing Then
            If oCurve.CurveType = kCircleCurve Then 'CurveTypeEnum
                Set oIntent = oSheet.CreateGeometryIntent(oCurve)
                Set oCenterOfPart = oSheet.Centermarks.Add(oIntent, True, True)
            End If
        End If
    Next oCurve
    
    'Add center marks to right view
    For Each oCurve In oRightView.DrawingCurves ' <- need to identify Hole Features
        If Not oCurve.CenterPoint Is Nothing Then
            If oCurve.CurveType = kCircleCurve Then 'CurveTypeEnum
                Set oIntent = oSheet.CreateGeometryIntent(oCurve)
                Set oCenterOfPart = oSheet.Centermarks.Add(oIntent, True, True)
            End If
        End If
    Next oCurve

 

oBaseView is the DrawingView object representing the base view the code just placed. I also used VBA to place the projected views oTopView and oRightView. I want to add center marks to each hole when viewed from the end (as circles) and add centerlines when viewed from the top or side (as hidden lines).

 

I will be iterating through several models representing various handhold styles. The feet can be in many orientations, 99% of them are paralel to one of the origin planes (XY,YZ, or XZ).

 

This is what my code generates:

 

Capture.PNG

 

 (The centermarks that are selected are the ones I don't want the code to generate)

 

 This is what I WANT the code to generate:

Capture2.PNG

 

 

 1) How do I distinguish whether a circle curve originated because of a hole or because of another cilindrical feature?

2) How to I identify the correspoding hidden lines in the other views so I can add a center line?

 

(Reposted from: http://forums.autodesk.com/t5/Autodesk-Inventor/VBA-Distinguish-hole-features-from-other-circles-in-...)

4 REPLIES 4
Message 2 of 5
00ash00
in reply to: CragMonkey

Hi CragMonkey 

 

With my automatic drawing program I call up the automatedCenterlines, the same as if you were to RMB on each view and select automated center lines.  

 

Code:

oSheet is the active drawing sheet,


oSheet.DrawingViews.Item(1).SetAutomatedCenterlineSettings()
oSheet.DrawingViews.Item(2).SetAutomatedCenterlineSettings()
oSheet.DrawingViews.Item(3).SetAutomatedCenterlineSettings()

 

In your drawing template yo need to set your default Automated centerlines,

Tools > Document Settings > Automated Centerlines > Select required centerlines.

 

This should set all your default centerlines for the three views

 

Ash

 

Ash

Dell - T1650
Intel(R)Xeon(R) CPU E3-1290 V2 @ 3.70GHz
16GB
64-Bit
Windows 7 Pro
Inventor 2013 Build: 138
Message 3 of 5
CragMonkey
in reply to: 00ash00

The holes were created not by using the hole function, but instead by excluding that area during the extrusion. Inventor is seeing them both as "Cylindrical Features" - the result is the same as the other code.

 

However, when I create a hole table it knows the difference and correctly identifies the holes. I'm just not sure how to leverage that for this purpose.

Message 4 of 5
xiaodong_liang
in reply to: CragMonkey

Hi,

 

I did no find a direct way, but at least you can get DrawingCurve.ModelGeometry which is an edge. Next iterate Edge.Faces. If the face is a cylinder, get Face.CreateByFeature. Thus you can know if the feature is a hole feature or other features. Hope this helps.

Message 5 of 5
b.gyure
in reply to: CragMonkey

Hi CragMonkey 2000 !

 

I realize this is an old post but it might come in handy for others too. I was looking for the same thing so I wrote the code for it. Granted I'm not done, since I would need it for drawing which has an an assembly in it, so far I only did it for a drawing that has a part file in it. I'll try and finish it for both, for now with a part file, it works.
You might have to tweak it a bit for it to do for all of the sheets and all of the partfiles but I think that's going to be a piece of cake. Here is my code:

If you can use this please give a thumbs up, or accept it as a solution, thank you!

Sub CenterMark()

Dim oDrawDoc As DrawingDocument
Set oDrawDoc = ThisApplication.ActiveDocument

Dim oSheet As Sheet
Set oSheet = oDrawDoc.ActiveSheet

Dim oBaseView As DrawingView
Set oBaseView = oSheet.DrawingViews.Item(1)

Dim oDoc As PartDocument
Set oDoc = oBaseView.ReferencedDocumentDescriptor.ReferencedDocument

Dim oDef As PartComponentDefinition
Set oDef = oDoc.ComponentDefinition

Dim oHoleFeatures As HoleFeatures
Set oHoleFeatures = oDef.Features.HoleFeatures

Dim oColl As ObjectCollection
Set oColl = ThisApplication.TransientObjects.CreateObjectCollection

Dim oHole As HoleFeature
For Each oHole In oHoleFeatures

Dim oCurves As DrawingCurvesEnumerator
Set oCurves = oBaseView.DrawingCurves(oHole)
For Each oCurve In oCurves 'oBaseView.DrawingCurves ' <- need to identify Hole Features
If Not oCurve.CenterPoint Is Nothing Then
'If oCurve.Type = kHoleFeatureObject Then
If oCurve.CurveType = kCircleCurve Then 'CurveTypeEnum
Set oIntent = oSheet.CreateGeometryIntent(oCurve)
Set oCenterOfPart = oSheet.Centermarks.Add(oIntent, True, True)
End If
End If
Next oCurve
'oColl.Add (oCurves.Item(1)
'''IMMEDIATE WINDOW
Debug.Print oHole.Name, oCurves.Count
Next


' Dim oIntent As GeometryIntent
' Dim oCenterOfPart As CenterMark

'Dim oCurve As DrawingCurve
'Add center marks to base view

End Sub

 

And I wrote a delete centermark too, so we can play around:

 

 

Sub DeleteCenterMarks()


'Dim oDoc As DrawingDocument
Set oDoc = ThisApplication.ActiveDocument

Dim oSheet As Sheet
Set oSheet = oDoc.ActiveSheet

Dim oBaseView As DrawingView
Set oBaseView = oSheet.DrawingViews.Item(1)

Dim oCenterMark As CenterMark
For Each oCenterMark In oSheet.Centermarks
oCenterMark.Delete
Next
End Sub

 

centermark.PNG

Can't find what you're looking for? Ask the community or share your knowledge.

Post to forums  

Autodesk Design & Make Report