0% found this document useful (0 votes)
132 views

Loading VBA Files With Visual LISP

The document discusses loading and running VBA files from within AutoCAD using Visual LISP. It explains that the VL-VBALOAD function can load VBA files without errors if the file is already loaded, unlike the VBALOAD command. It also provides code examples to load and run VBA files from menus or functions using VL-VBALOAD and VL-VBARUN. The document additionally shows how to get a list of loaded VBA projects and unload all projects from a drawing using Visual LISP.

Uploaded by

Marcos Antonio
Copyright
© © All Rights Reserved
Available Formats
Download as PDF, TXT or read online on Scribd
0% found this document useful (0 votes)
132 views

Loading VBA Files With Visual LISP

The document discusses loading and running VBA files from within AutoCAD using Visual LISP. It explains that the VL-VBALOAD function can load VBA files without errors if the file is already loaded, unlike the VBALOAD command. It also provides code examples to load and run VBA files from menus or functions using VL-VBALOAD and VL-VBARUN. The document additionally shows how to get a list of loaded VBA projects and unload all projects from a drawing using Visual LISP.

Uploaded by

Marcos Antonio
Copyright
© © All Rights Reserved
Available Formats
Download as PDF, TXT or read online on Scribd
You are on page 1/ 5

06/04/2015

LoadingVBAFileswithVisualLISP|AfraLISP

LoadingVBAFileswithVisualLISP
byKennyRamage
TherearetwoAutoCADfunctionsthatyouwouldusetoLoadandRunVBAApplications
namely,VBALOADandVBARUN.Inamenufileyouwouldusethemlikethis:

[Test]^C^C^C^Pvbaloadtest.dvbvbarunModule1.MyTest
Or,inanAutoLisproutine,youwouldwritesomethinglikethis:

(command"vbaload""test.dvb")
(command"vbarun""Module1.MyTest")
TheVBALOADfunctionhasoneseriousflawthough!IfaVBAapplicationisalreadyloaded,andyourun
VBALOADagain,yougetanerrormessage.Tryitout:

Command:vbaload
InitializingVBASystem...
OpenVBAProject:test.dvb
Nowtryandloaditagain.

Command:vbaload
OpenVBAProject:test.dvb
Youshouldgetanerrormessage:

"Filealreadyloadedd:/drawings/test.dvb"
ThisiswhereVisualLispcomesintoplay.
Thefunction(VLVBALOAD)behavesmuchlikethecommandVBALOAD.Youneedtosupplythefilenameofa
projectorDVBfile.ThecompletefilenameshouldbeprovidedalongwiththepathandDVBextension.For
example,ifyouwanttoloadaprojectnamedMyProject.dvbintheC:\MyWork\folder,the(VLVBALOAD)function
callwouldappearasfollows:

(VLVBALOAD"C:/MyWork/MyProject.DVB")
Youshouldnoteacoupleofthingsrightaway.VisualLISPmakesuseofforwardslasheswhenseparatingfolderor
directorynames.Also,theparenthesesarerequiredandtheextensionDVBisneededfortheprojecttobeproperly
located.
UnliketheVBALOADcommand,thisfunctionwillnotgenerateanerroriftheprojecthasalreadybeenloadedinto
data:text/htmlcharset=utf8,%3Ch1%20style%3D%22padding%3A%200px%3B%20margin%3A%2010px%200px%2012px%3B%20fontfamily%3A%20'R

1/5

06/04/2015

LoadingVBAFileswithVisualLISP|AfraLISP

thecurrentdrawingenvironment.Thus,programscanproceedsmoothlybyjustcallingtheloadfunctionandthen
callingtherunfunctionwithoutconcernabouttheprojectalreadybeingloaded.Anotherinterestingfeatureisthat
theEnableMacros/VirusWarningmessagedoesnotappearwhenyouusetheVisualLISPapproach.
Therefore,yourmenumacro:

[Test]^C^C^C^Pvbaloadtest.dvbvbarunMyTest
canbereplacedwiththefollowingone:

[Test]^C^C^C^P(vlvbaload"test.dvb")(vlvbarun"MyTest")
Andofcourse,yourAutoLispcodingshouldbereplacedwiththis:

(vlvbaload"test.dvb")
(vlvbarun"MyTest")
Here'salittlefunctionthatyoucouldloadatstartuptohelpyoulocate,loadandrunVBAfiles:

;CODINGSTARTHERE

(defunVBALOADIT(ProjNameMacro)
(if(findfileProjName)
(progn
(vlvbaloadProjName)
(vlvbarunMacro)
);progn
);if
(princ)
);defun
(princ)
;CODINGENDSHERE

data:text/htmlcharset=utf8,%3Ch1%20style%3D%22padding%3A%200px%3B%20margin%3A%2010px%200px%2012px%3B%20fontfamily%3A%20'R

2/5

06/04/2015

LoadingVBAFileswithVisualLISP|AfraLISP

Syntax: (vbaloadit"dvbfile""macro")
Example: (vbaloadit"test.dvb""MyTest")
Youmustkeepsomeotherconsiderationsinmindwhenusing(VLVBALOAD)and(VLVBARUN).Forexample,
afteryouinvokethe(VLVBARUN)function,theVisualLISPfunctionwillcontinuetorunandcan(will)interfere
withtheVBAinterfaceifyoutrytodotoomuch.Ontheotherhand,therearesomedistinctadvantagestousing
theVisualLISPapproachtoloadingandlaunchingVBAmacrosinsteadofthecommandlineversionswhen
programmingamenuortoolbarbasedinterface.
OnethingtonoteisthattheVBARUNisnotasubroutine.Thatis,programexecutionwillnotbehandedtothe
VBAmacroandtheVisualLISProutinesuspendedasifitwererunningafunction.Instead,theVisualLISP
functionwillcontinuetorunastheVBAmacrostarts.ThebestthingtodoissimplyfinishtheVisualLISPfunction
asquicklyaspossibleandlettheVBAmacrorunthecommandinterfacefromthatpointforward.Ifyouwantto
returntoaVisualLISPfunctionafterrunningtheVBAcode,thenusetheSendCommandmethodattachedtothe
DocumentobjectinVBA.WhenyouarereadytohandcontrolbacktoVisualLISP,callthefunctiondirectly
(remembertowrapparenthesesaroundthecommandstartupfordirectlaunchesofVisualLISPfunctions).When
youusethisapproach,theVBAprogramshouldendandallowtheVisualLISPfunctiontoproceedwithout
interference.SimilartostartingtheVBAmacrointhefirstplace,whenyousendcommandstotheAutoCAD
documentfromVBA,theywillberunalongwiththeVBAandsometimesthiscanresultinconfusionattheuser
levelasthetwotrytotaketurns.NotethatyoucanpassparametersfromVBAtotheVisualLISPfunctionby
sendingthemaspartofthecommandstream.Theywillneedtobeconvertedtostringsfirst,thensenttothe
VisualLISPfunctionaspartofthefunctionstartupfromtheSendCommandmethod.
Note:Sorry,butduetoadditionstotheObjectModel,thisnextsectionwillonlyworkinAutoCAD2002and
above.
WanttoknowwhatProjectsareloadedinyourdrawing?
Typethisattheconsoleprompt:

_$(vlloadcom)
_$(setqoApp(vlaxgetacadobject))
VLAOBJECTIAcadApplication00ac8928>
_$(setqoVbe(vlaxgetoapp"VBE"))
#<VLAOBJECTVBE020b9c18>
_$(vlaxdumpobjectoVBET)
;VBE:nil
;Propertyvalues:
;ActiveCodePane=nil
;ActiveVBProject=#<VLAOBJECT_VBProject020ba620>
data:text/htmlcharset=utf8,%3Ch1%20style%3D%22padding%3A%200px%3B%20margin%3A%2010px%200px%2012px%3B%20fontfamily%3A%20'R

3/5

06/04/2015

LoadingVBAFileswithVisualLISP|AfraLISP

;ActiveWindow(RO)=nil
;CodePanes(RO)=#<VLAOBJECT_CodePanes00b1c2e0>
;CommandBars(RO)=#<VLAOBJECT_CommandBars030b2a24>
;Events(RO)=#<VLAOBJECTEvents020b9c94>
;MainWindow(RO)=#<VLAOBJECTWindow020b8ce8>
;SelectedVBComponent(RO)=#<VLAOBJECT_VBComponent020ba748>
;VBProjects(RO)=#<VLAOBJECT_VBProjects020b9c4c>
;Version(RO)="5.00"
;Windows(RO)=#<VLAOBJECT_Windows020b9d18>

;Nomethods
T
IpresumeyoucanseewhatIsee?A"VBProjects"property.Nowthat'sinteresting!Buthowdoweextractthe
loadedProjects?
Loadandrunthissmallroutine:

;CODINGSTARTSHERE

(defunGvba(/oAppoVBEoProjsNNamsoProj)

(vlloadcom);requiresautomationlinks

(if(and

DrilldowntotheProjectsobject
(setqoApp(vlaxgetacadobject))
(setqoVBE(vlagetvbeoApp))
(setqoProjs(vlaxgetoVBE"VBProjects"))
)
;LoopthroughProjectsobject
(repeat(setqN(vlagetcountoProjs))

;gettheitematpositionN
(setqoProj(vlaitemoProjsN)

;getthenameproperty,
;addittothelist.
Nams(cons
(list
(vlaxgetoProj"Name")
data:text/htmlcharset=utf8,%3Ch1%20style%3D%22padding%3A%200px%3B%20margin%3A%2010px%200px%2012px%3B%20fontfamily%3A%20'R

4/5

06/04/2015

LoadingVBAFileswithVisualLISP|AfraLISP

(vlaxgetoProj"FileName")
)Nams)N(1N)))
)

;returnlistofnames
Nams

);defun
;CODINGENDSHERE
YoushouldhavealistofProjectsinthevariable"Nams".
And,wouldyouliketoUnloadallprojectswithinyourdrawing?Trythis:

;CODINGSTARTSHERE
(defunC:UNLOADALLVBA(/VBAProjsVBAProj)

(setqVBAProjs(Gvba))

(foreachVBAProjVBAProjs

(command"_VBAUNLOAD"(cadrVBAProj)))

;CODINGENDSHERE

data:text/htmlcharset=utf8,%3Ch1%20style%3D%22padding%3A%200px%3B%20margin%3A%2010px%200px%2012px%3B%20fontfamily%3A%20'R

5/5

You might also like