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 applying drawing dimensions

8 REPLIES 8
Reply
Message 1 of 9
alewer
3605 Views, 8 Replies

VBA applying drawing dimensions

I am wondering how best to apply drawing dimensions to a view. I am using VBA (Inventor 2010 x64) to modify a template skeletal assembly and save it. I have succeeded at generating the models, drawings, and drawing views, but have hit a wall when I attempt to automate the process of applying drawing dimensions.

I attempted to use GeneralDimensions.Retrieve with the DimensionsToRetrieve parameter, as I wish to retrieve only a few dimensions. My testing, however, indicated (and the helpfile confirmed) that the DimensionsToRetrieve parameter only work if the DimensionConstraint objects belong to a drawing sketch, and I'm retrieving dimensionconstraints from a model sketch. It appears to me that I will have to retrieve all dimensions and then somehow delete the unnecessary ones. This seems unusual to me--is there a better way? Can I, for example, retrieve a single dimensionconstraint at a time from the model rather than all of them at once? Perhaps I'm heading in the wrong direction to begin with: is anyone applying drawing dimensions without retrieving them from the model?

Thanks for any input.
8 REPLIES 8
Message 2 of 9
skyngu
in reply to: alewer

hi,

 

is there anyone has an example of this? I dont have any idea how DimensionsToRetrieve works.

 

thanks.

Autodesk Inventor Professional 2019
Message 3 of 9
Vladimir.Ananyev
in reply to: skyngu

If you can find the desired dimension constraints in your model then the rest is straightforward.  You should add these constraints to the object collection and call Retrieve method using this object collection as the second argument.  

The following VBA sample retrieves the first two dimentions from the first sketch in the part model that is referenced by the first drawing view in the first sheet in the active drawing document.

Private Sub RetrieveTest_1()
  
  Dim oDrawDoc As DrawingDocument
  Set oDrawDoc = ThisApplication.ActiveDocument
  
  Dim oSheet As Sheet
  Set oSheet = oDrawDoc.Sheets.Item(1)
  
  Dim oView As DrawingView
  Set oView = oSheet.DrawingViews.Item(1)
  
  'object collection for dimensions to be retrieved
  Dim oTO As TransientObjects
  Set oTO = ThisApplication.TransientObjects
  Dim oObjColl As ObjectCollection
  Set oObjColl = oTO.CreateObjectCollection
  
  'fill the object collection with some dimension constrains
  'Here we use sketch DimensionConstraint objects.
  Dim oDoc As PartDocument
  Set oDoc = oView.ReferencedDocumentDescriptor.ReferencedDocument
  Dim oDef As PartComponentDefinition
  Set oDef = oDoc.ComponentDefinition
  Dim oDimConstraints As DimensionConstraints
  Set oDimConstraints = oDef.Sketches.Item(1).DimensionConstraints
  
  Dim oDC As DimensionConstraint
  'add first two constraints to the collection
  Set oDC = oDimConstraints.Item(1)
  Call oObjColl.Add(oDC)  
  Set oDC = oDimConstraints.Item(2)
  Call oObjColl.Add(oDC)
  
  'retrieve subset of dimensions
  Call oSheet.DrawingDimensions.GeneralDimensions.Retrieve(oView, oObjColl)

'  'retrieve all the dimensions
'  Call oSheet.DrawingDimensions.GeneralDimensions.Retrieve(oView)

End Sub 'RetrieveTest_1

It is possible to locate desired dimension constraint object by model parameter name or you may use attached attribute.  See the overview article "Working with attributes" in Inventor API help.  


Vladimir Ananyev
Developer Technical Services
Autodesk Developer Network

Message 4 of 9
skyngu
in reply to: Vladimir.Ananyev

Thanks a lot!

 

I will take a look at it.

Autodesk Inventor Professional 2019
Message 5 of 9
fjrg1979
in reply to: Vladimir.Ananyev

Does this only work for parts? I'm able to make it work for a single part but I'd like to expand this to include retrieving dimensions within assemblies. Is this available throught the API?

 

Inventor 2013

Message 6 of 9
xiaodong_liang
in reply to: alewer

Hi,

 

If the sketch you want to access is within the context of the assembly, you just need to add one more branch, e.g.

 

if  part...

Dim oPartDef As PartComponentDefinition
Set oPartDef= oDoc.ComponentDefinition

 

if assembly...

Dim oAssDef As AssemblyComponentDefinition
Set oAssDef= oDoc.ComponentDefinition

 

If the sketch is within the context of the occurrences (sub-assembly/part) of the top assembly, you need to access the sketch by Occurrence.Definition. 

 

Hope this explains.

 

 

Message 7 of 9
fjrg1979
in reply to: alewer

Please review the attached (C#) code. I am able to retrieve the constraint I'm looking for within the sketch, but I'm getting an Unspecified COM Exception on the last line of code where the dimension is retrieved. Both parameters within the Retrieve method have valid values. 

 

Inventor.TransientObjects transObjs = Application.TransientObjects;
				Inventor.ObjectCollection objColl = transObjs.CreateObjectCollection();
 
				Inventor.AssemblyDocument mainCabAsm = hwyAsm as Inventor.AssemblyDocument;
				Inventor.ComponentOccurrence carSlingAsm = mainCabAsm.ComponentDefinition.Occurrences.ItemByName["CarSling:1"];
				Inventor.ComponentOccurrence platformAsm = carSlingAsm.Definition.Occurrences.ItemByName["650AE:1"];
				Inventor.ComponentOccurrence plywood = platformAsm.Definition.Occurrences.ItemByName["Plywood:1"];
				Inventor.PartComponentDefinition pCompDef = plywood.Definition as Inventor.PartComponentDefinition;
 
				Inventor.DimensionConstraints constraints = pCompDef.Sketches[1].DimensionConstraints;
				Inventor.DimensionConstraint dimCon = null;
 
				if (null != constraints)
				{
					foreach (Inventor.DimensionConstraint d in constraints)
					{
						if (d.Parameter.Name=="PlatformDepth")
						{
							dimCon = constraints[1];
							objColl.Add(dimCon);
						}
					}
				}
				else
				{
 
				}
 
				sheet.DrawingDimensions.GeneralDimensions.Retrieve(vw, objColl);
Message 8 of 9
mcm315
in reply to: xiaodong_liang

Xiaodong.liang,

 

I am trying to retrieve the dimensions from a sketch in item 1 of the an assembly.  I modified the above code.  I keep getting a Method Retrieve of General Dimension Failed error.  Can you take a look for me?

 

Sub Retrieve()
 
  Dim oDrawDoc As DrawingDocument
  Set oDrawDoc = ThisApplication.ActiveDocument
 
  Dim oSheet As Sheet
  Set oSheet = oDrawDoc.ActiveSheet
 
  Dim oView As DrawingView
  Set oView = oSheet.DrawingViews.Item(1)
 
  'object collection for dimensions to be retrieved
  Dim oTO As TransientObjects
  Set oTO = ThisApplication.TransientObjects
  Dim oObjColl As ObjectCollection
  Set oObjColl = oTO.CreateObjectCollection
 
  'fill the object collection with some dimension constrains
  'Here we use sketch DimensionConstraint objects.
  Dim oDoc As AssemblyDocument
  Set oDoc = oView.ReferencedDocumentDescriptor.ReferencedDocument
 
  Dim oDef As ComponentOccurrence
  Set oDef = oDoc.ComponentDefinition.Occurrences.Item(1)
 
  Dim oDoc1 As PartDocument
  Set oDoc1 = oDef.Definition.Document
 
  Dim oDef1 As PartComponentDefinition
  Set oDef1 = oDoc1.ComponentDefinition
  Dim oDimConstraints As DimensionConstraints
  Set oDimConstraints = oDef1.Sketches.Item("Sketch1").DimensionConstraints
 
  Dim oDC As DimensionConstraint
  'add first two constraints to the collection
  Set oDC = oDimConstraints.Item(1)
  Call oObjColl.Add(oDC)
  Set oDC = oDimConstraints.Item(2)
  Call oObjColl.Add(oDC)

 
  'retrieve subset of dimensions
  Call oSheet.DrawingDimensions.GeneralDimensions.Retrieve(oView, oObjColl)


End Sub

Message 9 of 9
mcm315
in reply to: mcm315

bump.  Any ideas?

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

Post to forums  

Autodesk Design & Make Report