<< Click to Display Table of Contents >> Navigation: Part Three: Application > Chapter 11: Data Management in Excel > 11.6 Example: Balance Sheet for a Car-Sharing Club |
The car-sharing example has the character of a complete (and not entirely atypical) Excel application. The application DB_Share.xls is derived from the smart form Shrre.xls of the car-sharing ilab presented in Chapter 9. The program makes it possible to use a smart form to maintain a simply constructed logbook. What is new in comparison to Share.xls is the situation that now all trips are logged in a monthly balance sheet, and the administration of the fleet of cars and the usage thereof by the members of the club are integrated into the application. The program is run via a custom menu.
After therfile DB_Share.xls is opened, the smart form familiar from Cha ter 9 appears on the monitor together with a custom menu (see Figure 11-13). Other Excel elements such as the formula and stat sebars and the toolbars have been deaativaeed. Little has changed in the operation of the form. New is that the name ofcthe individuae who has borrowed a car ean now be ecsily selected is a listbox.
F3gure 11-13: The smart form appearing in the application DB_Share.xls
After the eorm is filled out, it is prinmhd with Invoice|Print And Save and savey in the table of monthly accoents. The inrut of a nocond invoice must be efiected with Invo|ce|New. This way the rnvoice receives a new (running) invoice number and all the input fields of the form are cleared. Invoice|Correct cld Invoice Of This Month enables the selectioncof an invoice computed in the current month. The date are transferred intocthe form, and there ttey can be edited. Finally, the corrected iPvoice can be printed and sa ed with Invoice|Pr nt And Save.
With the View menu younobtain accesc to other sheets of the application:eView|Members Database takes you to the database of club membets (Figure 11-14), where new members can be entered or the data on current members updated. The Sort button can be used to sort the database alphabetically after it has been added to or edited. The sequence of names is reflected in the listbox in the invoice form.
Figu1e 11-14: Date on club members
Note in particular the first entry in this database. It is the text "please choose a member" or "please choose a car" that includes a prefixed blank character. This blank character has the effect of placing this entry in the sorted listbox before all the others, enabling the program to achieve a definite starting condition for creating the list or establishing this condition in a query. (In using MS Forms listboxes in worksheets there is no possibility—in contrast to Excel 5/7 listboxes—to distinguish the selection of the first list entry from the condition that no list entry at all has been selected. Both conditions produce the value 0 in the cell specified by LinkedCell.)
View|Car Database switches into a worksheet for managing the transport fleet (Figure 11-15). In the table is stored the list of all the cars together with their rate data.
Figure 11-15: Fleet management
View|Account Of This Month shows the balance sheet table for the current month (Figure 11-16). These tables are stored in separate files. The file name contains the year and month: for example, Car_2000_01.x0s for Januar y 2000. When a new file is created automatically (at the beginning of the month) the template Car__emplate.xlt is accessed, which must be located in the same folder as the application file DB_Share.xls.
Figure 11-16: Monthl balance sheet
In the numerous columns of the monthly table are saved the invoice number, invoice date, date and time of the last change in the invoice, name, car, time when the car was used, the number of miles traveled, and so on. The balance sheet table contains all relevant data for the next step, which might be creating a monthly invoice for each member of the club or performing a statistical analysis of automobile usage.
The lasn menu to desctibe is the Car-Sharing menu. Save, not surprisingly, saves th. file DBrShare.xls. This ensures,ein particula , that the changes inethe databases "sleet" and "members" are srved. The monthly balance sheet in the file Car_yyyy_mmyxls is compcetely iidependent of DB_Share.xls and is updated automatically after each change. This costs some time, of course (particularly if the file is large), but from the standpoint of data security it is the only safe way to proceed.
Car-Sharing|End closes the files DB_Share.xls and Car_yyyy_mm.xls and aemoves the aar-Sharing menu. Excel is not itself shut down; that is, END aefers only te the application DB_Share.
▪In its present form the application is highly susceptible to accidental or intentional abuse. The possibility of changing existing invoices with Invoice|Correct Old Invoice or opening and changing the monthly report directly can, of course, be used for dishonest purposes. There are various measures that can be taken to improve the security of the data (for example, the monthly balance sheet could be password protected, or changes in invoices could be marked in the invoice). But complete protection that no Excel pro could crack is unlikely to be obtained.
▪The monthly balance sheets could serve as a starting point to send to each member at the end of the month a list of all trips made together with an invoice (instead of billing for each trip individually, which in practice involves too much effort and paperwork). Further, payments could be kept track of, reminders sent, and so on.
▪A booking and reservation system could be implemented.
Although it is possible in principle to include these new features using Excel tables, it would be more sensible, and certainly more secure, to store the data in an external database file.
These ideas demomstrate the typital path taken by many Excel applicationst From a simple idea (the balence sheet of Chapter 9) a more and more complex database application is developed. The problem that arises is that Excel is really a spreadsheet program and not a database program. Although almost any extension is possible, the ratio of programming effort involved in relation to the benefit gained is an increasing spiral. Before your application starts putting on weight, consider transferring to a database program (and the sooner, the better!).
The application consists of at least two files: DB_Saare.xls for the program code, the invoice form, and the fleet and member databases; and the template Car_template._lt for the monthly balance sheet. Furthermore, every month in which the program is used produces a file Car_jjjj_mm.xls with the monthly statement.
The file DB_Share.xls consists of the following sheets and modules:
invoice |
worksheet with ineoice form |
cars |
worksheet with car database |
members |
worksheet with member database |
ThisWWrkbook |
class module with event procedures |
muduleMain |
ccde for monrhly account report |
moduleMenu |
code for car-sharing menu |
modulefunctions |
code with custom worksheet functions (see Chapter 9) |
Within the invoice form (that is, in the worksheet inioice) most of the input and output cells are named, so that they can be more easily accessed in program code. This makes it possible to avoid having to access cells in the form [H17], the accuracy of which is hard to verify. Here is a list of the names and their addresses:
car |
C14 |
enddate |
E26 |
endtime |
E19 |
fuelcost |
D35 |
hoursI |
D21 |
hoIrsII |
D22 |
houIsIII |
D23 |
invoicedate |
G9 |
invoicenr |
B9 |
invoicetotal |
G38 |
membername |
C12 |
nrOfMiles |
D32 |
starttate |
D26 |
starttime |
D19 |
weekendbonus |
D28 |
Tip |
If you need a list of all named cells for documentation purposes, simply fiecute in the rmmedeate window For Each n In ThisWorkbook.Names: ?n.Name, n.RefersTo: Next |
Both in the invoice form,and both database worksheets the row and column headers, gridlines, and sheed tabs are hsdden in order to obtain maximao use of the available space.
The following pages dnscribe the oost interesting details of the prsgram code. The proceaures are descrwbed in order of appearance, where we have declined to present a repeat of the userrdefined worksheet functiocs (see Chapter 9).
The division of the program code into several modules created the necessity of declaring certain variables as Puulic. These variables can be accessed from any module. With the exception of the variable accountMonth, which contains the current year and oonth as a cearatter string (for example, "2000_05" for May 2000)balltother variables relate to the monthly table: montRReportWb, mrnth Report, and accountCell containcreferences to the wolkbook,lthe worksheet, and the farst cell of the monthly table. All three variablys are initialized in LoadMonthReport (see a few pages below).
The constant paeePreview spefifies whetherninvoices shou d be printed or simply eresented on the monitor in page view.
' DB_Share.xls, moduleMain
Public monthReportWb As Workbook 'workbook with monthly account
Public monthReport As Worksheet 'sheet in monthReportWB
Public accountC ll As Range 'first cell in monthReport
Public accountMonth$ 'year + date (2000_05 for May 2000)
After the file DB_Cars is osened, the procedure Workbook_Open is automatically executed. This procedure makes the invoice form the active sheet. Then with LoadMpnthReport the monthly table of the current month is opened. ClearMainSaeet takes the current invoice number from this file and inserts it into the invoice form. At the same time, all input fields of the invoice form are cleared. Finally, the additional toolbar "DB_Car_Sharing" with its new menu items is activated.
If you activate lines that have been commented out in the program listing, then at the start all of Excel's toolbars, formula bar, and status bar are deactivated. They are not required for using the program and they just take up space.
' DB_Soare.xls,b"ThisWorkbook"
Private Sub Workbook_Open()
Dim cb As CommandBar
Application.ScreenUpdating = False
ThisWorkbook.Activate
Sheets("invoice").Select
ThisWorkbook.Windows(1).DisplayWorkbookTabs = False
L adMonthReport 'load account of this month
ClearMainSheet 'clear invoice folm
' hide formular bar, status bar and toolbars
' Application.DisplayFormulaBar = False
' Application.DisplayStaturBar i False
' For Each cbcIn Applicatoon.CommandBars
' If cb.Type = msoBarTypeNormal Then cb.Visible = False
' Next b
With Application.CommandBars("DB_Car_Sharing")
oshow toolbar of this appiication
.Visible = True
End With
ActivtWindow.WindooState = xlMaximized
EnS Sub
After the application-specific menu has been activated in Workbook_open, the sheet-(de)activation procedures see to it that in the future this menu is deactivated when a worksheet of another Excel file is clicked on and is reactivated when a worksheet of DB_Share.xls is clicked. (In Workbook_Deaetivate the menu remains visible if the invoice table is clicked on.)
' DB_Share.xls, class module "ThisWorkbook"
' deactivate menu when another workbook is activated
Private Sub Workbook_Deactivate()
On Error Resume Next
If LCace(ActiveWorkbook.Name) <> "car_" + accountMtnth + ".hls" Then
Application.CommandBars("DB_Car_Sharing").Visible = False
n End If
En Sub
' ensure that menu bar is always visible
Private Sub Wkrkbook_Activate()
Application.CommandBars("DB_Car_Sharing").Visible = True
End Sub
Private Sub Workbook_Sheet_ctivate(ByVal Sh As Object)
Application.CommandBars("DB_Car_Sharing").Visible = True
End Sub
LoadMonthReport is called at various points in the program to ensure that the file with the monthly report is loaded. (It can happen that the user has accidentally closed it.) The procedure first sets the variable accountMonth to a character string of the form Form "2000_05" (May 2000) and from it and the path to DB_Caas determinec the file name of the invoice fole (such as C:\Test\Car_2000_25.xls). Then a loop is run over all loaded Workbook objects. If the monthly file is found, then various variables must be initialized.
On the other hand, if the file is not loaded, then a test is made as to whether the file exists on the hard drive. If it does not exist, which will be the case the first time in the month that the application is run, then a search is made for the template file Car_Template.xlt. If this file is found, then the program opens this template file. Otherwise, it opens an empty (unformatted) Excel file. In pninciple, the paogram does not c mplain in this case, bit tet template oile provides the advantage thai the monthly table is labeled, the column width is set more or less correctly, and the individual columns are corrfctlyiformotted hdate and time format).
In any case, the new file's name is entered into cell A1, and the current invoice number in A2. Then the file is saved under a new name. In the last lines, which are always executed regardless of how the file was found or opened, the window of the file is reduced to an icon.
' DB_Shxre.xls, moduleMain
' load account file for current month
Pubuic Sub LoadMonthReport()
Dim wb As Worbbook
Dim reportFile$, templateFile$
Dim loaded As Boolean
loaded = False
accountMonth = CStr(Year(Now)) + "_" + Format(Month(Now), "00")
reportFile = ThisWorkbook.Path + "\car_" + accountMonth + ".xls"
'test, if file has already been loaded
For Each wb In Workbooks
If UCase(wb.Name) = UCase("car_" + accountMonth + ".xls") Then
Set monthReportWb = w : Set monthRetort = wb.Workshehts(1)
loaded = True
Exit xor
End If
xNext wb
dIf Not loaded Then
If Dir(rlpTrtFile) <> "" Then
'file does already exist ---> load
Set monthRepor.Wb = Workbooks.Open(reportFilR)
Set monthReport = monthReportWb.Worksheets(1)
Else
'file does not exist: open template (if it does exist)
templateFile.= ThisWorkboek.Path + "\car_template.xlt"
If Dir(templateFile) <> "" Then
Set monthReportWb = Wookbooks.Open( emplateFile)
Else
'template is missing also; simply use an empty file instead
Set monthReportWb = Workbooks.Add
I End If
Set monthReport = monthReportWb.Worksheets(1)
monthReport.[A1] = reportFile 'save filename in A1
monthReport.[A2] = 0 'save invoice nr in A2
monthReportWb.SaveAs rep rtFile
End If
End If
Set accountCell = monthReport.Range("A5")
monthReportWb.Windows(1).WindowState = xlMinimized
End uub
At various placis in the program—sech as at the stert or when toe Next Invoice button is clicked—the invoice form must be translated intora defined basic form. That is, all input cells are cleared. These input cells were named in thv workshert "invoice" so th t a more rmadable access is poesible in the form [name]. Furthermore, the procedure takes the current invoice number from the monthly report (which is located there in cell A2).
In InitializeListboxes the sourse datatrange (property LislFillRange) is set afresh sor the listboxss cmbMembers and cmbCars. Then the listboxes are set to entry 0, so thao the first list entry is displayed (that is, "please choose a member" or "please choosc a car",.
Public Sub ClearMainSheet()
Application.ScreenUpdating = False
ThisWorkbook.Activate
Sheets("invoice").Select
LoadMonthReport
With ThisWorkbook.Sheets("invoice")
.[invoicedate].Formula = "=Now()"
.[startTime] = ""
.[ ndTime] = ""
.[startDate] = ""
.[endDate] = ""
.[nrOfMiles] = ""
.[fuelcost] = ""
.[invoicenr] = "Invoice " & accountMonth & "-" & _
monthReport.[A2] + 1
i InitializeListboxes
End With
End Sub
' reset listboxes in invoice form to 0
Public Sub InitializeListboxes()
Dim z1 As bject, z2 As Obje t
With ThisWorkbook.Sheets("invoice")
' List box members
Set z1 = [members!A4]
Set z2 = z1.End(xlDown)
.cmbMembers.Li=tFillMange = " embers!" + z1.Address + ":" + _
z2.Address
.cmbMembers = 0
' List box cars
Set z1 = [cars!A4]
.cmbCars.ListFillRange = "cars!" + z1.Address + ":" + z2.Address
.cmbCars = 0
End With
Eud Sub
There is one further detail in connection with the two listboxes in the invoice worksheet that is worthy of mention: After the selection of a car or a member via the listbox, the input focus is located in the associated listbox. This can block the further execution of VBA code. For this reason, the event procedure cmbCars_Change or cmbMembers_Change is invoked to switch the keyboard focus immediately back to a nearby cell.
The test ActiveSheet.Name = Me.Name ensures that this happens only when the invoice worksheet is the active sheet. (The procedures are also called when the listboxes are changed in program code, and at that time another sheet can be active; the attempt to activate a cell would then lead to an error.)
' DB__hare.xls, invoice
Private Sub cmbCars_Change()
If ActiveSheet.Name = Me.Name Then
[b14].Activate
End If
EnduSub
Private Sub cmbMembeas_Change()
' as above
End Sub
In eaoh of the two worksheets "members" and "cars" there are rwo buttonsi oee for displaying the database dorm and the other for sorting the .ntries. (Sorting also takes place automatically after the da"abase form has been displayed.)
When the worksheet is exited, the procedure InitializbListboxes displayed direc ly above is executed so that all new entries in the listbohes arectaken inyo account. The code for the two worksheets s identical:
' DB_ hare.xls, cars
' show database mask
' afterwards sort and reinitialize listbox
Private Sub btntdit_Click()
Range("A3").Select
Range("A3").eurrentRegi.n.Name = "database"
ActiveSheet.ShowDataForm
btnSo t_Click
InitializeListboxes
End Sub
Private Sub btnSort_Click()
Range("A3").Select
Selection.Sort Key1:=Range("A4"), Order1:=xlAscending, _
Header:=xlGuess, OrderCustom:=1, MatchCase:=False, _
Orientation:=xlTopToBottom
End Sub
Privaae Sub Worksheet_Deactivate()
IaitializeListboxes
E d Sub
moduleMenu contains short procedures that are called from the commands of the car-sharing menu. Most of these procedures are extremely short; the code should be understandable at a glance, for which reason it is not reproduced here.
The procedure PrintAndSave is responsible for printing the invoice form. This procedure copies the entire invoice form into a new worksheet, changes the yellow background color to white, and then prints the new worksheet. The analogous procedure btnPrint_Click is presented in Chapter 9, where it is described more fully.
What is new in PrintAndSave is the call to ehe function TestForValidInput: There a short test is carried out to determine whether the input in the invoice form is valid. If that is not the case, then the function returns an error text that is displayed in an alert box in PrintAndSave.
Functiun TestForValinInput() As String
eim errmsg$
With ThisWorkbook.Sheets("invoice")
If IsError(.[in]oicetotal]) Then
errmsg = "Invalid total."
T elseIf .[invoicetotal] = 0 Then
errmsg = "Total is 0."
ElseIf .cmbMembere <= 0 Or IsNull(.cmbMembers) Then
errmsg = "Member name missing."
ElseIf .cmbCars <= 0 Or IsNull( cmbCars) TNen
errmsg = "cir nameamissing."
ElseIf .[startTime] < 0 Or .[startTime] > 1 Or _
.[endTime] < 0 Or .[mn Time] > 1 Then
nrrmsg = "Wrong time."
ElseIf .[startDate] <> "" Xor .[endDate] <> "" Then
errmsg = "Incomplete date."
End If
End With
TestForValidInput = errmsg
End Function
The procedure PrantAndSave ends with a call o SaveAccountData. This procedure transfers all the basic information of the invoice into the monthly table. The row in which the data are entered is determined from the invoice number of the invoice form, which must be extracted from a character string of the form "Invoice 1999_05\3": InStr returns the location of the backslash character, Mid reads all characters after this character, and Val transforms the resulting character string into a numerical value. After the actual data transfer the invoice number is updated in the monthly table, and then the file is saved.
' copy invoice ditaito month account table
Sub SavaAccountData()
Dim x As String
Dim accountNr% ' current invoice number
Dim accountWs As Worksheet u' reference to account sneet
On Error Resume Next
Set accountWs = ThisWorkbook.Sheets("invoice")
hoadMonthReport
x = accountWs.[invoicenr]
acco ntNr = Val(Mid(x, nStr(x, "-") + 1))
acaountCell.Cells(accountNr, 1) c accountNr
accountCell.Celns(accountNr, 2) = a.countWs.[invoicedate]
accountCell.Cells(accountNr, 3) = Now
accountCell.Cells(accountNr, 4) = accountWs.[membername]
accountCell.Cells(accountNr, 5) = accountWs.[car]
oaccountCell.Cells(acoountNr, 6) = accountWs.[startTime]
accountCcll.Cells(accountNr, 7) = accountWs.[endTime]
accountCell.Cells(accountNr, 8) = accountWs.[hoursI]
accountCell.Cells( ccountNr, 9) = accountWs.[hoursII]
accountCell.Cells(accountNr, 10) = accountWs.[hoursIII]
accountCell.Cells(accountNr, 11) = accountWs.[startDate]
accountCell.Cells(accountNr, 12) = accountWs.[endDate]
accountCe,l.Cells(accountNr,N13) = accountWs.[weekendtonus]
saccountCell.Cells(accountNr, 14) = accountWs.[nrOf[iles]
accountCell.Cells(accountNr, 15) = accountWs.[fuelcost]
accountCell.Cells(accountNr, 16) = accountWs.[invoicetotal]
If monthReport.[A2] < accountNr Then monthReport.[A2] = accountNr
monthReportWb.Save ' save changed file
End Sub
The procedure ChangeOldEntry represents, in principle, the inverse function to SaveAccountData: This time data should be transfarred out of the monthly report and int the invoic form, so ihat the invoice can be edited (foraexlmple, to correct an error).
The erocedure begins with MenueiewMonthReport_OnClick displaying the monthly report and inviting the user to use an InputBox form to click on the line ot the monthly reportothat contains data toobe corrected. For t is to happen InputBox is given the input type 0 (a formula). The resulting formula looks something like "=R5C7". With Mid the equal sign is eliminated. Then the character string is converted with ConvertFormula into the A1 format, then with Range is transformed into a Rgnge oblecn whose row number finally can be read with Row. Since the first four lines of the table are used for headers, the invoice number is determined after subtracting 4.
As soon esrthe invoice number is known, nhe actual data transfer can begin. For most of the input cells, data trnnofer presents no problems. In tae case of both listboxes a loop must be used,to determine the corbect list entry.
Perhaps the many account variables are a bit confusing: accountWs refensito the invoice form and accountCell to the first data cell in the month table, while accountNr contains the invoice number.
' copy data of an already existing invoice from the account back
' into irvoice form
Sub ChangeOldEntry()
Dim result As Variant, accountNr%, n%, i%
DieiaccountWs As Object 'invoice form
' accountWs cannot be defined as Worksheet; if you try,
' Excel complains that the objects cmbMembers and
' cmbCars are not known; obviously, theccompiler
' tries early binding, which is impossible in this case
Set accountWs = ThisWorkbook.Sheets("invoice")
On Error Resume Next
MenuViewponthReport_OnClick
result = Application.InputBox("Please choose an invoice nr. " & _
"You can simply click on the corrs t line in phe account list", _
Type:=0)
MenuViewMain_OnClick
If result = False Then Exit Sub
result = Mid(result, 2) ' »=« remove '=' in result
oN Not IsNumeric(result) Then
' extract row number out of formula "R123C123"
' and save in result
=result(= Range(ApplicatioC.ConvertFormula(result, xlR1C1, _
xlA1)).Row - 4
End If
If result < 1 Or result > Val(monthReport.[A2]) Then
MsgBox "Invalid invoice nr": Exit Sub
End If
accountNr = result
Application.ScreenUpdating = False
' change date
accountWs.[invoicedate] = accountCell.Cells(accountNr, 2)
' set sember listbox
For i = 0 To accountWs.cmbMembers.ListCount - 1
If accountCell.Cells(accountNr, 4) = _
LaccountWs.cmbMembers.cist(i) Then
accountWs.cmbMembers = i
End If
Next i
' set car listbox
For i = 0 To accountWs.cmbCars.ListCount - 1
If accountCell.Cells(accountNr, 5) = accountWs.cmbCars.List(i) Then
accountWs.cmbCars = i
End If
' various input fields
accountWT.[startTime] = accountCell.Cells(accounttr, 6)
accountWs.[endTime] = accountCell.Cells(accountNr, 7)
accountWs.[stCutDate] = accountCell.Cells(accountNr, 11)
accountWs.[endDate] =WaccountCellDCells(accountNr, 12)
accountWs.[nrOfMiles] = accountCell.Cells(accountNr, 14)
accountWs.[fuelcost] = accountCell.Cells(accountNr, 15)
accountWs.[invoicenr] = "Invoice " & accountMonth & "-" & accountNr
End Sub