VBA Code Sample 12 -- The Access 2000 Menu Manager Add-In

23
VBA Code Sample #12 The Access 2000 Menu Manager Add-in Updated 13-Jan-2004 Helen Feddema ([email protected]) Instructions  This Access 2000 add-in creates a main menu for an Access application, with drop-down lists for selecting database objects. (The add-in works in Access 2000 through Access 2003. !t consists of three menu add-ins, one to create the main menu, and two to perform housekeeping chores later on. To install and test the add-in, "rst cop# the "les listed below to the listed folders. Table 1: File Locations File ame Install to Folder Menu Manager.mda Add-ins folder (usually C:\WINDOWS\Applicaion Daa\Microsof\AddIns !es Daa"ase.md" Any folder !es #eer.do \!emplaes $e%t, open the Test &atabase.mdb included in the 'ip. This is a database containing some $orthwind components, with the $) naming con*ention applied, and a line of code added to the )lose or +nload e*ent of its forms to displa# the main menu when the# are closed. &rop down the Tools menu, select the Add-ins command, and select Add-!n anager from the #-out menu $%A Code Sample &' )age ' of *

description

VBA Code Sample 12 -- The Access 2000 Menu Manager Add-In

Transcript of VBA Code Sample 12 -- The Access 2000 Menu Manager Add-In

VBA Code Sample #12

VBA Code Sample #12 ( The Access 2000 Menu Manager Add-in

Updated 13-Jan-2004Helen Feddema ([email protected])

Instructions

This Access 2000 add-in creates a main menu for an Access application, with drop-down lists for selecting database objects. (The add-in works in Access 2000 through Access 2003.) It consists of three menu add-ins, one to create the main menu, and two to perform housekeeping chores later on. To install and test the add-in, first copy the files listed below to the listed folders.

Table 1: File Locations

File NameInstall to Folder

Menu Manager.mdaAdd-ins folder (usually C:\WINDOWS\Application Data\Microsoft\AddIns

Test Database.mdbAny folder

Test Letter.dot\Templates

Next, open the Test Database.mdb included in the zip. This is a database containing some Northwind components, with the LNC naming convention applied, and a line of code added to the Close or Unload event of its forms to display the main menu when they are closed. Drop down the Tools menu, select the Add-ins command, and select Add-In Manager from the fly-out menu:

If you see a Menu Manager selection, just select it and click the Install button, as shown below; if you don't see it, click the Add New button and select Menu Manager.mda from its location in the Add-ins folder.

After closing the Add-in Manager dialog, you should see three new selections on the Add-ins menu:

Create Main Menu

This add-in creates a main menu for your application, with several large buttons with images, and combo boxes displaying lists of database objects for the user to select, as an alternative to the confusing (and difficult to maintain) array of pop-up menus created by the built-in Access Menu Wizard. One of the buttons (newly added in 2003) is used to make a backup of the database, with an incrementing number, using a technique described in Access Archon #115.

The menu also has Start Date and End Date text boxes, which can be used for report date ranges, and checkboxes to indicate whether the report should be opened in print preview, or just printed. It is assumed that you will generally have a primary form which users will want to open most often; Menu Manager identifies this form by the prefix fpri.

To create a main menu for an Access 2000 (or 2002) application, first select a form as the primary form to be opened by the big button on the menu, and give it the fpri prefix. Next, select the Create Main Menu command from the Add-ins menu. After some processing while the add-in creates lists of the forms, reports, and other database objects, the Picture Picker dialog opens, where you can enter a name for your application and select a sidebar picture for the main menu.

After clicking the Apply Picture button, the main menu is updated with your information, and a message box asks if you want to open it now.

After creating a main menu using the add-in, select Tools|Startup from the database window, and select fmnuMain as the Display Form/Page. From now on, when the database is opened, the main menu will automatically open.

The main menu is divided into sections containing graphical command buttons, some with adjacent combo boxes for selecting items, and an option group and a pair of text boxes (in the Reports section).

The large Orders button opens the application's primary form (in this case, fpriOrders). The primary form is indicated by the "fpri" prefix; its name is saved in tblInfo.

The Backup button offers to create a backup copy of the databse, including the date and an incrementing number. The backups are created in a folder called "Backups" under the database folder. This folder will be created if it doesn't already exist.

The Exit button closes the database and exits from Access.

The Other Forms button opens the form selected from its combo box, which lists all forms with Use = True in tlkpForms, excluding the primary form, system forms and other inappropriate entries, based on their LNC tags. To temporarily remove a form from the drop-down list (without removing it from the database), just set the Use field to False for the form's record in tlkpForms.

The Reports button and combo box work similarly, with the addition of a few extra controls useful for reports, where users can select to open the report in print preview, or just print it; and a set of date text boxes which can be used to filter a report by a date range (rptEmployeeSalesbyCountry uses this feature). To temporarily remove a report from the drop-down list (without removing it from the database), just set the Use field to False for the report's record in tlkpReports.

The Word Letters and Recipients button and combo boxes let you select a Word template and a recipient for a letter; Automation code on the command button fills custom document properties in the Word letter with name and address data from Access. The zip file includes a sample letter; a table of sample name/address data is also included in the database. To test this feature, select Test Letter in the Word Letters combo box, then select a recipient from Recipients, and click the Word command button.

Note: The tlkpLetters combo box must be filled manually with the names of the Word templates you create to fill with Access data. My Code Sample #24, Four Ways to Merge to Word, describes in more detail how to export Access data to Word in four different ways.

The tlkpForms and tlkpReports look-up tables contain several fields of useful information, other than what is displayed in the drop-down lists:

The DisplayName field is what shows in the drop-down list; the RecordSource lists the form or reports record source, and the Width field (for reports) gives the Detail width, which is used to create a LTR or LGL prefix to indicate whether reports use letter- or legal-sized paper.

The RecordSource property is used to determine whether or not a report has any records, before attempting to open it. This feature will only work with table or query record sources, so if you frequently use SQL statement record sources for reports, you can comment out (or delete) the lines of code that check the record source before opening the report.

The Use field is checked when you want the form or report to appear in the drop-down list on the menu; uncheck it to hide the form or report, for example for a form that is only opened from another form.

Change Menu Picture

This command lets you change the picture used on your main menu, opening the Picture Picker dialog again.

Refresh Lookup Tables

Re-runs the functions that fill the lookup tables with form and report names and other information; run this command after renaming, adding or deleting forms or reports.

Code

basMenuManager

Option Compare Database

Option Explicit

'Code needs references to the DAO, Scripting Runtime and Word object libraries

'Open the References dialog from the Tools menu in the VBE window

'to check if these references have been set

Dim appWord As Word.Application

Dim strCodeDB As String

Dim strCallingDB As String

Dim strTable As String

Dim dbs As DAO.Database

Dim rst As DAO.Recordset

Dim qdf As DAO.QueryDef

Dim tdf As DAO.TableDef

Dim strSQL As String

Dim strSearch As String

Dim intResult As Integer

Dim strForm As String

Dim frm As Access.Form

Dim rpt As Access.Report

Dim strReport As String

Dim strQuery As String

Dim rstSource As DAO.Recordset

Dim rstTarget As DAO.Recordset

Dim strPrimaryForm As String

Dim strMainMenu As String

Public pstrPicture As String

Public Function MenuManager()

Dim strNewMainMenu As String

Dim strMainMenu As String

strCodeDB = CodeDb.Name

strTable = "MSysObjects"

strMainMenu = "fmnuMain"

On Error Resume Next

'Delete old tables and queries in calling database (if they exist)

Set dbs = CurrentDb

With dbs.TableDefs

.Delete "tblInfo"

.Delete "tblBackupInfo"

.Delete "tlkpForms"

.Delete "tlkpLetters"

.Delete "tlkpReports"

.Delete "zstblSampleData"

End With

With dbs.QueryDefs

.Delete "zsqryForms"

.Delete "zsqryReports"

.Delete "qmaxDayNumber"

End With

'Delete subform if it exists

DoCmd.DeleteObject acForm, "fsubDayMax"

On Error GoTo ErrorHandler

'Check for existence of main menu, and rename it if found

strSQL = "SELECT MSysObjects.Name FROM MSysObjects WHERE " _

& "MSysObjects.Name Like " & Chr$(39) & strMainMenu & Chr$(39) & ";"

Debug.Print "SQL string: " & strSQL

Set dbs = CurrentDb

Set rst = dbs.OpenRecordset(strSQL)

If rst.RecordCount > 0 Then

DoCmd.CopyObject , "-OriginalfmnuMain", acForm, strMainMenu

If Forms(strMainMenu).IsLoaded Then DoCmd.Close acForm, strMainMenu

DoCmd.DeleteObject acForm, strMainMenu

End If

rst.Close

dbs.Close

'Copy objects from code database to calling database

DoCmd.TransferDatabase acImport, databasetype:="Microsoft Access", _

databasename:=strCodeDB, objecttype:=acForm, Source:="zsfmnuMain", _

Destination:=strMainMenu

DoCmd.TransferDatabase acImport, databasetype:="Microsoft Access", _

databasename:=strCodeDB, objecttype:=acForm, Source:="zsfsubDayMax", _

Destination:="fsubDayMax"

DoCmd.TransferDatabase acImport, databasetype:="Microsoft Access", _

databasename:=strCodeDB, objecttype:=acForm, Source:="zsfrmLargeButtons", _

Destination:="zsfrmLargeButtons"

DoCmd.TransferDatabase acImport, databasetype:="Microsoft Access", _

databasename:=strCodeDB, objecttype:=acTable, Source:="zstblSampleData", _

Destination:="zstblSampleData", structureonly:=False

DoCmd.TransferDatabase acImport, databasetype:="Microsoft Access", _

databasename:=strCodeDB, objecttype:=acTable, Source:="tblBackupInfo", _

Destination:="tblBackupInfo", structureonly:=False

DoCmd.TransferDatabase acImport, databasetype:="Microsoft Access", _

databasename:=strCodeDB, objecttype:=acTable, Source:="tlkpLetters", _

Destination:="tlkpLetters", structureonly:=False

DoCmd.TransferDatabase acImport, databasetype:="Microsoft Access", _

databasename:=strCodeDB, objecttype:=acQuery, Source:="qmaxDayNumber", _

Destination:="qmaxDayNumber"

DoCmd.TransferDatabase acImport, databasetype:="Microsoft Access", _

databasename:=strCodeDB, objecttype:=acQuery, Source:="zsqryForms", _

Destination:="zsqryForms"

DoCmd.TransferDatabase acImport, databasetype:="Microsoft Access", _

databasename:=strCodeDB, objecttype:=acQuery, Source:="zsqryReports", _

Destination:="zsqryReports"

DoCmd.TransferDatabase acImport, databasetype:="Microsoft Access", _

databasename:=strCodeDB, objecttype:=acModule, Source:="basUtilities", _

Destination:="basUtilities"

Call FillFormsTable

Call FillReportsTable

Call CreateInfoTable

'Open Picture Picker form to select sidebar picture for menu

DoCmd.OpenForm "fdlgPicturePicker"

ErrorHandlerExit:

Exit Function

ErrorHandler:

MsgBox "Error No: " & Err.Number & "; Description: " & _

Err.Description

Resume ErrorHandlerExit

End Function

Public Function CreateInfoTable() As Integer

On Error GoTo ErrorHandler

strTable = "tblInfo"

strMainMenu = "fmnuMain"

'Copy table from code database

DoCmd.TransferDatabase acImport, databasetype:="Microsoft Access", _

databasename:=strCodeDB, objecttype:=acTable, Source:="tblInfo", _

Destination:="tblInfo", structureonly:=False

'Check for existence of primary form, and save to tblInfo if found

strSQL = "SELECT MSysObjects.Name FROM MSysObjects WHERE "

strSQL = strSQL & "MSysObjects.Name Like 'fpri*';"

Set rst = dbs.OpenRecordset(strSQL)

If rst.RecordCount = 0 Then

Exit Function

ElseIf rst.RecordCount > 0 Then

strPrimaryForm = rst!Name

DoCmd.SetWarnings False

strSQL = "UPDATE tblInfo SET tblInfo.PrimaryForm = " & _

Chr$(34) & strPrimaryForm & Chr$(34) & ";"

DoCmd.RunSQL strSQL

End If

rst.Close

dbs.Close

ErrorHandlerExit:

Exit Function

ErrorHandler:

MsgBox "Error No: " & Err.Number & "; Description: " & _

Err.Description

Resume ErrorHandlerExit

End Function

Public Function FillFormsTable() As Integer

strTable = "tlkpForms"

strQuery = "zsqryForms"

'Delete old table in calling database (if it exists)

Set dbs = CurrentDb

On Error Resume Next

dbs.TableDefs.Delete strTable

On Error GoTo ErrorHandler

'Copy table from code database

strCodeDB = CodeDb.Name

DoCmd.TransferDatabase acImport, databasetype:="Microsoft Access", _

databasename:=strCodeDB, objecttype:=acTable, Source:="tlkpForms", _

Destination:="tlkpForms", structureonly:=True

'Fill table with form names and properties

Set rstTarget = dbs.OpenRecordset(strTable, dbOpenTable)

Set rstSource = dbs.OpenRecordset(strQuery, dbOpenDynaset)

Do Until rstSource.EOF

rstTarget.AddNew

strForm = rstSource!Name

rstTarget![ObjectName] = strForm

DoCmd.OpenForm strForm, acDesign

Set frm = Forms(strForm)

rstTarget!DisplayName = IIf(Nz(frm.Caption) = "", _

"[No caption]", frm.Caption)

If Nz(frm.RecordSource) "" Then

rstTarget!RecordSource = Nz(frm.RecordSource)

End If

DoCmd.Close acForm, strForm

rstTarget.Update

rstSource.MoveNext

Loop

rstTarget.Close

rstSource.Close

ErrorHandlerExit:

Exit Function

ErrorHandler:

MsgBox "Error No: " & Err.Number & "; Description: " & _

Err.Description

Resume ErrorHandlerExit

End Function

Public Function FillReportsTable() As Integer

strTable = "tlkpReports"

strQuery = "zsqryReports"

On Error Resume Next

'Delete old table in calling database (if it exists)

Set dbs = CurrentDb

dbs.TableDefs.Delete strTable

On Error GoTo ErrorHandler

'Copy table from code database

strCodeDB = CodeDb.Name

DoCmd.TransferDatabase acImport, databasetype:="Microsoft Access", _

databasename:=strCodeDB, objecttype:=acTable, Source:="tlkpReports", _

Destination:="tlkpReports", structureonly:=True

'Fill table with report names and properties

Set rstTarget = dbs.OpenRecordset(strTable, dbOpenTable)

Set rstSource = dbs.OpenRecordset(strQuery, dbOpenDynaset)

Do Until rstSource.EOF

rstTarget.AddNew

strReport = rstSource!Name

rstTarget![ObjectName] = strReport

DoCmd.OpenReport strReport, acDesign

Set rpt = Reports(strReport)

Debug.Print "Report caption: " & rpt.Caption

rstTarget!DisplayName = IIf(Nz(rpt.Caption) = "", _

"[No caption]", rpt.Caption)

If Nz(rpt.RecordSource) "" Then

rstTarget!RecordSource = Nz(rpt.RecordSource)

End If

rstTarget!Width = rpt.Width / 1440

DoCmd.Close acReport, strReport

rstTarget.Update

rstSource.MoveNext

Loop

rstTarget.Close

rstSource.Close

ErrorHandlerExit:

Exit Function

ErrorHandler:

MsgBox "Error No: " & Err.Number & "; Description: " & _

Err.Description

Resume ErrorHandlerExit

End Function

Public Function RefreshTables() As Integer

On Error GoTo ErrorHandler

'Check for existence of a form with the primary form prefix,

'and save its name to tblInfo if found

Set dbs = CurrentDb

strSQL = "SELECT MSysObjects.Name FROM MSysObjects WHERE "

strSQL = strSQL & "MSysObjects.Name Like 'fpri*';"

Set rst = dbs.OpenRecordset(strSQL)

rst.MoveLast

rst.MoveFirst

If rst.RecordCount = 0 Then

GoTo RefreshOtherTables

ElseIf rst.RecordCount > 0 Then

strPrimaryForm = rst![Name]

DoCmd.SetWarnings False

strSQL = "UPDATE tblInfo SET tblInfo.PrimaryForm = " & _

Chr$(34) & strPrimaryForm & Chr$(34) & ";"

DoCmd.RunSQL strSQL

End If

rst.Close

dbs.Close

RefreshOtherTables:

Call FillFormsTable

Call FillReportsTable

ErrorHandlerExit:

Exit Function

ErrorHandler:

MsgBox "Error No: " & Err.Number & "; Description: " & _

Err.Description

Resume ErrorHandlerExit

End Function

Public Function ChangeMenuPicture()

'Changes the sidebar picture for the main menu

On Error GoTo ErrorHandler

strMainMenu = "fmnuMain"

'Check for existence of main menu form

strSQL = "SELECT MSysObjects.Name FROM MSysObjects WHERE "

strSQL = strSQL & "MSysObjects.Name Like 'fmnuMain';"

Set dbs = CurrentDb

Set rst = dbs.OpenRecordset(strSQL)

If rst.RecordCount = 0 Then

MsgBox "No main menu found; can't change picture"

Exit Function

End If

DoCmd.OpenForm "fdlgPicturePicker"

ErrorHandlerExit:

Exit Function

ErrorHandler:

MsgBox "Error No: " & Err.Number & "; Description: " & _

Err.Description

Resume ErrorHandlerExit

End Function

fmnuMain

Option Explicit

Option Compare Database

Dim appWord As Word.Application

Dim dbs As DAO.Database

Dim rst As DAO.Recordset

Private Sub cmdBackup_Click()

On Error GoTo ErrorHandler

Dim dbs As DAO.Database

Dim rst As DAO.Recordset

Dim strCurrentDB As String

Dim strCurrentDBNoExt As String

Dim fso As Scripting.FileSystemObject

Dim strTitle As String

Dim strPrompt As String

Dim intReturn As Integer

Dim strDayPrefix As String

Dim strSaveName As String

Dim strBackupPath As String

Set fso = CreateObject("Scripting.FileSystemObject")

strCurrentDB = Application.CurrentProject.Name

'Trim off extension

strCurrentDBNoExt = Mid(strCurrentDB, 1, Len(strCurrentDB) - 4)

Debug.Print "Current db: " & strCurrentDB

strBackupPath = Application.CurrentProject.Path & "\Backups\"

strCurrentDB = Application.CurrentProject.Path & "\" & strCurrentDB

Debug.Print "Current db with path: " & strCurrentDB

strDayPrefix = Format(Date, "mm-dd-yyyy")

strSaveName = strCurrentDBNoExt & " " & SaveNo & ", " & strDayPrefix & ".mdb"

strSaveName = strBackupPath & strSaveName

Debug.Print "Backup save name: " & strSaveName

strTitle = "Database backup"

strPrompt = "Save database to " & strSaveName & "?"

intReturn = MsgBox(strPrompt, vbYesNo, strTitle)

If intReturn = vbYes Then

Set dbs = CurrentDb

Set rst = dbs.OpenRecordset("tblBackupInfo")

With rst

.AddNew

![SaveDate] = Format(Date, "mm-dd-yyyy")

![SaveNumber] = SaveNo

.Update

.Close

End With

fso.CopyFile strCurrentDB, strSaveName

Me.Refresh

End If

ErrorHandlerExit:

Exit Sub

ErrorHandler:

MsgBox "Error No: " & Err.Number & "; Description: " & _

Err.Description

Resume ErrorHandlerExit

End Sub

Private Sub cmdExit_Click()

On Error GoTo ErrorHandler

Application.Quit

ErrorHandlerExit:

Exit Sub

ErrorHandler:

MsgBox "Error No: " & Err.Number & "; Description: " & _

Err.Description

Resume ErrorHandlerExit

End Sub

Private Sub cmdForms_Click()

On Error GoTo ErrorHandler

Dim strFormName As String

strFormName = Nz(Me![cboForms])

If Nz(Me![cboForms]) "" Then

strFormName = Me![cboForms]

DoCmd.OpenForm strFormName

Me.Visible = False

Else

Me![cboForms].SetFocus

Me![cboForms].Dropdown

End If

ErrorHandlerExit:

Exit Sub

ErrorHandler:

MsgBox "Error No: " & Err.Number & "; Description: " & _

Err.Description

Resume ErrorHandlerExit

End Sub

Private Sub cmdLetters_Click()

On Error GoTo ErrorHandler

Dim strLetter As String

Dim strRecipient As String

Dim strTestFile As String

Dim ctl As Access.Control

Dim docs As Word.Documents

Dim prps As Object

Dim strDocsPath As String

Dim strTemplatePath As String

'Check that a letter has been selected

strLetter = Nz(Me![cboLetters])

Set ctl = Me![cboLetters]

If strLetter = "" Then

ctl.SetFocus

ctl.Dropdown

Exit Sub

End If

'Check that a recipient has been selected

strRecipient = Nz(Me![cboRecipients])

Set ctl = Me![cboRecipients]

If strRecipient = "" Then

ctl.SetFocus

ctl.Dropdown

Exit Sub

End If

Set appWord = GetObject(, "Word.Application")

strDocsPath = DocsDir

strTemplatePath = TemplateDir

strLetter = strTemplatePath & strLetter

'Check for existence of template in template folder,

'and exit if not found

strTestFile = Nz(Dir(strLetter))

Debug.Print "Test file: " & strTestFile

If strTestFile = "" Then

MsgBox strLetter & " template not found; can't create letter"

Exit Sub

End If

Set docs = appWord.Documents

docs.Add strLetter

Set ctl = Me![cboRecipients]

On Error Resume Next

Set prps = appWord.ActiveDocument.CustomDocumentProperties

prps.Item("Name").Value = Nz(ctl.Column(6))

prps.Item("Street").Value = Nz(ctl.Column(1))

prps.Item("City").Value = Nz(ctl.Column(2))

prps.Item("State").Value = Nz(ctl.Column(3))

prps.Item("Zip").Value = Nz(ctl.Column(4))

prps.Item("Country").Value = Nz(ctl.Column(5))

On Error GoTo ErrorHandlerExit

'Update fields and make letter visible

With appWord

.Visible = True

.Selection.WholeStory

.Selection.Fields.Update

.Visible = True

.Activate

End With

ErrorHandlerExit:

Exit Sub

ErrorHandler:

If Err = 429 Then

'Word is not running; open Word with CreateObject

Set appWord = CreateObject("Word.Application")

Resume Next

Else

MsgBox "Error No: " & Err.Number & "; Description: " & Err.Description

Resume ErrorHandlerExit

End If

End Sub

Private Sub cmdPrimaryForm_Click()

On Error GoTo ErrorHandler

Dim strPrimaryForm As String

Dim strTable As String

Dim strPrompt As String

Dim intReturn As Integer

strPrompt = "Please select a form as the primary form for the database"

strPrimaryForm = Nz(Me![PrimaryForm])

If strPrimaryForm = "" Or strPrimaryForm = "fpri????" Then

intReturn = MsgBox(strPrompt, vbOKOnly, "No primary form")

GoTo ErrorHandlerExit

End If

If FormExists(strPrimaryForm) = False Then

intReturn = MsgBox(strPrompt, vbOKOnly, "No primary form")

strPrompt = "The designated primary form is not in the database"

intReturn = MsgBox(strPrompt, vbOKOnly, "Primary form not found")

GoTo ErrorHandlerExit

Else

DoCmd.OpenForm strPrimaryForm

Me.Visible = False

End If

ErrorHandlerExit:

Exit Sub

ErrorHandler:

MsgBox "Error No: " & Err.Number & "; Description: " & _

Err.Description

Resume ErrorHandlerExit

End Sub

Private Sub cmdReports_Click()

On Error GoTo ErrorHandler

Dim strReportName As String

Dim strRecordSource As String

If Nz(Me![cboReports]) "" Then

strReportName = Me![cboReports]

strRecordSource = Me![cboReports].Column(2)

If Nz(DCount("*", strRecordSource)) > 0 Then

If Me![fraReportMode] = 1 Then

DoCmd.OpenReport ReportName:=strReportName, view:=acPreview

ElseIf Me![fraReportMode] = 2 Then

DoCmd.OpenReport ReportName:=strReportName, view:=acNormal

End If

Else

MsgBox "No records for this report"

GoTo ErrorHandlerExit

End If

Else

Me![cboReports].SetFocus

Me![cboReports].Dropdown

End If

ErrorHandlerExit:

Exit Sub

ErrorHandler:

MsgBox "Error No: " & Err.Number & "; Description: " & _

Err.Description

Resume ErrorHandlerExit

End Sub

Private Sub Form_Unload(Cancel As Integer)

'Closes out database objects and releases all memory

'From MSDNFlash

On Error Resume Next

Dim wks As DAO.Workspace

For Each wks In Workspaces

For Each dbs In wks.Databases

For Each rst In dbs.Recordsets

rst.Close

Set rst = Nothing

Next

dbs.Close

Set dbs = Nothing

Next

wks.Close

Set wks = Nothing

Next

End Sub

Public Function DocsDir() As String

On Error GoTo ErrorHandler

Set appWord = GetObject(, "Word.Application")

DocsDir = appWord.Options.DefaultFilePath(wdDocumentsPath) & "\"

ErrorHandlerExit:

Exit Function

ErrorHandler:

If Err = 429 Then

'Word is not running; open Word with CreateObject

Set appWord = CreateObject("Word.Application")

Resume Next

Else

MsgBox "Error No: " & Err.Number & "; Description: " & Err.Description

Resume ErrorHandlerExit

End If

End Function

Public Function TemplateDir() As String

On Error GoTo ErrorHandler

Set appWord = GetObject(, "Word.Application")

TemplateDir = appWord.Options.DefaultFilePath(wdUserTemplatesPath) & "\"

ErrorHandlerExit:

Exit Function

ErrorHandler:

If Err = 429 Then

'Word is not running; open Word with CreateObject

Set appWord = CreateObject("Word.Application")

Resume Next

Else

MsgBox "Error No: " & Err.Number & "; Description: " & Err.Description

Resume ErrorHandlerExit

End If

End Function

Private Sub txtFromDate_AfterUpdate()

On Error GoTo ErrorHandler

DoCmd.RunCommand acCmdSaveRecord

ErrorHandlerExit:

Exit Sub

ErrorHandler:

MsgBox "Error No: " & Err.Number & "; Description: " & _

Err.Description

Resume ErrorHandlerExit

End Sub

Private Sub txtToDate_AfterUpdate()

On Error GoTo ErrorHandler

DoCmd.RunCommand acCmdSaveRecord

ErrorHandlerExit:

Exit Sub

ErrorHandler:

MsgBox "Error No: " & Err.Number & "; Description: " & _

Err.Description

Resume ErrorHandlerExit

End Sub

Public Function SaveNo() As String

On Error GoTo ErrorHandler

Dim strDBPath As String

Dim strBackupPath As String

Dim fso As Scripting.FileSystemObject

Dim fld As Scripting.Folder

Dim intDayNo As Integer

Dim strNextNo As String

'Save a copy of database

strDBPath = Application.CurrentProject.Path & "\"

strBackupPath = strDBPath & "Backups\"

'Check whether the backup path folder exists

Set fso = CreateObject("Scripting.FileSystemObject")

If Not fso.FolderExists(strBackupPath) Then

'Create folder if necessary

Set fld = fso.CreateFolder(strBackupPath)

End If

'Create unique save number for today

intDayNo = CInt(Nz(Forms![fmnuMain]![subDayMax].Form![DayMax]))

strNextNo = CStr(intDayNo + 1)

Debug.Print "Next No. " & strNextNo

SaveNo = strNextNo

ErrorHandlerExit:

Exit Function

ErrorHandler:

MsgBox "Error No: " & Err.Number & "; Description: " & _

Err.Description

Resume ErrorHandlerExit

End FunctionfdlgPicturePicker

Option Compare Database

Option Explicit

Dim dbs As dao.Database

Dim rst As dao.Recordset

Dim strSQL As String

Dim strAppTitle As String

Private Sub cmdApplyStyle_Click()

On Error GoTo ErrorHandler

Dim strMainMenu As String

Dim frm As Form

Dim intResult As Integer

strMainMenu = "fmnuMain"

'Check for existence of main menu and close it if it is open

strSQL = "SELECT MSysObjects.Name FROM MSysObjects WHERE "

strSQL = strSQL & "MSysObjects.Name Like 'fmnuMain';"

Set dbs = CurrentDb

Set rst = dbs.OpenRecordset(strSQL)

If rst.RecordCount = 0 Then

MsgBox "No main menu; can't change picture"

Exit Sub

ElseIf rst.RecordCount > 0 Then

On Error Resume Next

DoCmd.Close acForm, strMainMenu

End If

strAppTitle = Nz(Me![txtAppTitle], "Application Title")

Set dbs = CurrentDb

Set rst = dbs.OpenRecordset("tblInfo", dbOpenTable)

With rst

.Edit

!AppTitle = strAppTitle

.Update

.Close

End With

DoCmd.OpenForm strMainMenu, acDesign

Set frm = Forms![fmnuMain]

Call MakeControlsInvisible(frm)

frm.Controls(pstrPicture).Visible = True

DoCmd.Close acForm, strMainMenu, acSaveYes

DoCmd.Close acForm, Me.Name, acSaveNo

intResult = MsgBox("Open main menu now?", _

vbYesNo + vbQuestion + vbDefaultButton2, "Question?")

If intResult = vbYes Then

DoCmd.OpenForm strMainMenu, acNormal

End If

ErrorHandlerExit:

Exit Sub

ErrorHandler:

MsgBox "Error No: " & Err.Number & "; Description: " & Err.Description

Resume ErrorHandlerExit

End Sub

Private Sub Form_Load()

On Error GoTo Form_LoadError

Set dbs = CurrentDb

Set rst = dbs.OpenRecordset("tblInfo", dbOpenTable)

strAppTitle = Nz(rst!AppTitle, "Application Title")

Me![txtAppTitle] = strAppTitle

Form_LoadExit:

Exit Sub

Form_LoadError:

MsgBox Err.Description

Resume Form_LoadExit

End Sub

Private Sub fraPicture_AfterUpdate()

On Error GoTo ErrorHandler

Dim intPicture As Integer

intPicture = Me![fraPicture]

Call MakeControlsInvisible(Me)

Select Case intPicture

Case 1

pstrPicture = "imgBooks"

Me.Controls(pstrPicture).Visible = True

Case 2

pstrPicture = "imgContacts"

Me.Controls(pstrPicture).Visible = True

Case 3

pstrPicture = "imgMusic"

Me.Controls(pstrPicture).Visible = True

Case 4

pstrPicture = "imgFood"

Me.Controls(pstrPicture).Visible = True

Case 5

pstrPicture = "imgHousehold"

Me.Controls(pstrPicture).Visible = True

Case 6

pstrPicture = "imgInventory"

Me.Controls(pstrPicture).Visible = True

Case 7

pstrPicture = "imgMembers"

Me.Controls(pstrPicture).Visible = True

Case 8

pstrPicture = "imgMoney"

Me.Controls(pstrPicture).Visible = True

Case 9

pstrPicture = "imgPhoneOrders"

Me.Controls(pstrPicture).Visible = True

Case 10

pstrPicture = "imgPhotos"

Me.Controls(pstrPicture).Visible = True

Case 11

pstrPicture = "imgResources"

Me.Controls(pstrPicture).Visible = True

Case 12

pstrPicture = "imgSchool"

Me.Controls(pstrPicture).Visible = True

Case 13

pstrPicture = "imgVideos"

Me.Controls(pstrPicture).Visible = True

Case 14

pstrPicture = "imgWorkout"

Me.Controls(pstrPicture).Visible = True

End Select

ErrorHandlerExit:

Exit Sub

ErrorHandler:

MsgBox "Error No: " & Err.Number & "; Description: " & Err.Description

Resume ErrorHandlerExit

End Sub

Sub MakeControlsInvisible(frm As Access.Form)

On Error GoTo ErrorHandler

Dim ctl As Access.Control

For Each ctl In frm.Controls

If ctl.ControlType = acImage Then

ctl.Visible = False

End If

Next ctl

ErrorHandlerExit:

Exit Sub

ErrorHandler:

MsgBox "Error No: " & Err.Number & "; Description: " & Err.Description

Resume ErrorHandlerExit

End Sub

References

The add-in requires the following references (in addition to the standard ones):

DAO 3.6

Word 9.0 (or higher)Microsoft Scripting Runtime

References are set in the References dialog, opened from the VBA window. For more information on working with references, see Access Archon #107, Working with References.Notes

The images on the Picture Picker form were the available images for Office 97. These images can be resized considerably without distortion, and display well even on low-resolution monitors. Office 2000 (and Office XP) have a different set of images, which dont work as well on menus, so I moved the Office 97 images into the add-in database, so there is no need to pick them up from a folder on your computer, as in the Access 97 version of this add-in. The fdlgPicturePicker form has all the images stacked up on top of each other; when you select an image, the MakeControlsInvisible sub makes all the Image controls invisible, and then the selected one is made visible. If you don't anticipate needing to change the menu picture, you can delete all the images other than the one you want to use.

You can eliminate the need to refresh the lists of tables and reports by using SQL statements based on the MSysObjects table as the row sources for the combo boxes; however, this eliminates the possibility of removing certain objects from the drop-down lists (say, because they are under development) by unchecking the Use checkbox. Also, this method doesnt allow you to specify a different display name for the combo box, or to store the record source or report width. Creating the look-up tables takes longer, but they are more useful.

For full details on an earlier version of this add-in, see my article in the April 1999 issue of Smart Access. Smart Access is published by Pinnacle, http://www.pinpub.com.

Contents of Zip File

File NameFile TypeDestination Folder

Menu Manager.mdaAccess 2000 add-in (works in 2000 through 2003)Add-ins folder (usually C:\WINDOWS\Application Data\Microsoft\AddIns

Test Database.mdbAccess 2000 database \My Documents (or wherever you want)

Test Letter.dotWord 2000 template \Templates

VBA Code Sample 12 The Access 2000 Menu Manager Add-in.docWord 2000 Document \My Documents (or wherever you want)

VBA Code Sample #12

Page 23 of 23