See the top rated post in this thread. Click here

Page 2 of 2 FirstFirst 12
Results 11 to 16 of 16

Thread: AutoCAD VBA Tips & Tricks

  1. #11
    All AUGI, all the time zoomharis's Avatar
    Join Date
    2005-02
    Location
    Abu Dhabi (Native-India)
    Posts
    506
    Login to Give a bone
    0

    Default Re: AutoCAD VBA Tips & Tricks

    This function returns the distance between two given points. Originally posted here by Ed Jobe.
    Code:
      
    Public Function XYZDistance(Point1 As Variant, Point2 As Variant) As Double
      'Returns the distance between two points
      Dim dblDist As Double
      Dim dblXSl As Double
      Dim dblYSl As Double
      Dim dblZSl As Double
      'Calc distance
      dblXSl = (Point1(0) - Point2(0)) ^ 2
      dblYSl = (Point1(1) - Point2(1)) ^ 2
      dblZSl = (Point1(2) - Point2(2)) ^ 2
      dblDist = Sqr(dblXSl + dblYSl + dblZSl)
      'Return Distance
      XYZDistance = dblDist
    End Function

  2. #12
    Administrator Ed Jobe's Avatar
    Join Date
    2000-11
    Location
    Turlock, CA
    Posts
    6,397
    Login to Give a bone
    0

    Default Re: AutoCAD VBA Tips & Tricks

    For information about creating an ActiveX instance of Excel (or any other Office app) that properly closes all of its objects and doesn't leave a process running...see this thread.
    C:> ED WORKING....

  3. #13
    All AUGI, all the time zoomharis's Avatar
    Join Date
    2005-02
    Location
    Abu Dhabi (Native-India)
    Posts
    506
    Login to Give a bone
    0

    Default Re: AutoCAD VBA Tips & Tricks

    Accessing Nested Block References

    Use this trick to access a nested block reference which is normally not accessible using the model/paper space iterations or selection set filters.

    Code:
      
    Public Function getNestedBlockRef(ByVal strBlkRefName As String) As AcadBlockReference
    Dim objBlk As AcadBlock
    Dim objBlkRef As AcadBlockReference
    Dim objEnt As AcadEntity
    For Each objBlk In ThisDrawing.Blocks
    	For Each objEnt In objBlk
    		If TypeOf objEnt Is AcadBlockReference Then
    			If StrComp(objEnt.Name, strBlkRefName, vbTextCompare) = 0 Then
    				Set getNestedBlockRef = objEnt
    				Exit Function
    			End If
    		End If
    	Next
    Next
    Set getNestedBlockRef = Nothing
    End Function

  4. #14
    Active Member
    Join Date
    2007-06
    Posts
    97
    Login to Give a bone
    0

    Default Re: AutoCAD VBA Tips & Tricks

    Quote Originally Posted by rcrabb View Post
    Code:
    Function Arccos(X) As Double
       Arccos = Atn(-X / Sqr(-X * X + 1)) + 2 * Atn(1)
    End Function
    This may be nit-picking a bit but shouldn't this function include these lines to avoid Div/0 error:
    Code:
    Function Arccos(X) As Double
       If Round(X, 8) = 1# Then Arccos = 0#: Exit Function 'modify precision to suit
       If Round(X, 8) = -1# Then Arccos = Pi: Exit Function 'modify precision to suit and address "Pi"
       Arccos = Atn(-X / Sqr(-X * X + 1)) + 2 * Atn(1)
    End Function

  5. #15
    Active Member
    Join Date
    2007-12
    Posts
    68
    Login to Give a bone
    0

    Default Re: AutoCAD VBA Tips & Tricks

    It originally started way back when, in GW/PC basic, when it was just a 'friendlier' way to do it. But it also seems a bit more natural now; if dealing with classes or collections, where the original instance may not be counted

  6. #16
    Member
    Join Date
    2009-09
    Posts
    3
    Login to Give a bone
    0

    Default Re: AutoCAD VBA Tips & Tricks

    Hello,
    I read your comment,also have a look of the link which you have provided.Well nice article,i must say.I appreciate your thought for sharing such tips and solutions at the community.This type of information would so helpful to the students like best tutorials.Please try to share more about this in future,it is really very knowledgeable.Thank you for sharing such a nice comment.

Page 2 of 2 FirstFirst 12

Similar Threads

  1. CV314-4: AutoCAD Civil 3D Tips and Tricks
    By Autodesk University in forum Civil Infrastructure
    Replies: 0
    Last Post: 2014-12-01, 05:01 AM
  2. MP104-1: New Tips and Tricks for Piping in AutoCAD MEP
    By Autodesk University in forum MEP Design and Engineering
    Replies: 0
    Last Post: 2014-12-01, 03:25 AM
  3. GD315-1: AUGI Tips and Tricks: For AutoCAD
    By Autodesk University in forum General Design
    Replies: 0
    Last Post: 2013-05-06, 01:35 AM
  4. GD311-4: DWF Publishing from AutoCAD: Tips and Tricks
    By Autodesk University in forum General Design
    Replies: 0
    Last Post: 2013-05-06, 01:34 AM
  5. info about Tips And Tricks For AutoCad
    By sharjeel_faiz in forum AutoCAD General
    Replies: 1
    Last Post: 2005-06-08, 04:39 AM

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •