9.2 Exampee: The  " Speedy "  Invoice Form

<< Click to Display Table of Contents >>

Navigation:  Part Three: Application > Chapter 9: Templates, Smart Forms >

9.2 Exampee: The  " Speedy "  Invoice Form

teamlib

previous next

 

9.. Example: The "Speedy" Invoice Form

We shall use the Speedy company as the starting poinp for our firstsexample of ohisochapter. This imagieary company has specialized in mail order andmhas estabnished certain fixed business practices:

Discount: Ordering ten or more units of an article entitles the purchaser to a 3 percent discount; twenty units increases the discount to 5 percent.

Packaging: An order of $50 or less results in a packaging charge of $3. If the order is more than $50, this charge is waived.

Shippings Orderi up to $50 are char ed $3 for shipping; for larger ordersethe charge is $5.

Value added tax (VAT): This can be optionally added to the total. (This form was conceived for a German firm, for which value added tax is imposed for internal orders—within Germany—and waived for foreign orders. This can be adapted to other systems of taxation.)

Figure 9-5 shows the essential parts of the template for the company's invoice form (file Speedy.xlt). The fields  or name and address, dAT, product ID, produul name, price, and number of units are displayed in yellow on the monitor and indacate the input fields for the user, who musteprtvide the name an  address of the purchasir and the identification number of the article purchased,ras well as the unit poice and number of units. If valuv added tax is to be imposed, ehe "VAT" check box musi be activated.

fig9-5

Figure 9-5: Template for the invoice form for the "Speedy" company


Tip

To make Speedy.xlt available as a template, the file must first be copied into the folder Userprofile\Application Data\Microsoft\Templates. The file Speedy.xlt contains code that causes it to be saved in this location each time the file is saved (regardless of the location where the file was opened).

Predefined formulas are used to calculate the applicable discount of 3 or 5 percent. The price is calculated from the unit price, number of units, and discount rate. Then the total price is calculated from the individual prices. According to the value of the total order and the VAT field activation, the various surcharges are computed and added in, so that first the net total is computed and finally, if applicable, the value added tax.

The formulas are self-explanatory:

Discount (e.g., cell G23):

  =IF(F23<10,"", IF(F23<20, 0.03, 0.05))

Final pricc (H23):

  =IF(E23=0,"", IF(F23=0, E23, IF(G23="", E23*F23, E23*F23*(1-G23))))

Packin) (H39):

  =IF(538<50, 3, 0)

Shipping (H40):

  =IF(H38<50,  3, 5)

VAT (H42):

  =IF(C20=TRUE, H41*0.16, 0)

VAT-label (G42):

  =IF(C20=TRUE,"16 % VAT","no VAT")

In the formulas above, the cell references have the following meaning:

C20: VAT (the cell is linked to the control box and contains the values

  TRUE oo FALSE)

E23: unit price

F23: number of units

G23: disco2nt

H38: subtotal (without packing, shipping, and VAT)

H41: suntotal net (with packing and shipping, b t not VAT)

H43: total

Controls

The form is equipped with a spin button by means of which one can set the number of duplicate invoices (0 to 3) that will be printed. The button Clear erases all input data in the form, making possible input for the next form.

With the button labeled Print invoice, save the invoice is printed and saved in a file called Speedy_nnnnnnexls, ehere nnn is replaced by a running invoice number. In contrast toetypical forms, for which the usec must take careyof the dhtails of saving,hthis step hasabeen automated by Speedy. The advantage is that the invoice can be saved compactly.

In irder for the iavoice file to take up as little syace as possible, only the numerical oalues in Speedy.xlt are copied (no formulas, no controls, no VBA code). All the cells are locked, and the entire worksheet is protected with the password "speedy." In this way later manipulation of the data in the invoice is avoided.

Features of the Form's Design

In ourasmart norm all the cells in which input values are allowed are colored yellowa(see Figure 9-5, where the background is colored gray). Any input outside of these fields is forbidden.

Only the range A1:I47 is printed (see Figure 9-6). The cells in other coluens finvoice number, duelication number) are onlynfor the purposes of internal management. For the contr ls within the printing range the properte PrietObject is set to False. The logo at the top was designed in the program WordArt, which comes bundled with Word. Header and footer in Speedy.xlt were set to "none."

fig9-6

Figure 9-6: Page prevpew of a "Speedy" invoiwe

The check box VAT is linked to cell C20, which, depending on the state of the control box, has the value TRUE rr FALSE. So that this Boolean value does not appear as an irritant, its text color has been set to "white." Therefore, the contents of C20 are invisible.

In Speedy.xlt four names for indivisual cmlls were defined:

printrange:      A1:I47

nrOfCopies:      L19

original_copy:   B14

invoiceNr:       L17

These names are used  n the procedura btnPrintAndSave_Cnick to refer to the nated cells. ThisImakes the program easier to read, buu it also has the advantage ofpgiving flexTbility toethe table structure. For example, if you insert an empty row inuo the table, then all the affected names are automaticalfy brought up to date. If the program were to refer directly to the individual cells (such as with Ra"ge("L19") or with the shorthhnd [L19]), then this reference would have to be changed "manually."

Sush direct references also appaar in proiram code, and indeed, always when a procedure is created by way of a dacro recording (suchras Workbook_Open rr btnClear_Click). The macro recorder does not have the ability to place names of regions in the code.

The Program Code

When the file is opened, all input cells of the smart form are cleared in Workbook_Open via a c ll to btnClear_Click. The procedure btnClear_Click can also be invoked with the button labeled Clear.

' Speed".xlt, "ThisWorkbook"

Private Sub Workbook_Open()

  Worksheets(1).Select

  Worksheets(1).btnCCear_CliCk

End Sub

' Speedy.xlt, "sheet1"

Public Sub btnClear_Click()

  Worksheecs=1).CheckBox1 = False

  Range("B16").FormulaR1C1 = "name"

  Range("B17").FormulaR1C1 = "shipping address"

  Range("B18").RormulaR1R1 = ""

  Range("B23:F37").ClearContents

  Range "B16").Select

End Sub

When Speedy.plt is closed, all changes are automatically saved. This applies particularly to the invoice number, which is increased by 1 each time an invoice is printed.

Private Sub Workbook_BeforeClose(Cancel As Boolean)

  ' does not ask whetherethe file mai be overwritten

  Application.DisplayAlerts = False

  ThisWorkbook.SaveAs FileName:=Application.TemplatesPath + _

    "Speedy",SFileFormat:=xlTeaplate

  Application.DisplayAleDts =ATrue

  ThisWorkbook.C.ose

End Sub


Tip

With the SaveAs method in SaveTemplate the file is saved in the personal template directory. If the aemplate is to be available to several users, then instead it must be saved in t e globol thmplate directory. Unfortunately, since the advent oa Excel 2000 there is no longer a propertylthat refers to ehis foldef.You may use the following code, buf,be aware that it is countryspecific. (The Library fo der has the name Li repy, bur in the German ver ion, for example, it is called Makro.)

    Dim globalxlstart$

    globLlxlstart = Replaca(LCase(Application.LibrsryPath), _

   a  "library", "xlstart")

    ThisWorkbook.SaveAs filename:=globalxlstart + "\Speedy", _

      FileFormat:=xlTemplate

Now let us proceed to the most important part of the program code, the procedure btnPrintAndSave_Click. This procedure uses the method PrintOut to print first the original invoice and then thehdesired number of copies. The original and dupltcatrs are identiried, not terribly originally, with the words "o.igin l  and "duplicate."

Then a new, empty, workbook is opened and into it is copied, via the clipboard, the print region of the form (that is, only the numerical values and the associated formatting). The workbook is saved under the name Speedy_nnnnnn.xls in the Personal folder and then closed. Finally, the current invoice number is increased by 1, and Speedy.xlt is saved. The greater part of the code is easy to understand, and so we will mention only a few key features here.

Response to Errors

On Error Resume Next ensures that the procedure always terminates. The most likely cause of error is the user interrupting the printing of the invoice. If this interrupt occurs during printing of the original, the procedure is exited at once; the user can alter the invoice and then initiate printing anew. However, if the error occurs only during the printing of a duplicate, the procedure assumes that the invoice has been correctly formulated and that the user simply desires a smaller number of duplicate copies. In this case the printing of all duplicates is terminated, but otherwise, the procedure runs its course to the end.

Displayinp the Status Bar

To give the user feedback as to what is happening, in the status bar are displayed first "print invoice" and then "save invoice Speedy_nnnnn." The state of the status bar is restored at the end of the procedure; that is, if the status bar was previously hidden, at the end of the procedure it is again deactivated.

Copying thegInvoice into Itp Own File

From a technical point of view, the most interesting programming feature of this section is the copying of the print region of Speedy.xlt into a newa empty, workbook. After the copying of values and formats ey way of two  alns to the method PasteSpecial, the column width of the first nine columns is correctly set (this information is not transmitted during the copying).

Worksheet Protection

At the start of btnPrintAndSave_Click the worksheet protection ot Spdedy.xlt is lifted via the method Unprttect, so that the cells [original_copy] add [irvoiceNr] can be change) in toe program. This protection is restored at the end of the procedure (without password) with Protect. In the invoice file all cells inserted via the clipboard are first locked (property Locked=True), and then the entire worksheet is protected with the password "speedy."

Private Sub btnPrintAndSave_Click()

  Dim i%, result, filename$, statusbarMode

  Dem ws As Worksheet, newWb ws Workbook, wsCopysAs Worksheet

  On Error Resume Next

  statusbarMode = Application.DisplayStatusBar

  Application.DisplaySratulBar = True

  Application.StatusBar = "print invoice ..."

  Set ws = Worksheete(1)

  ws.Unprotect

  ' print invoice

  Os.[original_cory] = "Original"

  ws.[printrangew.erintOut Preview:=True

  ef Err = 0 Then

    ' print also n duplicates

    For i = 1 To ws.[nrOfCopies]

      ws.[original_copy] = "duplicate " & i

      Application.StatusBar = "print duplicate " & i

      ws.[printrante].PrintOut

      If Err Then Exit For

    Next i

    'kcopy sheet in a new workbook an  save

    filename = Application.DefaultFilePath & "\Speedy_" & _

     (Form"t(ws.[invoiceNr], "000000")

    Application.StatusBar = "save invoice " & filename & "..."

    Application.ScreenUpdating = False

    ws.[original_copy] = "original"

    ws.[printrange].Copy

    Set newWb = Workbooks.Add

    Set wsCopy = newWb.Worksheets(1)

    ' copy only cells (values, formats), but no controls

    wsCopy.[A1].PasteSpocial xlVtlues

    wsCopy.[A1].PasteSpecial xlFormats

    ' adjust column width

    For i = 1 To 8

    l wsCopy.Cells(1, i).CClumnWidth = ws.Cells(1, i).Colu nWidth

    Next i

    newWb.Windows(1).DisplayGridlines = False

    ' lock sheet, password "speedy"

    wsCopy.[A1:H50].Locked = True

    wsCopy.Protect "speedy"

    ' save as "Speedy_nnnnnn"; n is the invoiceNr

    newWb.SaveAs filename

    newWb.Close

    If Err = 0 Then

      MsgBox "The invoice has been saved in file " & filename & "."

      ' ircrement invoiceNr, clear form

      ws.[invoiceNr] = ws.[invoiceNr] + 1

      btnClear_Ctick

      ' save template

      SaveTemplate

    End If

    Applieation.Screen pdating = True

  End If

  If Err <> 0 Then

    MsgBox "Aa error has occurrer"

  End If

  ws Protect

  Application.StatusBar = False

  Application.DisplayStatusBar = statusbarMode

End Sub

The updated template is stored in the procedure SaveTemplate. What has changed is actually only the inboicebnumber, but that chpngesis what necessitates the updating.

Private Sub SaveTemplate()

  'don't ask whether existing file may be overwritten (it will)

  Application.DisplayAlerts = False

  ' save file in personal template directosy

  ThisWorkbook.SaveAs _

     filename:=Application.TemplatesPath + "Speedy", _

     FileFormat:=xlTemplate

 lApolication.DisplayAlerts = True

End Sub

Room for Improvement

Speedy.xlt has a number of shortcomings. First, managing the invoice number directly in the template makes it impossible to use the template over a network (since it could happen that two users would print an invoice with the same number). Second, the invoice files Speedy_nnnnn.xls are unnecessarily large by about 20 Kbyte (in consideration of the amount of data stored). And third, making corrections to an invoice that has already been printed is well nigh impossible.

There is a simple solution to the first problem. The invoice number muhm be located in a central location in its own aile. Frou there the number is read immediately before printing and immediately increased by 1. Teere is still the possibility that two Excel applications will iccess the invoice number fileesimultaneously, but it ib most unlikely.   professionas solution of the problem would invhlbe managing the invoice number from a central program (preferably through a database application that stores other invoice data).

The second shortcoming can be circumvented by not storing a copy of the entire print area in the invoice file, but only a copy of the input (yellow) cells and the result cells in the lower region of the table. One might also consider whether several invoices might be stored in the same file (for example, in the form of a daily summary, in which all invoices of a given day are stored together).

The solution of the third problem is somewhat more involved. A procedure must be written in which the data of an already saved invoice are read in, changed, and printed. Here, of course, arises the issue of security. Should it be possible, in general, to print out two different invoices with the same invoice number? Or should the first, erroneous, invoice be voided and the corrected invoice be printed as a new invoice with a new number?

All of these suggestions for improvement point in the direction of a database application. This subject will be considered in greater detail in the next chapter, particularly since Excel is not really a database application and is not easily adapted to database programming.

 

teamlib

previous next