AfraLisp Blog

The AutoLisp/Visual Lisp/VBA Resource Website

AfraLisp Blog

Home Newsletter Utter Rubbish Coding Tips AutoCAD Tips Contact Downloads WAUN


ACCESSing AutoCAD

Written by Scott McGlynn - SMcGlynn@MCECo.com

Scott has been working with AutoCAD since 1985 (Release 2.15) and with Visual Basic since 1993.
He has worked for one of the larger electrical contractors in the US since 1994 as a Project Engineer. He recently acquired a BS in Business Administration.

In regards to VB, he has been mostly self taught with a couple of classes here and there over
the years.


Microsoft Access is a simple relational database management system, RDBMS for short. Databases are great for storing data. An excellent use of databases can be found in what I call a "Conduit and Cable Schedule". Creating the Database is a whole topic unto itself and I will not go into a lot of detail about it, however, I will describe what this Conduit andCable Schedule is all about. Following is a screen shot of the "Relationships" view of the Database we will be referencing :



You will notice this is a large and rather complex database structure, but over the next few months, we will be going through it step by step and breaking it down. The tables we will be using today include the LOC, CAB, CON and DWG tables. The LOC table is a list of locations, the CAB, a list of Cables, the CON, a list of Conduits and the DWG table, a list of drawings.
In large electrical projects, there are lots and lots of pieces of equipment that need power, have control wires and other such interconnections. When designing the electrical distribution systems it is nice to have a method of referencing those conduits and wires between these locations. For instance, a particular Electrical panel might have 42 separate circuit breakers. Each one feeding a different pump. As electrical contractors, we have to install conduit and wire to feed all of these pieces of equipment.

From a purely theoretical standpoint, every location in a job must be unique. We can't have two pumps with the same name, no one would know which one we were referring to. By the same token, we can't have two conduits with the same number. So, in the Access Database, we will have the CAB, CON and LOC tables with indexes that prevent the generation of records with duplicate names.

Interfacing that Database with AutoCAD has been on my wish list for a few years, with the help of Kenny Ramage and the rest of the gang here at Afralisp and Cad Encoding, I've gotten up the courage to tackle just that. Ok, so let's begin.

Virtually Everything I do will be done from within Microsoft Access. The biggest question I have had to ask myself is which application to write the code in. I could Write the application in Access and have Access talk to AutoCAD, or I could write the code in AutoCAD and have AutoCAD talk to Access. I chose the former over the latter for the simple reason that I have thousands and thousands of lines of code written in Access to make the Conduit and Cable Schedule Work. I didn't really want to reinvent the wheel, so there it is. Also, for compatibility issues, I am working in AutoCAD 2002 and Microsoft Access 97. While there shouldn't be a big difference between versions, there may be.

My First step in this little shindig was to create a new class module to contain all of the code for the AutoCAD interface. Once the new class is created, at the top, add the following lines of code :

Option Compare Database
Option Explicit
Private WithEvents objACAD As AcadApplication
Private objDoc As AcadDocument
Private Appexists As Boolean

The "Option Compare Database and the "Option Explicit" tell the Access App to first use the Database default for comparing strings, etc and secondly to force the dimensioning of all variables.

That third line is a big one. It defines the interface for the AutoCAD Application. The "WithEvents" keyword allows Access to generate Event Handlers for all of the Events AutoCAD exposes. For instance, when a new drawing is opened, Access will know about it. The objDoc variable gives us a direct reference to the Autocad Document which is a drawing. Finally, we define a boolean value for internal use that makes sure the App Exists before we try to use it.

Please note, this is not an actual object, but a class. In order to create the object, we have to define an object variable as this class and instantiate it. In the case of the Access Application, I have a global variable called "objACAD" defined that is instantiated when the Access Application starts (it is instantiated when a splash form comes up This allows any and all objects within the Application to incorporate Autocad information into the data.)

When the class is instantiated, the "Class_Initialize" Event is executed. The code for this follows:

Private Sub Class_Initialize()
On Error Resume Next
Set objACAD = GetObject(, "Autocad.Application")
AppExists = True
If objACAD Is Nothing Then
    Set objACAD = CreateObject("AutoCad.Application")
    If objACAD Is Nothing Then Appexists = False
    
End If

IF AppExists Then Set objDoc = objACAD.ActiveDocument
End Sub

First we set up an Error handler, then we attempt to get a reference to any existing Autocad Applications that might be running. IF that fails, we then try to create a new instance of AutoCAD. If that fails, we then set Set our AppExists value to false. Finally, we set a reference to the Current Document.

Using an Exhaust Fan as an example, there are power conductors that go from a Motor Control Center (MCC) to an Exhaust Fan Disconnect (EF-DISC). Then there are Power conductors to go from EF-DISC to the Exhaust Fan (EF). Finally, there are control conductors that go from the MCC to a Processor Panel (PP) that indicate if the EF is Running, Faulted, etc. Schematically, it would look like this :

Notice the cable numbers. This is a cable numbering system I have come up with that seems to work reasonably well. Each cable is defined by the piece of equipment's name (in this case, EF). The second part, the P01, P02, and C01 define the types of cables they are, Power, Control, Signal, Data,Fiberoptic, etc. So, our Cable Table contains a list of all the Cable Names (each being unique). Now lets take a look at this schematic from the point of view of construction. Below is a floor plan showing the location of each of these pieces of equipment.


Notice there is more to this than just the equipment listed in the schematic. From a construction point of view, I have an additional pull box located on the west well (north is up) The conduit goes from MCC to PB-1 Then a conduit from PB-1 to EF-DISC. Finally, a conduit from EF-DISC to EF. Numbering the conduits, we get the plan shown below Notice, the cable EFC01 is contained in both Conduit 1 and Conduit 2.


Now that we have an idea of what the conduit and cable schedule will contain, lets take a look at interfacing it with AutoCAD. Something that would be nice to have is an ability to select a location in the database and have AutoCAD automatically open the drawing and zoom to the location. In pseudo code, it would be something like:

Given a Selected Location in the Database,
	Open Drawing Containing Location
	Find Autocad Entity that is the location
	Get Boudning Box of Entity
	Zoom to bounding box
	Complete.

Two important pieces of information are stored in the Location Table that will help in this endeavor. First, is an index that is the Drawing, second is the Handle of the Entity in that Drawing.

How do we obtain those two pieces of information? . .Well, lets look at some pseudocode for that one:

Given a Selected Location in the Database,

  • 1. Ask the user if the current Autocad Drawing is the one containing the entity that is the location (is the polyline box representing PB-1 on the current drawing?)

  • 2. If it is, leave the current drawing open, if not, allow the user to select the drawing required.

  • 3. Allow the user to select the entity that represents the location.

  • 4. Retrieve the drawing name and the handle

  • 5. Store information in the database.

  • 6. Complete.


This is a screen shot of the "Location" Form. There are many fields in this form that are of little consequence to us here. The fields we are most concerned with are the Handle, DWGID and the button next to it as well as the "Show Item" command button.

Lets take a look at the code behind the button next to the Handle Text box.

Private Sub cmdGetHandle_Click()
Dim col As Collection
Dim ent As AcadEntity
Dim strDWG As String
Set col = objACAD.GetHandle
If col.Count = 0 Then Exit Sub
Set ent = col.Item(1)
txtHandle = ent.Handle
strDWG = ent.Document.Path & "\" & ent.Document.name
txtDWGID = FindDrawing("filename", strDWG).DWGID
End Sub

Similar to our pseudo code, we call a function from our ojbACAD class called GetHandle. Notice the return value for the GetHandle Function is a Collection. In our current example, we only want one entity.
However, there are other uses for this function. Namely, when routing cables through conduits, I can select all the conduits and pull boxes the cable goes through and the Database will be able to add the cable to all of those items.

Public Function GetHandle() As Collection
Dim objDoc As Object
Dim col As Collection
Dim ob As AcadEntity
Dim str As String
Dim pt As Variant
Dim str As String
Dim fname As String

Set col = New Collection
If objACAD Is Nothing Then
    MsgBox "Could Not Get Autocad Application"
    Exit Function
End If
If objACAD.Documents.Count = 0 Then
    str = GetFileName(CurrentDb.name, "Select File to Open")
    If str = "" Then
        Set GetHandle = Nothing
        GoTo CleanUp
    End If
    Set objDoc = objACAD.Documents.Open(str)
End If
Do
    On Error Resume Next
    Set ob = Nothing
    objDoc.Utility.GetEntity ob, pt, "Select the Enetity:"
    If Err.number = 80020009 Then GoTo CleanUp
    col.Add ob, ob.Handle
    ob.Highlight True
   
Loop Until ob Is Nothing
CleanUp:
For Each ob In col
    ob.Highlight False
    str = str & ob.Handle & ", "
Next
str = Left$(str, Len(str) - 2)
Set GetHandle = col

Set col = Nothing
End Function

To Be Continued........

 
The AutoLisp/Visual Lisp/VBA Resource Website

Copyright © 1999-Perpetuity by AfraLisp

All rights reserved.
Information in this document is subject to change without notice.
Site created and maintained by Kenny Ramage

The AutoLisp/Visual Lisp/VBA Resource Website