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 II.

VBA and Menu's - Page III

Let's look at the right-click Pop-up menu first. Up until now we've been dealing with our own partial menu that we loaded to run alongside the AutoCAD menu. Pop-up menu's on the other hand, are part of the AutoCAD menu. Therefore we need to access this menu and add the items that we require.

Place this coding into a module and save it as VbaMenu3 :

'CODING STARTS HERE

Option Explicit

Sub VbaMenu3()

Dim currMenuGroup As AcadMenuGroup
Dim openMacro As String
Dim newScmenu As AcadPopupMenu
Dim newMenu As AcadPopupMenu
Dim scMenu As AcadPopupMenu
Dim entry As AcadPopupMenu

On Error GoTo Err_Control

' To add items to the right-click shortcut menu, we need to obtain
' reference to the AutoCAD menu.

' Use MenuGroups property to obtain reference to main ACAD menu
Set currMenuGroup = ThisDrawing.Application.MenuGroups.Item("ACAD")

'===================================================================
'find the shortcut menu
For Each entry In currMenuGroup.Menus
If entry.ShortcutMenu = True Then
Set scMenu = entry
End If
Next entry

'create a shortcut menu item
Set newScmenu = scMenu.AddSubMenu(0, "&VBA Menu")

'create the vbaload macro
openMacro = Chr(3) & Chr(3) & Chr(95) & "vbaload" & Chr(32)
'display the shortcut sub-menu item
newScmenu.AddMenuItem "", "VBA &Load", openMacro

'create the vbaide macro
openMacro = Chr(3) & Chr(3) & Chr(95) & "vbaide" & Chr(32)
'display the shortcut sub-menu item
newScmenu.AddMenuItem "", "VBA &Editor", openMacro

'create the vbarun macro
openMacro = Chr(3) & Chr(3) & Chr(95) & "vbarun" & Chr(32)
'display the shortcut sub-menu item
newScmenu.AddMenuItem "", "VBA &Macro", openMacro

'create the vbaman macro
openMacro = Chr(3) & Chr(3) & Chr(95) & "vbaman" & Chr(32)
'display the shortcut sub-menu item
newScmenu.AddMenuItem "", "&VBA Manager", openMacro

'add a separator line
scMenu.AddSeparator 1

're-compile the AutoCAD MENU
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

Now run the macro VbaMenu3. Right-click anywhere on the screen to activate the right-click pop-up menu. It should now look like this :

Now open the AutoCAD.mns file and have a look at the POP0 menu section.

***POP0
**SNAP
[&Object Snap Cursor Menu]
ID_mnuVBA Menu [->&VBA Menu]
ID_VBA Load [VBA &Load]^C^C_vbaload 
ID_VBA Editor [VBA &Editor]^C^C_vbaide 
ID_VBA Macro [VBA &Macro]^C^C_vbarun 
ID_VBA Manager [&VBA Manager]^C^C_vbaman 

[--]
ID_Tracking [Temporary trac&k point]_tt 
ID_From [&From]_from 
ID_MnPointFi [->Poin&t Filters]
ID_PointFilx [.X].X 
ID_PointFily [.Y].Y 
ID_PointFilz [.Z].Z 
[--]
ID_PointFixy [.XY].XY 
ID_PointFixz [.XZ].XZ 
ID_PointFiyz [<-.YZ].YZ 
[--]
ID_OsnapEndp [&Endpoint]_endp 
ID_OsnapMidp [&Midpoint]_mid 
ID_OsnapInte [&Intersection]_int 
ID_OsnapAppa [&Apparent Intersect]_appint 
ID_OsnapExte [E&xtension]_ext 
[--]
ID_OsnapCent [&Center]_cen 
ID_OsnapQuad [&Quadrant]_qua 
ID_OsnapTang [Tan&gent]_tan 
[--]
ID_OsnapPerp [&Perpendicular]_per 
ID_OsnapPara [Para&llel]_par 
ID_OsnapNode [No&de]_nod 
ID_OsnapInse [In&sert]_ins 
ID_OsnapNear [Nea&rest]_nea 
ID_OsnapNone [&None]_non 
[--]
ID_Osnap [&Osnap Settings...]'_+dsettings 2

As you can see, the AutoCAD menu has been re-compiled with our new menu items included.


Right, let's now add to the cursor menu. Place this coding into a module and save it as VbaMenu4.

'CODING STARTS HERE

Private Sub AcadDocument_BeginShortcutMenuDefault(ShortcutMenu As AutoCAD.IAcadPopupMenu)
On Error Resume Next
'Add a menu item to the cursor menu
Dim newMenuItem As AcadPopupMenuItem
Dim openMacro As String
openMacro = Chr(27) + Chr(27) + Chr(95) + "trim" + Chr(32) + Chr(32)
Set newMenuItem = ShortcutMenu.AddMenuItem _
(11, "&Trim", openMacro)
openMacro = Chr(27) + Chr(27) + Chr(95) + "extend" + Chr(32) + Chr(32)
Set newMenuItem = ShortcutMenu.AddMenuItem _
(12, "&Extend", openMacro)
End Sub


Private Sub AcadDocument_EndShortcutMenu _
(ShortcutMenu As AutoCAD.IAcadPopupMenu)
On Error Resume Next
ShortcutMenu.Item("Trim").Delete
ShortcutMenu.Item("Extend").Delete
End Sub

'CODING ENDS HERE

Add VbaMenu4 to your startup suitcase and re-start AutoCAD. Now, trigger your curser pop-up menu.

You should have two new menu items, namely Trim and Extend.

Do you notice that this does not force the AutoCAD menu to re-compile but just adds and deletes from it  on the fly. Worth thinking about isn't it?


Would you like to boldly go where no man ever goes? Then be brave and just click here for the source coding. 



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