AfraLisp Blog

The AutoLisp/Visual Lisp/VBA Resource Website

AfraLisp Blog

Home Newsletter Utter Rubbish Coding Tips AutoCAD Tips Contact Downloads WAUN

Home. Page I. Page III.

VBA and Menu's - Page II

Before continuing with this tutorial, please delete the VbaMenu.mnc, VbaMenu.mnr files, and delete the contents of VbaMenu.mns. This is to allow the menu to be re-compiled with only the Toolbar menu items. You must also ensure that the 4 bitmap files, VbaLoad.bmp, Vbaide.bmp, VbaMacro.bmp, and VbaMan.bmp are in the same folder as your menu files.

Now place the following coding into a module and save it as VbaMenu2.

'CODING STARTS HERE

Option Explicit

Sub VbaMenu2()

Dim currMenuGroup As AcadMenuGroup
Dim newToolBar As AcadToolbar
Dim newToolBarButton As AcadToolbarItem
Dim openMacro As String
Dim SmallBitmapName As String
Dim LargeBitmapName As String

On Error GoTo Err_Control

'Load the VBAMENU menu
ThisDrawing.Application.MenuGroups.Load "VbaMenu.mns"

'We now need to obtain a reference to our new menu, VBAMENU
'Use MenuGroups property to obtain reference to main VBAMENU menu

Set currMenuGroup = ThisDrawing.Application.MenuGroups.Item("VBAMENU")

'==========================================================
' Create Toolbar Menu
Set newToolBar = currMenuGroup.Toolbars.Add("Vba Menu")
'==========================================================
'vbaload macro and bitmaps
openMacro = Chr(3) & Chr(3) & Chr(95) & "vbaload" & Chr(32)
Set newToolBarButton = newToolBar.AddToolbarButton(newToolBar.Count + 1, "VBA Load", "VBALoad", openMacro, False)
SmallBitmapName = "VBALOAD.BMP"
LargeBitmapName = "VBALOAD.BMP"
newToolBarButton.SetBitmaps SmallBitmapName, LargeBitmapName
newToolBarButton.HelpString = "Load a VBA Application"
'==========================================================
'vbaide macro and bitmaps
openMacro = Chr(3) & Chr(3) & Chr(95) & "vbaide" & Chr(32)
Set newToolBarButton = newToolBar.AddToolbarButton(newToolBar.Count + 1, "VBA Editor", "VBA Editer", openMacro, False)
SmallBitmapName = "VBAIDE.BMP"
LargeBitmapName = "VBAIDE.BMP"
newToolBarButton.SetBitmaps SmallBitmapName, LargeBitmapName
'==========================================================
'vbarun macro and bitmaps
openMacro = Chr(3) & Chr(3) & Chr(95) & "vbarun" & Chr(32)
Set newToolBarButton = newToolBar.AddToolbarButton(newToolBar.Count + 1, "Run Macro", "Run Macro", openMacro, False)
SmallBitmapName = "VBAMACRO.BMP"
LargeBitmapName = "VBAMACRO.BMP"
newToolBarButton.SetBitmaps SmallBitmapName, LargeBitmapName
'==========================================================
'vbaman macro and bitmaps
openMacro = Chr(3) & Chr(3) & Chr(95) & "vbaman" & Chr(32)
Set newToolBarButton = newToolBar.AddToolbarButton(newToolBar.Count + 1, "VBA Manager", "VBA Manager", openMacro, False)
SmallBitmapName = "VBAMAN.BMP"
LargeBitmapName = "VBAMAN.BMP"
newToolBarButton.SetBitmaps SmallBitmapName, LargeBitmapName
'==========================================================

're-compile the VBAMENU menu - VBAMENU.MNC
currMenuGroup.Save acMenuFileCompiled

'save it as a MNS file.
currMenuGroup.Save acMenuFileSource

Just_Here:
Exit Sub

Err_Control:
Select Case Err.Number
'The menu exists, just exit
Case -2147024809
Err.Clear
Resume Just_Here
Case Else
MsgBox Err.Description
Exit Sub
End Select
End Sub

'CODING ENDS HERE


Run the VbaMenu2 macro. A toolbar like this should appear on your screen :

Open your VbaMenu.mns file. It should look like this :

//
// AutoCAD menu file - VbaMenu.mns
//

***MENUGROUP=VbaMenu

***TOOLBARS
**VBA_MENU
ID_Vba_Menu_0 [_Toolbar("Vba Menu", _Floating, _Show, 212, 192, 1)]
ID_VBA_Load_0 [_Button("VBA Load", "VBALOAD.BMP", "VBALOAD.BMP")]^C^C_vbaload 
ID_VBA_Editor_0 [_Button("VBA Editor", "VBAIDE.BMP", "VBAIDE.BMP")]^C^C_vbaide 
ID_Run_Macro_0 [_Button("Run Macro", "VBAMACRO.BMP", "VBAMACRO.BMP")]^C^C_vbarun 
ID_VBA_Manager_0 [_Button("VBA Manager", "VBAMAN.BMP", "VBAMAN.BMP")]^C^C_vbaman 


***HELPSTRINGS
ID_VBA_MANAGER_0 [VBA Manager]
ID_VBA_LOAD_0 [Load a VBA Application]
ID_RUN_MACRO_0 [Run Macro]
ID_VBA_EDITOR_0 [VBA Editer]

//
// End of AutoCAD menu file - VbaMenu.mns
//


Again, the coding for the menu has been compiled.

Crikey, this is getting interesting! Let's dig a bit deeper.
On the next page we'll have a look at accessing and adding to the AutoCAD PopUp menu's. Come on, don't be scared.......



Home. Page II. Page III.
 
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