Need VBA code to create a list of macros in personal.xls


Posted by Greg on January 18, 2000 10:57 AM

I have been trying, unsuccessfully, to find (or write)a bit of VBA code to create a list of the macros in personal.xls, for use in a combo box on a userform. Can anyone help?

Posted by Celia on January 18, 2000 9:42 PM


Greg

The following may or may not help.
It creates a macro that will display a list of your Personal.xls macros in a dialog box, and allows the user to select and run a macro from the list.
But there is probably an easier way.

In a new workbook :
__Name a worksheet “Personal Macros” and input the names of the macros in your Personal.xls file
(I don't know how to do this with code)
__Open a dialog sheet named “Macro Dialog” and add a list box named “Macro List Box”
__Create the macro shown below.

The workbook can be hidden

Celia

*****
Sub PersonalMacros()

Dim dBox, lBox, macroSheet
Dim lastCell
Dim macroList(), i
Dim macroToRun
Dim response As Boolean

Set dBox = ThisWorkbook.DialogSheets("Macro Dialog")
Set lBox = dBox.ListBoxes("Macro List Box")
Set macroSheet = ThisWorkbook.Sheets("Personal Macros")

'Find the address of the last cell on the macroSheet
lastCell = macroSheet.Range("A1").End(xlDown).Address

'Put the personal macro list in the List Box
lBox.ListFillRange = macroSheet.Range("A1", lastCell).Address(external:=True)

'Store the macro names
ReDim macroList(1 To lBox.ListCount)
With macroSheet.Range("A1", lastCell)
For i = 1 To lBox.ListCount
macroList(i) = Trim(.Cells(i, 1).Value)
Next i
End With

'Display the macro list
response = dBox.Show
If response = False Then Exit Sub

'Run the selected macro
macroToRun = "Personal.xls!" & macroList(lBox.Value)
Application.Run Macro:=macroToRun

End Sub


Posted by Greg on January 19, 2000 5:33 AM

Perhaps i should expand a bit more. I have a marco with a userform written that allows a user to run any macro they have recorded and/or stored previously, but allows them to have the macro repeat either until the end of the sheet or for a specified number of "runs". The way it is now they must input the name of their macro into a text box and that works just fine but i think the functionality would be improved if i could provide a listbox for them to choose from. What makes this function attractive is that it would be dynamic, the list of macros would be up to date at all times. My macro is stored in the user's peersonal.xls and assignred to a menu item under tools, making it available for any worksheet they are working in. To make a long story short, i need the VBA code to create the list of macros at run time.

Posted by Celia on January 19, 2000 4:37 PM

Greg
I think my suggestion provides what you are looking for except that the macro list produced for the user's selection does not get updated automatically(I don't know how to do that). It is necessary to update the list as and when a new macro is added to Personal.xls.
This would appear, however, to be better than your present procedure of having to type a macro name to a text box every time a macro is to be run.
It may be helpful to run my suggested macro. You can see what it does and you may be able to amend/adapt/improve it to your needs.
Celia

PS. The macro names on the "Personal Macros" worksheet should be input to colomn A starting with cell A1 (so as to fit in with the macro code)

Posted by Chris on January 20, 2000 10:52 AM

Greg,

Here you go. I modified this procedure from some code by Chip Pearson. It adds the macros listed in standard modules. It could be modified to also show those in class modules, but for your purposes, that isn't likely needed.

Chris

Sub ShowMacroUserForm()

Dim VBComp As VBComponent
Dim VBCodeMod As CodeModule
Dim StartLine As Long
Dim Msg As String
Dim ProcName As String

For Each VBComp In Workbooks("Personal.xls").VBProject.VBComponents
If VBComp.Type = vbext_ct_StdModule Then
Set VBCodeMod = Workbooks("Personal.xls").VBProject.VBComponents(VBComp.Name).CodeModule
With VBCodeMod
StartLine = .CountOfDeclarationLines + 1
Do Until StartLine >= .CountOfLines
UserForm1.ListBox1.AddItem .ProcOfLine(StartLine, vbext_pk_Proc)
StartLine = StartLine + .ProcCountLines(.ProcOfLine(StartLine, _
vbext_pk_Proc), vbext_pk_Proc)
Loop
End With
End If
Next VBComp

UserForm1.Show

End Sub

Posted by Chris on January 20, 2000 11:22 AM

Sorry, forgot to mention:

You'll need to set a reference in VBA to the VBA Extensibility library. In the VBA editor, go to the Tools menu, choose the References item, and put a check next to "Microsoft Visual Basic For Applications Extensibility" library.

Chris

Posted by Greg on January 20, 2000 12:59 PM

Wow, Thanks Chris, that looks like just what i needed.

Greg

Dim VBComp As VBComponent Dim VBCodeMod As CodeModule Dim StartLine As Long Dim Msg As String Dim ProcName As String For Each VBComp In Workbooks("Personal.xls").VBProject.VBComponents If VBComp.Type = vbext_ct_StdModule Then Set VBCodeMod = Workbooks("Personal.xls").VBProject.VBComponents(VBComp.Name).CodeModule With VBCodeMod StartLine = .CountOfDeclarationLines + 1 Do Until StartLine >= .CountOfLines UserForm1.ListBox1.AddItem .ProcOfLine(StartLine, vbext_pk_Proc) StartLine = StartLine + .ProcCountLines(.ProcOfLine(StartLine, _ vbext_pk_Proc), vbext_pk_Proc) Loop End With End If Next VBComp UserForm1.Show

Posted by Greg on January 21, 2000 7:39 AM

This looks real good when i read it through, i'm sure it will do what i want BUT i keep getting an error message "Compile Error: Can't find project or library" The code stops at the line "Dim VBComp As VBComponent) I have a missing reference ("MISSING: ISCtrls OLE Control Module) in the references list but i can't clear it or find what may be causing it. The file referred to by this reference seems to be in place (C:\windows\system\ISCTRLSLIB.TWD). I have also searched the knowledgebase at Microsoft but it's getting frustrating. I expect i'm missing something easy but i don't know where to go next.

Thanks in advance

Greg

Dim VBComp As VBComponent Dim VBCodeMod As CodeModule Dim StartLine As Long Dim Msg As String Dim ProcName As String For Each VBComp In Workbooks("Personal.xls").VBProject.VBComponents If VBComp.Type = vbext_ct_StdModule Then Set VBCodeMod = Workbooks("Personal.xls").VBProject.VBComponents(VBComp.Name).CodeModule With VBCodeMod StartLine = .CountOfDeclarationLines + 1 Do Until StartLine >= .CountOfLines UserForm1.ListBox1.AddItem .ProcOfLine(StartLine, vbext_pk_Proc) StartLine = StartLine + .ProcCountLines(.ProcOfLine(StartLine, _ vbext_pk_Proc), vbext_pk_Proc) Loop End With End If Next VBComp UserForm1.Show

Posted by Chris on January 21, 2000 10:21 AM

Are you sure you set up the reference?

That's the only thing I can think of. I can assure you that it does work for me. Maybe someone else can give it a shot?

Chris

Posted by Celia on January 21, 2000 4:06 PM


Worked first time for me. Very useful. Thanks Chris.

Celia

Posted by Dave on January 22, 2000 1:45 AM

THis was of interest to me too but I tried it as well but without success.

Firstly when I went to Tools to check the Extensibility option, there wasn't one on the list. There were 3 just with "Visual Basic For Applications". If I check one or all of these I got the error msg back "Name conflicts with existingmodule, project, or object library".

If I check none of these and run the macro, the first error message I get is "Compile error - User defined type not defined" and highlights the line

Dim VBComp As VBComponent

Posted by Greg on January 23, 2000 10:10 AM

It works great on my machine at home but not at the office! There must be something missing or different about the MSOffice install at work. I should be able to figure this out.

Thanks for your help

Greg

:

Are you sure you set up the reference? : That's the only thing I can think of. I can assure you that it does work for me. Maybe someone else can give it a shot? Chris

Posted by Ivan Moala on January 23, 2000 3:46 PM

Firstly when I went to Tools to check the Extensibility option, there wasn't one on the list. There were 3 just with "Visual Basic For Applications". If I check one or all of these I got the error msg back "Name conflicts with existingmodule, project, or object library". If I check none of these and run the macro, the first error message I get is "Compile error - User defined type not defined" and highlights the line


If the microsoft visual basics extensibilty file
if not listed then browsed for it....ie click
browse and search for this object library file
in the /common files/microsoft shared/vba DIR.
The file you want is the Vbeext1.olb file.

This should clear up the errors


Ivan

Posted by Ivan Moala on January 24, 2000 10:00 AM


Try this assuming you want to add it to a listbox1Dim VBACodeModule As CodeModule
Dim StartLine As Long

Set VBACodeModule = Workbooks("Personal.xls").VBProject.VBComponents("Module1").CodeModule


With VBACodeModule
StartLine = .CountOfDeclarationLines + 1
Do Until StartLine >= .CountOfLines
listbox1.AddItem = .ProcOfLine(StartLine, vbext_pk_Proc)
StartLine = StartLine + .ProcCountLines(.ProcOfLine(StartLine, _
vbext_pk_Proc), vbext_pk_Proc)
x = x + 1
Loop
End With


Ivan

Posted by Ivan Moala on January 24, 2000 10:01 AM


Try this assuming you want to add it to a listbox1

Dim VBACodeModule As CodeModule
Dim StartLine As Long

Set VBACodeModule = Workbooks("Personal.xls").VBProject.VBComponents("Module1").CodeModule


With VBACodeModule
StartLine = .CountOfDeclarationLines + 1
Do Until StartLine >= .CountOfLines
listbox1.AddItem = .ProcOfLine(StartLine, vbext_pk_Proc)
StartLine = StartLine + .ProcCountLines(.ProcOfLine(StartLine, _
vbext_pk_Proc), vbext_pk_Proc)
Loop
End With


Ivan



Posted by Greg on January 26, 2000 12:36 PM

I have it working nicely now. I had to go and temporarily move the object library file from windows\system and then re-add it from the tools reference dialog box. This is a very useful bit of code.

Thanks to all

Greg